summaryrefslogtreecommitdiffstats
path: root/src/Zettel.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Zettel.hs')
-rw-r--r--src/Zettel.hs63
1 files changed, 43 insertions, 20 deletions
diff --git a/src/Zettel.hs b/src/Zettel.hs
index a576143..d754741 100644
--- a/src/Zettel.hs
+++ b/src/Zettel.hs
@@ -1,30 +1,51 @@
+{-# Language GeneralizedNewtypeDeriving #-}
+{-# Language DerivingVia #-}
+{-# Language StandaloneDeriving #-}
+
module Zettel where
-import Text.Pandoc.Class (runIOorExplode)
-import Text.Pandoc.Definition (Block (..), Inline (..), Pandoc (..))
-import Text.Pandoc.Readers (readOrg)
-import Text.Pandoc.Writers (writeHtml5String, writeMarkdown)
-import Text.Pandoc.Shared (stringify)
-import Text.Pandoc.Walk (walkM)
+import Text.Pandoc.Definition (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
newtype ZettelId = ZettelId
{ -- | 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.
unZettelId :: Text
}
- deriving (Show, Eq, Ord)
+ deriving (Show, Eq, Ord, IsString, ToString, Semigroup, Monoid)
+ deriving (Combine) via (UseCombine ZettelId)
+
+data ZettelMetadata = ZettelMetadata
+ { -- | Optional creation date of the Zettel.e
+ zettelCreationDate :: Maybe Int,
+ -- | Optional last modified date of the Zettel.
+ zettelModifiedDate :: Maybe Int
+ }
+ deriving (Show, Eq)
-instance IsString ZettelId where
- fromString = ZettelId . fromString
+instance Combine (Maybe a) where
+ cappend Nothing a = a
+ cappend a _ = a
-instance ToString ZettelId where
- toString = toString . unZettelId
+ cempty = Nothing
-instance Semigroup ZettelId where
- ZettelId a <> ZettelId b = ZettelId $ a <> b
+instance Combine ZettelMetadata where
+ cappend (ZettelMetadata c m) (ZettelMetadata c' m') =
+ ZettelMetadata (cappend c c') (cappend m m')
-instance Monoid ZettelId where
- mempty = ZettelId mempty
+ cempty = ZettelMetadata cempty cempty
data Zettel = Zettel
{ -- | The ID that is assigned to the Zettel.
@@ -34,12 +55,14 @@ data Zettel = Zettel
zettelTitle :: !Text,
-- | The text body of the Zettel, which is stored as a Pandoc document to make it
-- easy to export to other documents.
- zettelBody :: Pandoc
+ zettelBody :: Pandoc,
+ -- | Zettel metadata which is mostly optional.
+ zettelMetadata :: ZettelMetadata
}
deriving (Show, Eq)
-instance Semigroup Zettel where
- Zettel a b c <> Zettel _ _ c' = Zettel a b $ c <> c'
+instance Combine Zettel where
+ cappend (Zettel a b c d) (Zettel a' b' c' d') =
+ Zettel (cappend a a') (cappend b b') (cappend c c') (cappend d d')
-instance Monoid Zettel where
- mempty = Zettel mempty mempty mempty
+ cempty = Zettel cempty cempty cempty cempty