----------------------------------------------------------------------------- -- Copyright 2019, Advise-Me project team. This file is distributed under -- the terms of the Apache License 2.0. For more information, see the files -- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution. ----------------------------------------------------------------------------- -- | -- Maintainer : bastiaan.heeren@ou.nl -- Stability : provisional -- Portability : portable (depends on ghc) -- ----------------------------------------------------------------------------- module Recognize.Data.StringLexer where import Data.Monoid ( (<>) ) import Ideas.Text.HTML hiding (table, ul) import Ideas.Text.HTML.W3CSS hiding (input) import Ideas.Text.XML hiding (tag) import Recognize.Data.Solution import Recognize.Data.StringLexerOptions import Recognize.Parsing.MathLexer import Util.Monad import Util.W3CSSHTML import Recognize.Preprocessing import qualified Text.PrettyPrint.Leijen as PP data LayoutMode = Column | Row deriving (Show, Eq) instance ToXML LayoutMode where toXML Column = makeXML "layoutmode" $ string "column" toXML Row = makeXML "layoutmode" $ string "row" -- | The LexerOutput contains the lexed strings and the layout mode which is determind by the columnizer in "Recognize.Parsing.MathLexer" data LexerOutput = LexerOutput { stringLexerOutput :: [String], layoutMode :: LayoutMode } instance Show LexerOutput where show = show . PP.pretty instance PP.Pretty LexerOutput where pretty lo = PP.vcat $ map PP.string (stringLexerOutput lo) ++ [ PP.string $ "Layout mode: " ++ show (layoutMode lo) ] instance ToXML LexerOutput where toXML lo = makeXML "stringlexeroutput" $ mconcat [ string (unlines (stringLexerOutput lo)) , builderXML (layoutMode lo) ] stringLexer :: StringLexerOptions -> Maybe Language -> Input -> LexerOutput stringLexer opts lang i = let (ss,uc) = extract opts $ preProcess lang $ inputToString (getInput i) in LexerOutput { stringLexerOutput = ss , layoutMode = if uc then Column else Row } instance ToHTML LexerOutput where toHTML out = mWhen (not $ null $ stringLexerOutput out) (panel (w3list (map toHTML (stringLexerOutput out)))) <> string ("layout mode: " ++ show (layoutMode out))