diff options
| -rw-r--r-- | spec/src/Thermoprint/Printout/BBCode.hs | 95 | 
1 files changed, 78 insertions, 17 deletions
| diff --git a/spec/src/Thermoprint/Printout/BBCode.hs b/spec/src/Thermoprint/Printout/BBCode.hs index cee36b8..8df70c0 100644 --- a/spec/src/Thermoprint/Printout/BBCode.hs +++ b/spec/src/Thermoprint/Printout/BBCode.hs | |||
| @@ -1,5 +1,6 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} | 
| 2 | {-# LANGUAGE DeriveGeneric #-} | 2 | {-# LANGUAGE DeriveGeneric #-} | 
| 3 | {-# LANGUAGE GADTs #-} | ||
| 3 | 4 | ||
| 4 | -- | Use 'Text.BBCode' to parse BBCode | 5 | -- | Use 'Text.BBCode' to parse BBCode | 
| 5 | module Thermoprint.Printout.BBCode | 6 | module Thermoprint.Printout.BBCode | 
| @@ -12,11 +13,14 @@ module Thermoprint.Printout.BBCode | |||
| 12 | import Data.Text (Text) | 13 | import Data.Text (Text) | 
| 13 | import qualified Data.Text as T (unpack) | 14 | import qualified Data.Text as T (unpack) | 
| 14 | 15 | ||
| 16 | import qualified Data.Text.Lazy as Lazy (Text) | ||
| 17 | import qualified Data.Text.Lazy as TL (fromStrict) | ||
| 18 | |||
| 15 | import Data.Map (Map) | 19 | import Data.Map (Map) | 
| 16 | import qualified Data.Map as Map (lookup) | 20 | import qualified Data.Map as Map (lookup) | 
| 17 | 21 | ||
| 18 | import Data.Sequence (Seq) | 22 | import Data.Sequence (Seq) | 
| 19 | import qualified Data.Sequence as Seq () | 23 | import qualified Data.Sequence as Seq (fromList, singleton) | 
| 20 | 24 | ||
| 21 | import Data.CaseInsensitive (CI) | 25 | import Data.CaseInsensitive (CI) | 
| 22 | import qualified Data.CaseInsensitive as CI | 26 | import qualified Data.CaseInsensitive as CI | 
| @@ -32,7 +36,7 @@ import Text.Read (readMaybe) | |||
| 32 | 36 | ||
| 33 | import Data.Maybe (fromMaybe) | 37 | import Data.Maybe (fromMaybe) | 
| 34 | 38 | ||
| 35 | import Text.BBCode (DomTree(..), TreeError(..)) | 39 | import Text.BBCode (DomForest, DomTree(..), TreeError(..)) | 
| 36 | import qualified Text.BBCode as Raw (bbcode, BBCodeError(..)) | 40 | import qualified Text.BBCode as Raw (bbcode, BBCodeError(..)) | 
| 37 | 41 | ||
| 38 | import Thermoprint.Printout | 42 | import Thermoprint.Printout | 
| @@ -45,30 +49,87 @@ data BBCodeError = LexerError String -- ^ Error while parsing input to stream of | |||
| 45 | 49 | ||
| 46 | instance Exception BBCodeError | 50 | instance Exception BBCodeError | 
| 47 | 51 | ||
| 52 | morph' :: Raw.BBCodeError -> BBCodeError | ||
| 53 | -- ^ Transform 'Raw.BBCodeError' to 'BBCodeError' | ||
| 54 | morph' (Raw.LexerError x) = LexerError x | ||
| 55 | morph' (Raw.TreeError x) = TreeError x | ||
| 56 | |||
| 48 | -- ^ An error ocurred while parsing the DOM-Forest (`['DomTree']`) | 57 | -- ^ An error ocurred while parsing the DOM-Forest (`['DomTree']`) | 
| 49 | data SemanticError = UnmappedTag Text -- ^ An `Element` does not map to any structure in the context it occurred in | 58 | data SemanticError = BlockInLineContext -- ^ A 'Block' structure was encountered when a 'Line' was expected | 
| 59 | | LineInBlockContext -- ^ A 'Line' structure was encountered when a 'Block' was expected | ||
| 60 | | UnmappedBlockElement Text -- ^ We encountered an 'Element' that, in a 'Block' context, does not map to any structure | ||
| 61 | | UnmappedLineElement Text -- ^ We encountered an 'Element' that, in a 'Line' context, does not map to any structure | ||
| 50 | deriving (Show, Eq, Generic, Typeable) | 62 | deriving (Show, Eq, Generic, Typeable) | 
| 51 | 63 | ||
| 52 | instance Exception SemanticError | 64 | instance Exception SemanticError | 
| 53 | 65 | ||
| 66 | -- | Result of parsing a single 'DomTree' | ||
| 67 | data ParseResult = RBlock Block -- ^ Parses only as 'Block' | ||
| 68 | | RLine Line -- ^ Parses only as 'Line' | ||
| 69 | | RAmbiguous Block Line -- ^ Parses as either 'Block' or 'Line' depending on context | ||
| 70 | | RNoParse SemanticError SemanticError -- ^ Does not parse as either 'Block' or 'Line' | ||
| 71 | |||
| 72 | -- | Current parser context | ||
| 73 | data Context a where | ||
| 74 | BlockCtx :: Context Block -- ^ Parsing 'Block's | ||
| 75 | LineCtx :: Context Line -- ^ Parsing 'Line's | ||
| 76 | |||
| 77 | extract :: Context a -> ParseResult -> Either SemanticError a | ||
| 78 | -- ^ Extract information from a 'ParseResult' given 'Context' | ||
| 79 | extract BlockCtx (RBlock b) = Right b | ||
| 80 | extract LineCtx (RLine l) = Right l | ||
| 81 | extract BlockCtx (RAmbiguous b _) = Right b | ||
| 82 | extract LineCtx (RAmbiguous _ l) = Right l | ||
| 83 | extract BlockCtx (RNoParse bErr _) = Left bErr | ||
| 84 | extract LineCtx (RNoParse _ lErr) = Left lErr | ||
| 85 | extract BlockCtx _ = Left LineInBlockContext | ||
| 86 | extract LineCtx _ = Left BlockInLineContext | ||
| 87 | |||
| 54 | bbcode :: Text -> Either BBCodeError Printout | 88 | bbcode :: Text -> Either BBCodeError Printout | 
| 55 | -- ^ Parse BBCode | 89 | -- ^ Parse BBCode | 
| 56 | bbcode = join . fmap (first SemanticError) . bimap morph' morph . Raw.bbcode | 90 | bbcode = join . fmap (first SemanticError) . bimap morph' morph . Raw.bbcode | 
| 57 | 91 | ||
| 58 | morph' :: Raw.BBCodeError -> BBCodeError | 92 | morph :: DomForest -> Either SemanticError Printout | 
| 59 | morph' (Raw.LexerError x) = LexerError x | 93 | -- ^ Parse a list of paragraphs | 
| 60 | morph' (Raw.TreeError x) = TreeError x | 94 | -- | 
| 61 | 95 | -- Since we permit only cooked input via 'Raw' 'Paragraph' is identical to 'Block' | |
| 62 | morph :: [DomTree] -> Either SemanticError Printout | 96 | morph f = Seq.fromList <$> mapM (\t -> Seq.singleton . Cooked <$> parse BlockCtx t) f | 
| 63 | morph = undefined | 97 | |
| 64 | 98 | parseDom :: DomTree -> ParseResult | |
| 65 | asBlock :: CI Text -> Map (CI Text) Text -> Either SemanticError Block | 99 | -- ^ Invoke 'asLine' and 'asBlock' to parse a single 'DomTree' | 
| 66 | asBlock "VSpace" = Right . VSpace . lookupAttr "size" 1 | 100 | parseDom (Content t) = either RBlock (\l -> RAmbiguous (Line l) l) . text . TL.fromStrict $ t | 
| 67 | asBlock t = Left . const (UnmappedTag . CI.original $ t) | 101 | parseDom (Element t attrs cs) | 
| 68 | 102 | | Right blockParse' <- blockParse | |
| 69 | asLine :: CI Text -> Map (CI Text) Text -> Either SemanticError Line | 103 | , Right lineParse' <- lineParse = RAmbiguous blockParse' lineParse' | 
| 70 | asLine "HSpace" = Right . HSpace . lookupAttr "size" 1 | 104 | | Right blockParse' <- blockParse = RBlock blockParse' | 
| 71 | asLine t = Left . const (UnmappedTag . CI.original $ t) | 105 | | Right lineParse' <- lineParse = RLine lineParse' | 
| 106 | | Left bErr <- blockParse | ||
| 107 | , Left lErr <- lineParse = RNoParse bErr lErr | ||
| 108 | where | ||
| 109 | blockParse = asBlock t cs attrs | ||
| 110 | lineParse = asLine t cs attrs | ||
| 111 | |||
| 112 | mergeResult :: Monoid a => Context a -> [ParseResult] -> Either SemanticError a | ||
| 113 | -- ^ Merge a list of 'ParseResults' in a certain 'Context' | ||
| 114 | mergeResult _ [] = Right mempty | ||
| 115 | mergeResult BlockCtx xs@((RLine _):_) = bimap (const LineInBlockContext) Line $ mergeResult LineCtx xs | ||
| 116 | mergeResult ctx (amb@(RAmbiguous _ _):xs) = mappend <$> extract ctx amb <*> mergeResult ctx xs | ||
| 117 | mergeResult ctx (err@(RNoParse _ _):_) = extract ctx err | ||
| 118 | mergeResult ctx (x:xs) = mappend <$> extract ctx x <*> mergeResult ctx xs | ||
| 119 | |||
| 120 | parse :: Monoid a => Context a -> [DomTree] -> Either SemanticError a | ||
| 121 | -- ^ Parse a list of 'DomTree's in a certain 'Context' | ||
| 122 | -- | ||
| 123 | -- @parse ctx = 'mergeResult' ctx . map 'parseDom'@ | ||
| 124 | parse ctx = mergeResult ctx . map parseDom | ||
| 72 | 125 | ||
| 73 | lookupAttr :: Read a => CI Text -> a -> Map (CI Text) Text -> a | 126 | lookupAttr :: Read a => CI Text -> a -> Map (CI Text) Text -> a | 
| 74 | lookupAttr t def attrs = fromMaybe def $ Map.lookup t attrs >>= (readMaybe . T.unpack) | 127 | lookupAttr t def attrs = fromMaybe def $ Map.lookup t attrs >>= (readMaybe . T.unpack) | 
| 128 | |||
| 129 | asBlock :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Block | ||
| 130 | asBlock "VSpace" [] = Right . VSpace . lookupAttr "height" 1 | ||
| 131 | asBlock t _ = const $ Left . UnmappedBlockElement . CI.original $ t | ||
| 132 | |||
| 133 | asLine :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Line | ||
| 134 | asLine "HSpace" [] = Right . HSpace . lookupAttr "width" 1 | ||
| 135 | asLine t _ = const $ Left . UnmappedLineElement . CI.original $ t | ||
