{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Hdoc.DTC.Write.HTML5.Base where import Control.Monad (Monad(..)) import Data.Char (Char) import Data.Default.Class (Default(..)) import Data.Either (Either(..)) import Data.Foldable (Foldable(..)) import Data.Function (($), (.)) import Data.Functor ((<$>)) import Data.Functor.Compose (Compose(..)) import Data.Int (Int) import Data.Locale hiding (Index) import Data.Map.Strict (Map) import Data.Maybe (Maybe(..), maybe) import Data.Semigroup (Semigroup(..)) import Data.String (String, IsString(..)) import Data.Text (Text) import Prelude (mod) import Text.Show (Show(..)) import qualified Control.Category as Cat import qualified Control.Monad.Trans.State as S import qualified Data.HashMap.Strict as HM import qualified Data.HashSet as HS import qualified Data.Text.Lazy as TL import qualified Data.TreeSeq.Strict as TreeSeq import qualified Hjugement as MJ import qualified Text.Blaze.Html5 as H import qualified Text.Blaze.Internal as H import Hdoc.DTC.Document as DTC import Hdoc.DTC.Write.XML () import qualified Text.Blaze.Internal as B -- import Text.Blaze.Utils import Control.Monad.Utils import qualified Hdoc.DTC.Check as Check import qualified Hdoc.DTC.Collect as Collect import qualified Hdoc.DTC.Index as Index import qualified Hdoc.DTC.Write.Plain as Plain import qualified Hdoc.XML as XML -- * Type 'HTML5' type HTML5 = ComposeState State B.MarkupM () instance IsString HTML5 where fromString = html5ify -- ** Type 'Config' data Config = forall locales. ( Locales locales , Loqualize locales (L10n HTML5) , Loqualize locales (Plain.L10n Plain.Plain) ) => Config { config_css :: Either FilePath TL.Text , config_js :: Either FilePath TL.Text , config_locale :: LocaleIn locales , config_generator :: TL.Text } instance Default Config where def = Config { config_css = Right "style/dtc-html5.css" , config_js = Right "style/dtc-html5.js" , config_locale = LocaleIn @'[EN] en_US , config_generator = "https://hackage.haskell.org/package/hdoc" } -- ** Type 'State' data State = State -- RW { state_styles :: HS.HashSet (Either FilePath TL.Text) , state_scripts :: HS.HashSet FilePath , state_notes :: Check.NotesBySection , state_judgments :: HS.HashSet Judgment , state_opinions :: HM.HashMap Judgment [MJ.OpinionsByChoice Choice Name (MJ.Ranked Grade)] -- RO , state_section :: TreeSeq.Trees BodyNode , state_collect :: Collect.All , state_indexs :: Map XML.Pos (Terms, Index.Irefs) -- TODO: could be a list , state_rrefs :: HM.HashMap Ident [(Maybe Section,Nat1)] , state_plainify :: Plain.State , state_l10n :: Loqualization (L10n HTML5) } instance Default State where def = State { state_styles = HS.fromList [Left "dtc-html5.css"] , state_scripts = def , state_section = def , state_collect = def , state_indexs = def , state_rrefs = def , state_notes = def , state_plainify = def , state_l10n = Loqualization EN_US , state_judgments = HS.empty , state_opinions = def } -- * Class 'Html5ify' class Html5ify a where html5ify :: a -> HTML5 instance Html5ify H.Markup where html5ify = Compose . return instance Html5ify Char where html5ify = html5ify . H.toMarkup instance Html5ify Text where html5ify = html5ify . H.toMarkup instance Html5ify TL.Text where html5ify = html5ify . H.toMarkup instance Html5ify String where html5ify = html5ify . H.toMarkup instance Html5ify Ident where html5ify (Ident i) = html5ify i instance Html5ify Int where html5ify = html5ify . show instance Html5ify Name where html5ify (Name i) = html5ify i instance Html5ify Nat where html5ify (Nat n) = html5ify n instance Html5ify Nat1 where html5ify (Nat1 n) = html5ify n instance Html5ify a => Html5ify (Maybe a) where html5ify = foldMap html5ify html5AttrClass :: [TL.Text] -> HTML5 -> HTML5 html5AttrClass = \case [] -> Cat.id cls -> Compose . (H.AddCustomAttribute "class" (H.String $ TL.unpack $ TL.unwords cls) <$>) . getCompose html5AttrId :: Ident -> HTML5 -> HTML5 html5AttrId (Ident id_) = Compose . (H.AddCustomAttribute "id" (H.String $ TL.unpack id_) <$>) . getCompose html5CommonAttrs :: CommonAttrs -> HTML5 -> HTML5 html5CommonAttrs CommonAttrs{id=id_, ..} = html5AttrClass classes . maybe Cat.id html5AttrId id_ -- * Class 'L10n' class ( Plain.L10n msg lang , Plain.L10n TL.Text lang ) => L10n msg lang where l10n_Header_Address :: FullLocale lang -> msg l10n_Header_Date :: FullLocale lang -> msg l10n_Header_Version :: FullLocale lang -> msg l10n_Header_Origin :: FullLocale lang -> msg l10n_Header_Source :: FullLocale lang -> msg l10n_Errors_All :: FullLocale lang -> Nat -> msg l10n_Error_Tag_unknown :: FullLocale lang -> msg l10n_Error_Tag_ambiguous :: FullLocale lang -> msg l10n_Error_Rref_unknown :: FullLocale lang -> msg l10n_Error_Reference_ambiguous :: FullLocale lang -> msg l10n_Error_Judgment_Judges_unknown :: FullLocale lang -> msg l10n_Error_Judgment_Judge_unknown :: FullLocale lang -> msg l10n_Error_Judgment_Judge_duplicated :: FullLocale lang -> msg l10n_Error_Judgment_Grades_unknown :: FullLocale lang -> msg l10n_Error_Judgment_Grades_duplicated :: FullLocale lang -> msg l10n_Error_Judgment_Grade_unknown :: FullLocale lang -> msg l10n_Error_Judgment_Choice_duplicated :: FullLocale lang -> msg instance L10n HTML5 EN where l10n_Header_Address _l10n = "Address" l10n_Header_Date _l10n = "Date" l10n_Header_Origin _l10n = "Origin" l10n_Header_Source _l10n = "Source" l10n_Header_Version _l10n = "Version" l10n_Errors_All _l10n n = "All errors ("<>html5ify n<>")" l10n_Error_Tag_unknown _l10n = "Unknown tag" l10n_Error_Tag_ambiguous _l10n = "Ambiguous tag" l10n_Error_Rref_unknown _l10n = "Unknown reference" l10n_Error_Reference_ambiguous _l10n = "Ambiguous reference" l10n_Error_Judgment_Judges_unknown _l10n = "Unknown judges" l10n_Error_Judgment_Judge_unknown _l10n = "Unknown judge" l10n_Error_Judgment_Judge_duplicated _l10n = "Duplicated judge" l10n_Error_Judgment_Grades_unknown _l10n = "Unknown grades" l10n_Error_Judgment_Grades_duplicated _l10n = "Duplicated grades" l10n_Error_Judgment_Grade_unknown _l10n = "Unknown grade" l10n_Error_Judgment_Choice_duplicated _l10n = "Duplicated choice" instance L10n HTML5 FR where l10n_Header_Address _l10n = "Adresse" l10n_Header_Date _l10n = "Date" l10n_Header_Origin _l10n = "Origine" l10n_Header_Source _l10n = "Source" l10n_Header_Version _l10n = "Version" l10n_Errors_All _l10n n = "Toutes les erreurs ("<>html5ify n<>")" l10n_Error_Tag_unknown _l10n = "Tag inconnu" l10n_Error_Tag_ambiguous _l10n = "Tag ambigu" l10n_Error_Rref_unknown _l10n = "Référence inconnue" l10n_Error_Reference_ambiguous _l10n = "Référence ambiguë" l10n_Error_Judgment_Judges_unknown _l10n = "Juges inconnu·es" l10n_Error_Judgment_Judge_unknown _l10n = "Juge unconnu·e" l10n_Error_Judgment_Judge_duplicated _l10n = "Juge en double" l10n_Error_Judgment_Grades_unknown _l10n = "Mentions inconnues" l10n_Error_Judgment_Grades_duplicated _l10n = "Mentions en double" l10n_Error_Judgment_Grade_unknown _l10n = "Mention inconnue" l10n_Error_Judgment_Choice_duplicated _l10n = "Choix en double" instance Plain.L10n HTML5 EN where l10n_Colon l10n = html5ify (Plain.l10n_Colon l10n :: TL.Text) l10n_Table_of_Contents l10n = html5ify (Plain.l10n_Table_of_Contents l10n :: TL.Text) l10n_Date date l10n = html5ify (Plain.l10n_Date date l10n :: TL.Text) l10n_Quote msg _l10n = do depth <- liftComposeState $ S.gets $ Plain.state_quote . state_plainify let (o,c) :: (HTML5, HTML5) = case unNat depth `mod` 3 of 0 -> ("“","”") 1 -> ("« "," »") _ -> ("‟","„") o setDepth $ succNat depth msg setDepth $ depth c where setDepth d = liftComposeState $ S.modify' $ \s -> s{state_plainify=(state_plainify s){Plain.state_quote=d}} instance Plain.L10n HTML5 FR where l10n_Colon l10n = html5ify (Plain.l10n_Colon l10n :: TL.Text) l10n_Table_of_Contents l10n = html5ify (Plain.l10n_Table_of_Contents l10n :: TL.Text) l10n_Date date l10n = html5ify (Plain.l10n_Date date l10n :: TL.Text) l10n_Quote msg _l10n = do depth <- liftComposeState $ S.gets $ Plain.state_quote . state_plainify let (o,c) :: (HTML5, HTML5) = case unNat depth `mod` 3 of 0 -> ("« "," »") 1 -> ("“","”") _ -> ("‟","„") o setDepth $ succNat depth msg setDepth $ depth c where setDepth d = liftComposeState $ S.modify' $ \s -> s{state_plainify=(state_plainify s){Plain.state_quote=d}}