summaryrefslogtreecommitdiffstats
path: root/src/Zettel/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Zettel/Types.hs')
-rw-r--r--src/Zettel/Types.hs106
1 files changed, 106 insertions, 0 deletions
diff --git a/src/Zettel/Types.hs b/src/Zettel/Types.hs
new file mode 100644
index 0000000..26dee7f
--- /dev/null
+++ b/src/Zettel/Types.hs
@@ -0,0 +1,106 @@
+{-# LANGUAGE DerivingVia #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE StandaloneDeriving #-}
+
+module Zettel.Types
+ ( Combine (..),
+ UseCombine (..),
+ ZettelId (..),
+ ZettelCat (..),
+ ZettelTag (..),
+ ZettelMetadata (..),
+ Zettel (..),
+ ZettelNode (..),
+ ZettelGraph (..),
+ )
+where
+
+import Text.Pandoc.Builder (ToMetaValue (..))
+import Text.Pandoc.Definition (Inline (..), Pandoc (..))
+
+class Combine a where
+ cappend :: a -> a -> a
+ cempty :: a
+
+newtype UseCombine a = UC a
+
+instance (Monoid a) => Combine (UseCombine a) where
+ cappend (UC a) (UC b) = UC $ a <> b
+ cempty = UC mempty
+
+deriving via (UseCombine Text) instance Combine Text
+
+deriving via (UseCombine Pandoc) instance Combine Pandoc
+
+deriving via (UseCombine [a]) instance Combine [a]
+
+instance Combine (Maybe a) where
+ cappend Nothing a = a
+ cappend a _ = a
+
+ cempty = Nothing
+
+-- | The ZettelId is just Text, however, it should also be possible to convert
+-- it to a list of the ID split up into it's parts.
+newtype ZettelId = ZettelId {unZettelId :: Text}
+ deriving (Show, Eq, Ord, IsString, ToString, Semigroup, Monoid, ToMetaValue)
+ deriving (Combine) via (UseCombine ZettelId)
+
+newtype ZettelTag = ZettelTag {unZettelTag :: Text}
+ deriving (Show, Eq, Ord, IsString, ToString, Semigroup, Monoid, ToMetaValue)
+ deriving (Combine) via (UseCombine ZettelId)
+
+newtype ZettelCat = ZettelCat {unZettelCat :: Text}
+ deriving (Show, Eq, Ord, IsString, ToString, Semigroup, Monoid, ToMetaValue)
+ deriving (Combine) via (UseCombine ZettelId)
+
+data ZettelMetadata = ZettelMetadata
+ { -- | Optional creation date of the Zettel.
+ zettelCreationDate :: Maybe Text,
+ -- | Optional last modified date of the Zettel.
+ zettelModifiedDate :: Maybe Text,
+ -- | Optional tags.
+ zettelTags :: [ZettelTag],
+ -- | Optional Category
+ zettelCategory :: [ZettelCat]
+ }
+ deriving (Show, Eq)
+
+instance Combine ZettelMetadata where
+ cappend (ZettelMetadata c m t a) (ZettelMetadata c' m' t' a') =
+ ZettelMetadata (cappend c c') (cappend m m') (cappend t t') (cappend a a')
+
+ cempty = ZettelMetadata cempty cempty cempty cempty
+
+data Zettel = Zettel
+ { -- | The title of the Zettel, which should also be present in the body,
+ -- however, this is useful to gather metadata about the Zettel.
+ zettelTitle :: ![Inline],
+ -- | Zettel metadata which is mostly optional.
+ zettelMetadata :: ZettelMetadata,
+ -- | The text body of the Zettel, which is stored as a Pandoc document to
+ -- make it easy to export to other documents.
+ zettelBody :: Pandoc
+ }
+ deriving (Show, Eq)
+
+instance Combine Zettel where
+ cappend (Zettel b c d) (Zettel b' c' d') =
+ Zettel (cappend b b') (cappend c c') (cappend d d')
+
+ cempty = Zettel cempty cempty cempty
+
+data ZettelNode = ZettelNode
+ { zettelNodeZettel :: Zettel,
+ zettelNodeNext :: [ZettelId],
+ zettelNodePrev :: [ZettelId]
+ }
+ deriving (Show, Eq)
+
+instance Combine ZettelNode where
+ cappend (ZettelNode b c d) (ZettelNode b' c' d') =
+ ZettelNode (cappend b b') (cappend c c') (cappend d d')
+
+ cempty = ZettelNode cempty cempty cempty
+
+newtype ZettelGraph = ZettelGraph {unZettelGraph :: Map ZettelId ZettelNode}