{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | This module contains the definition of the structure -- 'Printout' -- used to represent the content of a job module Thermoprint.Printout ( Printout(..) , Paragraph(..) , Chunk(..) , Block(..) , Line( HSpace , JuxtaPos ) , text, cotext , prop_text ) where import Data.Sequence (Seq, (|>), (<|)) import Data.Text.Lazy (Text) import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as LBS (toStrict) import qualified Data.ByteString as Strict (ByteString) import GHC.Generics (Generic) import Control.DeepSeq (NFData) import Data.Aeson (FromJSON(..), ToJSON(..), Value(..)) import qualified Data.Aeson as JSON (encode, decode, eitherDecodeStrict') import Data.Aeson.Types (typeMismatch) import Data.Proxy (Proxy(..)) import Database.Persist.Class (PersistField(..)) import Database.Persist.Sql (PersistFieldSql(..)) import Test.QuickCheck.Arbitrary (Arbitrary(..), CoArbitrary, genericShrink) import Test.QuickCheck.Modifiers (NonNegative(..)) import Test.QuickCheck.Gen (oneof, scale) import Test.QuickCheck.Instances import Test.QuickCheck (forAll, Property) import qualified Data.Text.Lazy as TL (split, null, pack, groupBy, filter, intercalate, map, head, length) import qualified Data.Text as T (pack) import Data.Char (isSpace) import Data.Monoid (Monoid(..), (<>)) import Data.List (dropWhile, dropWhileEnd, groupBy, genericLength, genericReplicate) import Data.Sequence as Seq (fromList, null, singleton) import Data.Function (on) import Data.Foldable (toList, fold) import Data.Bifunctor import Control.Monad ((<=<)) import Data.Encoding (encodeLazyByteStringExplicit, decodeLazyByteString) import Data.Encoding.UTF8 import qualified Data.ByteString.Base64.Lazy as Base64 (encode, decode) import Prelude hiding (fold) -- | A 'Printout' is a sequence of visually seperated 'Paragraph's type Printout = Seq Paragraph instance PersistField Printout where toPersistValue = toPersistValue . LBS.toStrict . JSON.encode fromPersistValue = first T.pack . JSON.eitherDecodeStrict' <=< fromPersistValue instance PersistFieldSql Printout where sqlType _ = sqlType (Proxy :: Proxy Strict.ByteString) -- | A 'Paragraph' is a non-seperated sequence of 'Chunk's type Paragraph = Seq Chunk -- | We introduce both 'Chunk' and 'Paragraph' mainly to allow 'Raw'. -- -- Were we to disallow 'Raw', 'Block' would be identical to 'Paragraph' data Chunk = Cooked Block -- ^ text semantically structured to be rendered in accordance with the display format of printer | Raw ByteString -- ^ direct instructions to the printer deriving (Generic, NFData, Show, CoArbitrary) instance FromJSON Chunk where parseJSON s@(String _) = Raw <$> ((either fail return . decodeBase64) =<< parseJSON s) where decodeBase64 :: String -> Either String ByteString decodeBase64 s = (either (Left . show) Right . encodeLazyByteStringExplicit UTF8Strict $ s) >>= Base64.decode parseJSON o@(Object _) = Cooked <$> parseJSON o parseJSON v = typeMismatch "Chunk" v instance ToJSON Chunk where toJSON (Raw bs) = String . T.pack . decodeLazyByteString UTF8Strict . Base64.encode $ bs toJSON (Cooked block) = toJSON block -- | 'Block' is the entry point for our structured document format data Block = Line Line -- ^ a single 'Line' of text | VSpace Integer -- ^ vertical space of height equivalent to 'Integer' lines | NewlSep (Seq Block) -- ^ A sequence of 'Block's seperated by newlines deriving (Generic, NFData, Show, CoArbitrary, FromJSON, ToJSON) {- | A 'Line' is one of: * a single word * horizontal space equivalent to the width of 'Integer' `em`. * a sequence of 'Line' fragments juxtaposed without seperation We don't export all constructors and instead encourage the use of 'text'. -} data Line = Word Text | HSpace Integer | JuxtaPos (Seq Line) deriving (Generic, NFData, Show, CoArbitrary, FromJSON, ToJSON) instance Monoid Block where mempty = NewlSep mempty x@(NewlSep xs) `mappend` y@(NewlSep ys) | Seq.null xs = y | Seq.null ys = x | otherwise = NewlSep (xs <> ys) (NewlSep xs) `mappend` y | Seq.null xs = y | otherwise = NewlSep (xs |> y) x `mappend` (NewlSep ys) | Seq.null ys = x | otherwise = NewlSep (x <| ys) x `mappend` y = NewlSep $ Seq.fromList [x, y] instance Monoid Line where mempty = JuxtaPos mempty x@(JuxtaPos xs) `mappend` y@(JuxtaPos ys) | Seq.null xs = y | Seq.null ys = x | otherwise = JuxtaPos (xs <> ys) (JuxtaPos xs) `mappend` y | Seq.null xs = y | otherwise = JuxtaPos (xs |> y) x `mappend` (JuxtaPos ys) | Seq.null ys = x | otherwise = JuxtaPos (x <| ys) x `mappend` y = JuxtaPos $ Seq.fromList [x, y] text :: Text -> Either Block Line -- ^ Smart constructor for 'Line'/'Block' which maps word and line boundaries (as determined by 'isSpace' and '(== '\n')' respectively) to the structure of 'Block' and 'Line'. -- -- Since we are unwilling to duplicate the list of chars from 'isSpace' we cannot reasonably determine a width for the various whitespace 'Char's. -- Thus they are all weighted equally as having width 1 `em`. text t = case splitLines t of [] -> Right mempty [Line x] -> Right x xs -> Left $ mconcat xs where splitLines :: Text -> [Block] splitLines t = map toBlock . groupBy ((==) `on` TL.null) $ TL.split (== '\n') t splitWords :: Text -> [Line] splitWords t = map toLine . TL.groupBy ((==) `on` isSpace) $ t toBlock [] = mempty toBlock xs@(x:_) | TL.null x = VSpace $ genericLength xs - 1 | otherwise = mconcat . map (Line . mconcat . splitWords) $ xs toLine xs | TL.null xs = mempty | isSpace $ TL.head xs = HSpace . toInteger $ TL.length xs | otherwise = Word xs list :: b -> (a -> [a] -> b) -> [a] -> b list c _ [] = c list _ f (x:xs) = f x xs cotext :: Block -> Text -- ^ inverse of -- @ -- either id Line . `text` -- @ cotext (VSpace n) = TL.pack . genericReplicate n $ '\n' cotext (NewlSep xs) = TL.intercalate "\n" . map cotext . toList $ xs cotext (Line x) = cotext' x where cotext' (Word x) = x cotext' (HSpace n) = TL.pack . genericReplicate n $ ' ' cotext' (JuxtaPos xs) = mconcat . map cotext' . toList $ xs prop_text :: Text -> Bool -- ^ prop> (`cotext` . either id Line . `text` $ x) == x -- -- Where 'x' is restricted to those `TL.Text` which do not contain whitespace besides ' ' and '\n'. prop_text x = (cotext . either id Line . text $ x') == x' where x' = TL.map normSpace x normSpace c | isSpace c , c `elem` keep = c | isSpace c = ' ' -- We have to do this because all whitespace gets interpreted as width 1 | otherwise = c keep = [' ', '\n'] :: [Char] -- | We don't test 'Raw' 'Chunk's instance Arbitrary Chunk where shrink = genericShrink arbitrary = Cooked <$> arbitrary instance Arbitrary Block where shrink = genericShrink arbitrary = oneof [ Line <$> arbitrary , VSpace . getNonNegative <$> arbitrary , NewlSep <$> scale' arbitrary ] instance Arbitrary Line where shrink = genericShrink arbitrary = oneof [ Word . TL.filter (not . isSpace) <$> arbitrary -- 'isSpace '\n' == True' , HSpace . getNonNegative <$> arbitrary , JuxtaPos <$> scale' arbitrary ] scale' = scale (round . sqrt . fromInteger . toInteger)