Skip to content

Commit

Permalink
Release 0.2 (#71)
Browse files Browse the repository at this point in the history
* Pin rib at 0.8 release

* Up ver to 0.2

* Fix version spec

* Add synopsis and description

* Update haddocks

* Pin base to make hackage happy

* Update minVersion

* Add more fields to cabal
  • Loading branch information
srid authored Apr 8, 2020
1 parent 078b2d2 commit 274bcaf
Show file tree
Hide file tree
Showing 11 changed files with 80 additions and 28 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
# Change Log for neuron

## 0.2.0.0

- Initial public release
2 changes: 1 addition & 1 deletion default.nix
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ let
# To upgrade rib, go to https://github.com/srid/rib/commits/master, select the
# revision you would like to upgrade to and set it here. Consult rib's
# ChangeLog.md to check any notes on API migration.
ribRevision = "a5171e7";
ribRevision = "19b1022442a0cde2a0b1d9373b0397030472721e";
projectRoot = ./.;
in {
# Rib library source to use
Expand Down
18 changes: 16 additions & 2 deletions neuron.cabal
Original file line number Diff line number Diff line change
@@ -1,11 +1,25 @@
cabal-version: 2.4
name: neuron
-- This version must be in sync with what's in Default.dhall
version: 0.1.0.0
version: 0.2.0.0
license: BSD-3-Clause
copyright: 2020 Sridhar Ratnakumar
maintainer: [email protected]
author: Sridhar Ratnakumar
category: Web
homepage: https://neuron.srid.ca
bug-reports: https://github.com/srid/neuron/issues
synopsis:
Haskell meets Zettelkasten, for your plain-text delight.
description:
neuron is a system for managing your plain-text Zettelkasten notes.
extra-source-files:
README.md
CHANGELOG.md

source-repository head
type: git
location: https://github.com/srid/neuron

common ghc-common
ghc-options:
Expand All @@ -18,7 +32,7 @@ common library-common
hs-source-dirs: src
default-language: Haskell2010
build-depends:
base,
base >=4.7 && <5,
aeson,
clay -any,
containers,
Expand Down
2 changes: 1 addition & 1 deletion src-dhall/Config/Default.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -9,5 +9,5 @@
, mathJaxSupport =
True
, minVersion =
"0.1"
"0.2"
}
5 changes: 3 additions & 2 deletions src/Neuron/Version.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Neuron version
module Neuron.Version where

import qualified Data.Text as T
Expand All @@ -12,14 +11,16 @@ import Paths_neuron (version)
import Relude
import Text.ParserCombinators.ReadP (readP_to_S)

-- | Neuron cabal library version
neuronVersion :: Text
neuronVersion = toText $ showVersion version

-- | Neuron full version (cabal library version + git revision)
neuronVersionFull :: Text
neuronVersionFull =
T.concat [neuronVersion, " (", RepoVersion.version, ")"]

-- | Check if neuronVersion is older than the given version
-- | Check if `neuronVersion` is older than the given version
olderThan :: Text -> Bool
olderThan s =
case reverse (readP_to_S parseVersion (toString s)) of
Expand Down
17 changes: 14 additions & 3 deletions src/Neuron/Zettelkasten.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,19 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Main module for using neuron as a library, instead of as a CLI tool.
module Neuron.Zettelkasten
( generateSite,
( -- * CLI
App (..),
NewCommand (..),
commandParser,
run,
runWith,

-- * Rib site generation
generateSite,

-- * Etc
newZettelFile,
)
where
Expand Down Expand Up @@ -67,6 +75,7 @@ data Command
Rib Rib.App.Command
deriving (Eq, Show)

-- | optparse-applicative parser for neuron CLI
commandParser :: Parser App
commandParser =
App
Expand Down Expand Up @@ -164,10 +173,12 @@ generateSite writeHtmlRoute' zettelsPat = do
writeHtmlRoute Z.Route_IndexRedirect
pure (zettelStore, zettelGraph)

-- | Create a new zettel file and return its slug
-- TODO: refactor this
-- | Create a new zettel file and open it in editor if requested
--
-- As well as print the path to the created file.
newZettelFile :: Path b Dir -> NewCommand -> IO ()
newZettelFile inputDir NewCommand {..} = do
-- TODO: refactor this function
zId <- Z.zettelNextIdForToday inputDir
zettelFileName <- parseRelFile $ toString $ Z.zettelIDSourceFileName zId
let srcPath = inputDir </> zettelFileName
Expand Down
11 changes: 9 additions & 2 deletions src/Neuron/Zettelkasten/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,11 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Zettelkasten config
module Neuron.Zettelkasten.Config where
module Neuron.Zettelkasten.Config
( Config (..),
getConfig,
)
where

import Data.FileEmbed (embedFile)
import Development.Shake (Action, readFile')
Expand All @@ -23,6 +26,9 @@ import Path.IO (doesFileExist)
import Relude
import qualified Rib

-- | Config type for @neuron.dhall@
--
-- See <https://neuron.srid.ca/2011701.html guide> for description of the fields.
makeHaskellTypes
[ SingleConstructor "Config" "Config" "./src-dhall/Config/Type.dhall"
]
Expand All @@ -34,6 +40,7 @@ deriving instance FromDhall Config
defaultConfig :: ByteString
defaultConfig = $(embedFile "./src-dhall/Config/Default.dhall")

-- | Read the optional @neuron.dhall@ config file from the zettelksaten
getConfig :: Action Config
getConfig = do
inputDir <- Rib.ribInputDir
Expand Down
25 changes: 20 additions & 5 deletions src/Neuron/Zettelkasten/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,22 @@
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Graph of zettels.
module Neuron.Zettelkasten.Graph where
module Neuron.Zettelkasten.Graph
( -- * Graph type
ZettelGraph,

-- * Construction
mkZettelGraph,

-- * Algorithms
backlinks,
topSort,
zettelClusters,
dfsForestFrom,
dfsForestBackwards,
obviateRootUnlessForest,
)
where

import qualified Algebra.Graph.AdjacencyMap as AM
import qualified Algebra.Graph.AdjacencyMap.Algorithm as Algo
Expand All @@ -23,9 +37,10 @@ import Neuron.Zettelkasten.Store (ZettelStore)
import Neuron.Zettelkasten.Type
import Relude

-- | The Zettelkasten graph
type ZettelGraph = LAM.AdjacencyMap [Connection] ZettelID

-- | Build the entire Zettel graph from the given list of note files.
-- | Build the Zettelkasten graph from the given list of note files.
mkZettelGraph :: ZettelStore -> ZettelGraph
mkZettelGraph store =
mkGraphFrom (Map.elems store) zettelID zettelEdges connectionWhitelist
Expand Down Expand Up @@ -58,8 +73,8 @@ topSort = Algo.topSort . LAM.skeleton

-- | Get the graph without the "index" zettel.
-- This is unused, but left for posterity.
withoutIndex :: ZettelGraph -> ZettelGraph
withoutIndex = LAM.induce ((/= "index") . unZettelID)
_withoutIndex :: ZettelGraph -> ZettelGraph
_withoutIndex = LAM.induce ((/= "index") . unZettelID)

zettelClusters :: ZettelGraph -> [NonEmpty ZettelID]
zettelClusters = mothers . LAM.skeleton
Expand Down
3 changes: 1 addition & 2 deletions src/Neuron/Zettelkasten/ID.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Zettel ID
module Neuron.Zettelkasten.ID
( ZettelID (..),
Connection (..),
Expand All @@ -28,7 +27,7 @@ import System.Directory (listDirectory)
import qualified System.FilePattern as FP
import Text.Printf

-- Short Zettel ID encoding `Day` and a numeric index (on that day).
-- | Short Zettel ID encoding `Day` and a numeric index (on that day).
--
-- Based on https://old.reddit.com/r/Zettelkasten/comments/fa09zw/shorter_zettel_ids/
newtype ZettelID = ZettelID {unZettelID :: Text}
Expand Down
2 changes: 1 addition & 1 deletion src/Neuron/Zettelkasten/Link.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import Relude
import qualified Text.MMark.Extension as Ext
import Text.MMark.Extension (Extension, Inline (..))

-- | MMark extension to transform `z:/` links in Markdown
-- | MMark extension to transform @z:/@ links in Markdown
linkActionExt :: ZettelStore -> Extension
linkActionExt store =
Ext.inlineRender $ \f -> \case
Expand Down
18 changes: 9 additions & 9 deletions test/Neuron/VersionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,20 +15,20 @@ import Test.Hspec
spec :: Spec
spec = do
describe "Application version" $ do
-- TODO: More checks. This one is trivial and unnecessary, just for testing tests.
it "should have dots" $ do
neuronVersion `shouldSatisfy` T.isInfixOf "."
it "should contain the git rev" $ do
pending
-- TODO: Check minVersion in Default.dhall is same as the one in Paths_neuron
describe "Version comparison" $ do
it "must compare simple versions" $ do
"0.2" `shouldSatisfy` olderThan
"0.1" `shouldNotSatisfy` olderThan -- This is current version
"0.0" `shouldNotSatisfy` olderThan
"0.3" `shouldSatisfy` olderThan
"0.2" `shouldNotSatisfy` olderThan -- This is current version
"0.1" `shouldNotSatisfy` olderThan
it "must compare full versions" $ do
"0.2.1.2" `shouldSatisfy` olderThan
"0.2.3" `shouldSatisfy` olderThan
"0.1.0.0" `shouldNotSatisfy` olderThan -- This is current version
"0.0.1.0" `shouldNotSatisfy` olderThan
"0.3.1.2" `shouldSatisfy` olderThan
"0.3.3" `shouldSatisfy` olderThan
"0.2.0.0" `shouldNotSatisfy` olderThan -- This is current version
"0.1.1.0" `shouldNotSatisfy` olderThan
it "must compare within same major version" $ do
"0.1.0.2" `shouldSatisfy` olderThan -- 0.1.0.0 is the current version
"0.2.0.2" `shouldSatisfy` olderThan -- This is current version

0 comments on commit 274bcaf

Please sign in to comment.