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 ()
14 import Data.Maybe (Maybe(..))
15 import Data.Monoid (Monoid(..))
17 import Data.Semigroup (Semigroup(..))
18 import Data.Sequence (Seq)
19 import Data.Text (Text)
20 import Data.TreeSeq.Strict (Tree, Trees)
21 import Text.Show (Show)
31 instance Default Document where
42 instance Default Head where
52 , editor :: Maybe Entity
58 , includes :: [Include]
60 instance Default About where
72 instance Semigroup About where
74 { titles = titles x <> titles y
75 , authors = authors x <> authors y
76 , editor = editor x <> editor y
77 , date = date x <> date y
78 , version = version x <> version y
79 , keywords = keywords x <> keywords y
80 , links = links x <> links y
81 , series = series x <> series y
82 , includes = includes x <> includes y
86 type Body = Trees BodyKey BodyValue
90 = Section { pos :: XmlPos
91 , attrs :: CommonAttrs
97 -- ** Type 'BodyValue'
100 , attrs :: CommonAttrs
103 | ToF { pos :: XmlPos
104 , attrs :: CommonAttrs
107 | Figure { pos :: XmlPos
108 , attrs :: CommonAttrs
113 | Index { pos :: XmlPos
114 , attrs :: CommonAttrs
124 type Words = [WordOrSpace]
126 -- **** Type 'WordOrSpace'
130 deriving (Eq,Ord,Show)
133 type Aliases = [Words]
136 type Terms = [Aliases]
143 = Para { pos :: XmlPos
144 , attrs :: CommonAttrs
148 , attrs :: CommonAttrs
152 , attrs :: CommonAttrs
156 , attrs :: CommonAttrs
157 , refs :: [Reference]
159 | Artwork { pos :: XmlPos
160 , attrs :: CommonAttrs
166 -- * Type 'CommonAttrs'
180 type Blocks = [Block]
188 type Para = Seq Lines
191 type Lines = Tree LineKey LineValue
206 | Iref {count :: Int, term :: Words}
211 -- ** Type 'LineValue'
218 newtype Title = Title { unTitle :: Para }
219 deriving (Eq,Show,Default)
233 instance Default Address where
250 instance Default Include where
255 -- * Type 'Reference'
262 reference :: Ident -> Reference
269 instance Default Reference where
278 instance Default Entity where
283 instance Semigroup Entity where
290 , month :: Maybe Nat1
293 instance Default Date where
296 , month = Just (Nat1 01)
297 , day = Just (Nat1 01)
299 instance Semigroup Date where
310 instance Default Link where
323 instance Default Alias where
334 instance Default Serie where