summaryrefslogtreecommitdiffstats
path: root/src/Zettel/Types.hs
blob: 65d738e13303bb83fd89eafb8ac996bea4271bb3 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}

module Zettel.Types
  ( Combine (..),
    UseCombine (..),
    ZettelId (..),
    ZettelCat (..),
    ZettelTag (..),
    ZettelMetadata (..),
    Zettel (..),
    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
    zettelCats :: [ZettelCat],
    -- | Author
    zettelAuthor :: Maybe Text
  }
  deriving (Show, Eq)

instance Combine ZettelMetadata where
  cappend (ZettelMetadata c m t a b) (ZettelMetadata c' m' t' a' b') =
    ZettelMetadata (cappend c c') (cappend m m') (cappend t t') (cappend a a') (cappend b b')

  cempty = ZettelMetadata cempty 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,
    zettelNext :: [ZettelId],
    zettelPrev :: [ZettelId]
  }
  deriving (Show, Eq)

instance Combine Zettel where
  cappend (Zettel b c d e f) (Zettel b' c' d' e' f') =
    Zettel (cappend b b') (cappend c c') (cappend d d') (cappend e e') (cappend f f')

  cempty = Zettel cempty cempty cempty cempty cempty

newtype ZettelGraph = ZettelGraph {unZettelGraph :: Map ZettelId Zettel}
  deriving (Show, Eq)