1 {-# LANGUAGE DisambiguateRecordFields #-}
2 {-# LANGUAGE DuplicateRecordFields #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
5 module Language.DTC.Document
6 ( module Language.DTC.Document
10 import Data.Default.Class (Default(..))
11 import Data.Default.Instances.Containers ()
13 import Data.Function (on)
15 import Data.Map.Strict (Map)
16 import Data.Maybe (Maybe(..))
17 import Data.Monoid (Monoid(..))
18 import Data.Ord (Ord(..))
19 import Data.Semigroup (Semigroup(..))
20 import Data.Sequence (Seq)
21 import Data.Text (Text)
22 import Data.TreeSeq.Strict (Tree, Trees)
23 import Text.Show (Show)
33 instance Default Document where
44 instance Default Head where
55 , editor :: Maybe Entity
61 , includes :: [Include]
63 instance Default About where
76 instance Semigroup About where
78 { titles = titles x <> titles y
79 , url = url (x::About) <> url (y::About)
80 , authors = authors x <> authors y
81 , editor = editor x <> editor y
82 , date = date x <> date y
83 , version = version x <> version y
84 , keywords = keywords x <> keywords y
85 , links = links x <> links y
86 , series = series x <> series y
87 , includes = includes x <> includes y
91 type Body = Trees BodyKey BodyValue
95 = Section { pos :: Pos
96 , attrs :: CommonAttrs
102 -- ** Type 'BodyValue'
105 , attrs :: CommonAttrs
109 , attrs :: CommonAttrs
112 | Figure { pos :: Pos
113 , attrs :: CommonAttrs
119 , attrs :: CommonAttrs
122 | References { pos :: Pos
123 , attrs :: CommonAttrs
124 , refs :: [Reference]
132 { posAncestors :: PosPath
133 , posAncestorsWithFigureNames :: PosPath
134 , posPrecedingsSiblings :: Map XmlName Rank
136 instance Ord Pos where
137 compare = compare `on` posAncestors
138 instance Default Pos where
139 def = Pos mempty mempty mempty
141 -- *** Type 'PosPath'
142 type PosPath = Seq (XmlName,Rank)
148 type Words = [WordOrSpace]
150 -- **** Type 'WordOrSpace'
154 deriving (Eq,Ord,Show)
157 type Aliases = [Words]
160 type Terms = [Aliases]
168 , attrs :: CommonAttrs
172 , attrs :: CommonAttrs
176 , attrs :: CommonAttrs
179 | Artwork { pos :: Pos
180 , attrs :: CommonAttrs
186 -- * Type 'CommonAttrs'
194 type Blocks = [Block]
202 type Para = Seq Lines
205 type Lines = Tree LineKey LineValue
220 | Iref {anchor :: Maybe Anchor, term :: Words}
222 | Rref {anchor :: Maybe Anchor, to :: Ident}
232 -- ** Type 'LineValue'
239 newtype Title = Title { unTitle :: Para }
240 deriving (Eq,Show,Default)
256 instance Default Entity where
269 instance Semigroup Entity where
277 instance Default Include where
282 -- * Type 'Reference'
288 reference :: Ident -> Reference
294 instance Default Reference where
301 , month :: Maybe Nat1
304 instance Default Date where
307 , month = Just (Nat1 01)
308 , day = Just (Nat1 01)
310 instance Semigroup Date where
321 instance Default Link where
334 instance Default Alias where
345 instance Default Serie where