{-# LANGUAGE OverloadedLists #-} module Rosetta.Matching 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 System.Random qualified as Random import System.Random.Shuffle as Random -- 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 { matterText :: Pron.InputLexemes , matterLangue :: Langue } deriving (Eq, Show, Generic) deriving (HasTypeDefault) via (Generically Matter) data Match = Match { matchMatters :: [Matter] , matchPicture :: File.FilePath , matchPictureCSS :: HTML.CSSBlock } deriving (Eq, Show, Generic) instance HasTypeDefault Match where typeDefault = Match { matchPicture = "" , matchPictureCSS = mempty , matchMatters = [] } data Page = Page { pageMatches :: [Match] , pageMatchesNum :: Natural , pageSize :: PageSize , pageOrientation :: PageOrientation } deriving (Eq, Show, Generic) instance HasTypeDefault Page where typeDefault = Page { pageMatches = mempty , pageMatchesNum = 10 , pageSize = typeDefault , 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 randomGen <- Random.getStdGen pagesListShuffled :: [Page] <- (mconcat <$>) $ forM (pages & pagesList) \page -> do forM (page & pageMatches & chunksOf (page & pageMatchesNum)) \matches -> do pageMatches <- Random.shuffleM matches return page{pageMatches} -- Random.shuffleM -- Random.shuffleM -- forM_ (pageMatch & ol0) \(matchIdx :: Int, match) -> do -- forM_ (match & matchMatters & ol1) \(matterIdx :: Natural, matter) -> do -- Random.shuffleM -- let n = page & pageMatchesNum & fromIntegral -- in let (q, r) = page & pageMatches & List.length & (div n) -- in List.unfoldr _ (List.replicate q n <> [r]) 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/Matching.css" ] & list ) \cssFile -> HTML.link ! HA.rel "stylesheet" ! HA.type_ "text/css" ! HA.href (dataPath cssFile & toValue) -- styleCSS $ cssPrintPage pageOrientation pageSize HTML.styleCSS $ pages & pagesDifficulties & difficultyCSS HTML.body do forM_ (pages & pagesList) \page -> do "\n" forM_ (page & pageMatches & chunksOf (page & pageMatchesNum)) \pageMatch -> do HTML.section ! classes [ "rosetta-matching" , "A4" , "sheet" , page & pageOrientation & HTML.cssPageOrientation ] ! styles [ "size" := List.unwords [ page & pageSize & HTML.cssPageSize , page & pageOrientation & HTML.cssPageOrientation ] ] $ do "\n" let matchColumns = pageMatch & foldMap (matchMatters >>> List.length >>> Max) & getMax let pageColumns = pageMatch & List.length HTML.div ! classes ["matches"] ! styles ["grid-template-columns" := "1fr" <> mconcat (List.replicate (max 0 (2 * (matchColumns - 1) + 1)) " 2em 1fr 2em 1fr")] $ do let pageMatchNum = pageMatch & List.length forM_ (pageMatch & ol0) \(matchIdx :: Int, match) -> do let commonStyles = [ "grid-row-start" := show (pageColumns - matchIdx + 1) , "grid-row-end" := show (pageColumns - matchIdx + 1) ] let matchAnchor c = HTML.div ! classes ["match-anchor"] ! styles commonStyles $ do HTML.span c matchLinks = do matchAnchor "▷" HTML.div ! classes ["match-links"] ! styles commonStyles $ "" matchAnchor "◁" "\n" forM_ (match & matchMatters & ol1) \(matterIdx :: Natural, matter) -> do when (matterIdx /= 1) do matchLinks let words :: [[Either Char Pron.Pron]] = case matter & matterLangue of LangueAnglais -> matter & matterText & Pron.unInputLexemes & Pron.runParser dictsEnglish & either errorShow id & Pron.words LangueFrançais -> matter & matterText & Pron.unInputLexemes & Pron.runParser dictsFrench & either errorShow id & Pron.words LangueMandarin -> matter & matterText & Pron.unInputLexemes & Chinese.pronunciation dictsChinese _ -> errorShow ("matterLangue unsupported" :: Text, matter & matterLangue) HTML.div ! classes [ "match-matter" , "lang-" <> className (matter & matterLangue) ] ! styles commonStyles $ do 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(" <> (sylText & Text.length & 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 ] <> commonStyles ) $ do sylSoundPart & HTML.toHtml matchLinks HTML.div ! classes [ "match-matter" , "lang-" <> className (matter & matterLangue) ] ! styles commonStyles $ do forM_ (words & Pron.addIndexes) \word -> do HTML.div ! classes ["sentence-horiz"] $ do forM_ word \syl -> do forM_ (syl & Pron.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 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