Skip to content

Commit

Permalink
Document IDScheme.hs
Browse files Browse the repository at this point in the history
  • Loading branch information
srid committed Aug 31, 2020
1 parent 170d3cf commit 7140f96
Showing 1 changed file with 19 additions and 4 deletions.
23 changes: 19 additions & 4 deletions neuron/src/app/Neuron/Zettelkasten/ID/Scheme.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,13 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Neuron.Zettelkasten.ID.Scheme where
module Neuron.Zettelkasten.ID.Scheme
( nextAvailableZettelID,
genVal,
IDScheme (..),
IDConflict (..),
)
where

import Control.Monad.Except
import Data.GADT.Compare.TH
Expand All @@ -21,9 +27,13 @@ import Relude
import Text.Megaparsec.Simple
import Text.Show

-- | The scheme to use when generating new IDs
data IDScheme a where
-- | Legacy date IDs (deprecated)
IDSchemeDate :: Day -> IDScheme ()
-- | Random IDs (default)
IDSchemeHash :: IDScheme UUID
-- | Custom ID (specified by the user)
IDSchemeCustom :: Text -> IDScheme ()

data IDConflict
Expand All @@ -44,7 +54,7 @@ instance Show IDConflict where
IDConflict_BadCustomID s e ->
"The custom ID " <> toString s <> " is malformed: " <> toString e

-- | Produce a value that is required to run an ID scheme.
-- | Produce a value that is required ahead to run an ID scheme.
genVal :: forall a. IDScheme a -> IO a
genVal = \case
IDSchemeHash ->
Expand All @@ -54,13 +64,18 @@ genVal = \case
IDSchemeCustom _ ->
pure ()

-- | Create a new zettel ID based on the given scheme without conflicting with
-- the IDs of existing zettels.
-- | Create a new zettel ID based on the given scheme
--
-- This is a pure function, with all impure actions done in @genVal@
--
-- Ensures that new ID doesn't conflict with existing zettels.
nextAvailableZettelID ::
forall a.
-- Existing zettels
Set ZettelID ->
-- Seed value for the scheme
a ->
-- Scheme to use when generating an ID
IDScheme a ->
Either IDConflict ZettelID
nextAvailableZettelID zs val = \case
Expand Down

0 comments on commit 7140f96

Please sign in to comment.