{-# LANGUAGE OverloadedLists #-} module Rosetta.Reading where import Data.ByteString.Builder (Builder) -- import Data.Char qualified as Char import Data.List qualified as List import Data.Map.Strict qualified as Map -- import Data.Set qualified as Set import Data.Text qualified as Text -- import Data.Text.Short qualified as ShortText import System.FilePath.Posix (()) import System.FilePath.Posix qualified as File import Text.Blaze import Text.Blaze.Html5 qualified as HTML import Text.Blaze.Html5.Attributes qualified as HA import Text.Blaze.Renderer.Utf8 qualified as Blaze import Prelude (div, even) import Language import Language.Chinese (ChineseDict (..), ChineseDictEntries (..)) import Language.Chinese qualified import Language.Chinese qualified as Chinese import Language.English qualified as English import Language.French qualified as French import Language.Pronunciation qualified as Pron import Paths_worksheets qualified as Self import Worksheets.Utils.Char as Char import Worksheets.Utils.HTML (Length, className, classes, cm, fr, styles) import Worksheets.Utils.HTML qualified as HTML import Worksheets.Utils.IPA qualified as IPA import Worksheets.Utils.Paper import Worksheets.Utils.Prelude type Difficulties = Map Langue (Map UnicodeBlock Difficulty) data Difficulty = Difficulty { difficultyCharWidth :: Length , difficultyCharHeight :: Length , difficultyWordSpacing :: Length , difficultyFontSize :: Length , difficultyColor :: Text } deriving (Eq, Show, Generic) instance HasTypeDefault Difficulty where typeDefault = Difficulty { difficultyCharWidth = 1 & cm , difficultyCharHeight = 1 & cm , difficultyWordSpacing = 0.5 & cm , difficultyFontSize = 1 & cm , difficultyColor = "#000000" } difficultyBig :: Char.UnicodeBlock -> Modifier Difficulty difficultyBig ub v = case ub of Char.UnicodeBlockLatin{} -> v { difficultyCharWidth = 1 & cm , difficultyCharHeight = 1 & cm , difficultyWordSpacing = 0.5 & cm , difficultyFontSize = 0.90 & cm } Char.UnicodeBlockCJK{} -> v { difficultyCharWidth = 1.50 & cm , difficultyCharHeight = 1.50 & cm , difficultyWordSpacing = 0.5 & cm , difficultyFontSize = 1.40 & cm } Char.UnicodeBlockHalfwidth_and_Fullwidth_Forms{} -> v { difficultyCharWidth = 1.50 & cm , difficultyCharHeight = 1.50 & cm , difficultyWordSpacing = 0.5 & cm , difficultyFontSize = 1.40 & cm } _ -> v data Matter = Matter { partLangue :: Langue , partText :: Pron.InputLexemes } deriving (Eq, Show, Generic) deriving (HasTypeDefault) via (Generically Matter) data Card = Card { cardMatters :: [Matter] , cardDescription :: Text , cardPicture :: File.FilePath , cardPictureCSS :: HTML.CSSBlock } deriving (Eq, Show, Generic) instance HasTypeDefault Card where typeDefault = Card { cardPicture = "" , cardDescription = "" , cardPictureCSS = mempty , cardMatters = [] } data Page = Page { pageCards :: [Card] , pageCardsColumns :: Natural -- = 8 , pageCardsRows :: Natural -- = 8 , pageSize :: PageSize , pageCardWidth :: Length , pageCardHeight :: Length , pageOrientation :: PageOrientation } deriving (Eq, Show, Generic) instance HasTypeDefault Page where typeDefault = Page { pageCards = mempty , pageCardsColumns = 4 , pageCardsRows = 2 , pageSize = typeDefault , pageCardWidth = 6.3 & cm , pageCardHeight = 8.8 & cm , pageOrientation = typeDefault } data Pages = Pages { pagesList :: [Page] , pagesDifficulties :: Difficulties } deriving (Eq, Show, Generic) instance HasTypeDefault Pages where typeDefault = Pages { pagesList = [] , pagesDifficulties = [ lang := [ block := typeDefault | block <- Char.unicodeBlocks & toList ] & Map.fromList | lang <- langues & toList ] & Map.fromList } data Dicts = Dicts { dictsChinese :: Chinese.ChineseDict , dictsFrench :: Pron.Table , dictsEnglish :: Pron.Table } pagesHTML :: Dicts -> Text -> Pages -> IO Builder pagesHTML Dicts{..} title Pages{..} = do -- FIXME: this absolute path is not portable out of my system dataPath <- Self.getDataDir <&> File.normalise return $ Blaze.renderMarkupBuilder do HTML.docTypeHtml do HTML.head do HTML.title $ title & HTML.toHtml forM_ ( [ "styles/Paper.css" , "styles/Rosetta/Common.css" , "styles/Rosetta/Reading.css" ] & list ) \cssFile -> HTML.link ! HA.rel "stylesheet" ! HA.type_ "text/css" ! HA.href (dataPath cssFile & toValue) -- styleCSS $ cssPrintPage pageOrientation pageSize HTML.styleCSS $ pagesDifficulties & difficultyCSS HTML.body do forM_ pagesList \Page{..} -> do "\n" let pageCardsNum = pageCardsColumns * pageCardsRows forM_ (pageCards & chunksOf pageCardsNum) \cardsGiven -> do let cards = cardsGiven & (<> List.repeat typeDefault) & List.take (pageCardsNum & fromIntegral) let forPageCards cardType cardsForPage k = do HTML.section ! classes [ "rosetta-reading" , "A4" , "sheet" , pageOrientation & HTML.cssPageOrientation ] ! styles [ "size" := List.unwords [ pageSize & HTML.cssPageSize , pageOrientation & HTML.cssPageOrientation ] ] $ do "\n" HTML.div ! classes [ "cards" , "cards-" <> cardType ] ! styles [ "grid-template-columns" := "repeat(" <> show pageCardsColumns <> "," <> HTML.toCSS pageCardWidth <> ")" , "grid-template-rows" := "repeat(" <> show pageCardsRows <> "," <> HTML.toCSS pageCardHeight <> ")" ] $ do forM_ cardsForPage \card_ -> do "\n" HTML.div ! classes [ "card" , "card-" <> cardType ] $ do k card_ -- ExplanationNote: short-edge binding, enable recto and verso to have the same bottom and top margins let organize = case pageOrientation :: PageOrientation of PageOrientationPortrait -> List.concatMap List.reverse PageOrientationLandscape -> List.concatMap List.reverse forPageCards "front" (cards & chunksOf pageCardsColumns & organize) \Card{..} -> do forM_ cardMatters \Matter{..} -> do {- HTML.div ! classes [ "word" , "lang-" <> className wordLangue -- , "script-" <> className uniScript ] $ do let classEven i = if even i then "part-even" else "part-odd" HTML.div ! classes ["word-field", "word-parts"] $ do (\f -> foldM_ f (0 :: Int) wordMatters) \i Matter{..} -> do HTML.span ! classes ["word-part", classEven i, "word-part-" <> show partSyllabs] $ do forM_ (partText & ShortText.unpack) \char -> do HTML.span ! classes ["word-char"] $ do char & HTML.toHtml return $ if partSyllabs == 1 then i + 1 else i unless (wordIPABroad & null) do HTML.div ! classes ["word-field", "word-ipas", "word-ipas-broad"] $ do forM_ (wordIPABroad & List.zip [0 :: Int ..]) \(i, ipa) -> do HTML.span ! classes ["word-ipa-broad", "word-ipa", classEven i] $ do ipa & HTML.toHtml unless (wordPinyin & null) do HTML.div ! classes ["word-field", "word-pinyins"] $ do forM_ (wordPinyin & List.zip [0 :: Int ..]) \(i, pinyin) -> do HTML.span ! classes ["word-pinyin", classEven i] $ do pinyin & HTML.toHtml -} HTML.div ! classes [ "card-matter" , "sentence" , "lang-" <> className partLangue ] $ do let words :: [[Either Char Pron.Pron]] = case partLangue of LangueAnglais -> partText & Pron.unInputLexemes & Pron.runParser dictsEnglish & either errorShow id & Pron.words LangueFrançais -> partText & Pron.unInputLexemes & Pron.runParser dictsFrench & either errorShow id & Pron.words LangueMandarin -> partText & Pron.unInputLexemes & Chinese.pronunciation dictsChinese _ -> errorShow ("partLangue unsupported" :: Text, partLangue) forM_ (words & Pron.addIndexes) \word -> do HTML.div ! classes ["sentence-horiz"] $ do forM_ word \syl@Pron.Syl{..} -> do let sylTextLength = sylText & Text.length HTML.div ! classes [ "sentence-syllable" ] ! styles [ "grid-template-columns" := "repeat(" <> (sylTextLength & show) <> ",auto)" ] $ do let sylSoundParts = sylSound & Text.words & \l -> if null l then [""] else l let sylSoundsSpanRest = sylTextLength - List.length sylSoundParts + 1 forM_ (sylSoundParts & List.zip (sylSoundsSpanRest : List.repeat 1)) \(sylSoundSpan, sylSoundPart) -> do HTML.div ! classes [ "sentence-cell" , "pronunciation" , "cell-" <> case syl of Pron.Syl{sylSilent = True} -> "silent" Pron.Syl{sylIndex = i} -> if i & even then "even" else "odd" , if sylDependsOnAfter then "cell-depends-on-after" else "" , if sylDependsOnBefore then "cell-depends-on-before" else "" , if sylDependsOnMeaning then "cell-depends-on-meaning" else "" , if sylSplit then "cell-split" else "" ] ! styles [ "grid-column-end" := "span " <> show sylSoundSpan ] $ do HTML.toHtml sylSoundPart forM_ (sylText & Text.unpack) \pronChar -> do let uniScript = pronChar & Char.unicodeBlock & fromMaybe (UnicodeBlockLatin UnicodeBlockLatin_Basic) HTML.span ! classes [ "sentence-cell" , "model" , "script-" <> className uniScript ] $ do HTML.span ! classes ["cell"] $ do pronChar & HTML.toHtml unless (cardDescription & Text.null) do HTML.div ! classes [ "card-description" ] $ do cardDescription & HTML.toHtml forPageCards "back" cards \Card{..} -> do HTML.div ! classes [ "card-picture" ] $ do unless (null cardPicture) do HTML.img ! styles cardPictureCSS ! HA.title (cardPicture & toValue) ! HA.src ("file://" <> dataPath "images" cardPicture & toValue) pagePortrait m = m { pageOrientation = PageOrientationPortrait } pageLandscape m = m { pageOrientation = PageOrientationLandscape } difficultyCSS :: Difficulties -> HTML.CSS difficultyCSS diffs = [ [ [ [".lang-" <> show lang <> " " <> ".script-" <> className uniScript] := [ "width" := difficultyCharWidth & HTML.toCSS , "height" := difficultyCharHeight & HTML.toCSS , "font-size" := difficultyFontSize & HTML.toCSS , "color" := difficultyColor & HTML.toCSS ] , [ ".lang-" <> show lang <> ".sentence" ] := ["column-gap" := difficultyWordSpacing & HTML.toCSS] ] | (uniScript, Difficulty{..}) <- blocks & toList ] | (lang, blocks) <- diffs & Map.toList ] & mconcat & fromList & mconcat