1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE DuplicateRecordFields #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE MultiParamTypeClasses #-}
6 {-# LANGUAGE OverloadedStrings #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeApplications #-}
9 {-# OPTIONS_GHC -fno-warn-orphans #-}
10 module Language.DTC.Write.Plain where
12 import Control.Applicative (Applicative(..), liftA2)
13 import Control.Category
16 import Data.Default.Class (Default(..))
17 import Data.Eq (Eq(..))
18 import Data.Foldable (Foldable(..), concat)
19 import Data.Function (($))
21 import Data.Maybe (Maybe(..), maybe)
22 import Data.Monoid (Monoid(..))
23 import Data.Semigroup (Semigroup(..))
24 import Data.String (String)
25 import Data.Text (Text)
26 import Data.TreeSeq.Strict (Tree(..))
27 import Data.Tuple (fst, snd)
28 import Data.String (IsString(..))
30 import Text.Show (Show(..))
31 import qualified Control.Monad.Trans.State as S
32 import qualified Data.List as List
33 import qualified Data.Text.Lazy as TL
34 import qualified Data.Text.Lazy.Builder as TLB
36 import Data.Locale hiding (localize, Index)
38 import Language.DTC.Write.XML ()
39 import qualified Language.DTC.Document as DTC
42 type Plain = S.State State TLB.Builder
44 runPlain :: Plain -> State -> (TL.Text, State)
46 let (b,s') = S.runState p s in
47 (TLB.toLazyText b, s')
49 text :: Plainify a => State -> a -> TL.Text
50 text st a = fst $ runPlain (plainify a) st
52 instance IsString Plain where
53 fromString = return . fromString
54 instance Semigroup Plain where
56 instance Monoid Plain where
63 { state_localize :: L10n -> Plain
64 , state_italic :: Bool
65 , state_quote :: DTC.Nat
67 instance Default State where
69 { state_localize = plainify . show
70 , state_italic = False
71 , state_quote = DTC.Nat 0
76 class Plainify a where
77 plainify :: a -> Plain
78 instance Plainify String where
79 plainify = return . TLB.fromString
80 instance Plainify Text where
81 plainify = return . TLB.fromText
82 instance Plainify TL.Text where
83 plainify = return . TLB.fromLazyText
84 instance Plainify DTC.Para where
85 plainify = foldMap plainify
86 instance Plainify DTC.Lines where
91 DTC.Plain p -> plainify p
94 DTC.B -> "*"<>plainify ls<>"*"
95 DTC.Code -> "`"<>plainify ls<>"`"
96 DTC.Del -> "-"<>plainify ls<>"-"
97 DTC.I -> "/"<>plainify ls<>"/"
100 let depth = DTC.Nat 0 in
101 plainify (L10n_QuoteOpen{..}) <>
103 plainify (L10n_QuoteClose{..})
104 DTC.SC -> plainify ls
105 DTC.Sub -> plainify ls
106 DTC.Sup -> plainify ls
107 DTC.U -> "_"<>plainify ls<>"_"
108 DTC.Eref{..} -> plainify ls
109 DTC.Iref{..} -> plainify ls
110 DTC.Ref{..} -> plainify ls
111 DTC.Rref{..} -> plainify ls
112 instance Plainify DTC.Title where
113 plainify (DTC.Title t) = plainify t
114 instance Plainify DTC.PosPath where
117 snd . foldl' (\(nParent,acc) (n,c) ->
119 (if TL.null acc then acc else acc <> ".") <>
121 then TL.pack (show c)
122 else TL.pack (show n)<>TL.pack (show c))
126 instance Plainify DTC.XmlName where
127 plainify = plainify . show
128 instance Plainify Int where
129 plainify = plainify . show
130 instance Plainify DTC.Nat where
131 plainify (DTC.Nat n) = plainify n
132 instance Plainify DTC.Nat1 where
133 plainify (DTC.Nat1 n) = plainify n
137 = L10n_Table_of_Contents
139 | L10n_QuoteOpen {depth :: DTC.Nat}
140 | L10n_QuoteClose {depth :: DTC.Nat}
143 instance Plainify L10n where
145 loc <- S.gets state_localize
147 instance LocalizeIn FR Plain L10n where
149 L10n_Table_of_Contents -> "Sommaire"
151 L10n_QuoteOpen{..} ->
152 case DTC.unNat depth `mod` 3 of
156 L10n_QuoteClose{..} ->
157 case DTC.unNat depth `mod` 3 of
161 L10n_Date DTC.Date{..} ->
163 List.intersperse " " $
165 [ maybe [] (pure . plainify) day
178 9 -> pure "septembre"
180 11 -> pure "novembre"
181 12 -> pure "décembre"
185 instance LocalizeIn EN Plain L10n where
187 L10n_Table_of_Contents -> "Summary"
189 L10n_QuoteOpen{..} ->
190 case DTC.unNat depth `mod` 3 of
194 L10n_QuoteClose{..} ->
195 case DTC.unNat depth `mod` 3 of
199 L10n_Date DTC.Date{..} ->
201 List.intersperse " " $
203 [ maybe [] (pure . plainify) day
216 9 -> pure "September"
218 11 -> pure "November"
219 12 -> pure "December"