{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} module Thermoprint.Server.Printer.Generic ( genericPrint , mkPrintout ) where import Thermoprint.Printout import Thermoprint.API (PrintingError(..)) import Thermoprint.Server.Printer import System.FileLock import System.IO import Data.Sequence (Seq, (|>), (<|), ViewL(..), viewl, ViewR(..), viewr) import qualified Data.Sequence as Seq import qualified Data.ByteString.Lazy as Lazy (ByteString) import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy.Char8 as CLBS import qualified Data.Text.Lazy as Lazy (Text) import qualified Data.Text.Lazy as TL import qualified Data.Text as T import Data.Encoding import Data.Encoding.CP437 import Data.Binary.Put import Data.Word import Data.Bits import Control.Monad import Control.Monad.Reader import Control.Monad.Trans.State import Control.Monad.Logger import Control.Monad.IO.Class import Control.Monad.Trans.Resource import Data.Acquire import Control.Exception.Base (IOException) import Control.Monad.Catch import Data.Foldable import Data.List (genericReplicate, genericLength, intercalate) import Data.Set (Set) import qualified Data.Set as Set import Data.Monoid import Data.Int (Int64) import Control.Concurrent (threadDelay) import Prelude hiding (mapM_, sequence_, lines) genericPrint :: FilePath -> PrinterMethod genericPrint path = PM $ genericPrint' path genericPrint' :: (MonadIO m, MonadMask m, MonadLogger m) => FilePath -> Printout -> m (Maybe PrintingError) genericPrint' path = flip catches handlers . withFile path . print where withFile path f = flip withEx f $ mkAcquire (openFile path WriteMode >>= (\h -> h <$ hSetBuffering h NoBuffering)) hClose handlers = [ Handler $ return . Just . IOError . (show :: IOException -> String) , Handler $ return . Just . EncError , Handler $ return . Just ] print printout handle = $(logDebug) (T.pack $ show printout') >> liftIO (slowPut handle printout' >> return Nothing) where printout' = mkPrintout printout mkPrintout :: Printout -> Lazy.ByteString mkPrintout printout = runPut $ initialize >> render printout >> finalize slowPut :: Handle -> Lazy.ByteString -> IO () slowPut h = slowPut' . LBS.split (LBS.last newl) where slowPut' [] = return () slowPut' [t] = LBS.hPutStr h t slowPut' (x:xs) = slowPut' [x] >> LBS.hPutStr h (LBS.singleton $ LBS.last newl) >> threadDelay (50 * 10^3) >> slowPut' xs encode' :: ByteSink m => String -> m () encode' = encode CP437 width :: Integer width = 32 esc :: Word8 esc = 27 escSequence :: [Word8] -> Put escSequence = mapM_ pushWord8 . (esc:) initialize :: Put initialize = replicateM_ 2 $ escSequence [64] newl :: Lazy.ByteString newl = encodeLazyByteString CP437 "\n" newls :: Integer -> Lazy.ByteString newls i = mconcat $ genericReplicate i newl newls' :: Integer -> Put newls' = mapM_ pushWord8 . LBS.unpack . newls finalize :: Put finalize = newls' 3 >> encode' " " >> newls' 1 intersperse :: b -> (a -> b) -> Seq a -> Seq b intersperse _ _ (viewl -> EmptyL) = Seq.empty intersperse _ f (viewl -> x :< (viewl -> EmptyL)) = Seq.singleton $ f x intersperse b f (viewl -> x :< xs) = f x <| b <| intersperse b f xs intersperse' :: Monad m => m b -> (a -> m b) -> Seq a -> m () intersperse' b f = sequence_ . intersperse b f render :: Printout -> Put render = intersperse' (newls' 2) renderPar . getParagraphs renderPar :: Paragraph -> Put renderPar = mapM_ renderChunk . getChunks where renderChunk (Raw bs) = mapM_ pushWord8 $ LBS.unpack bs renderChunk (Cooked block) = renderDoc $ execState (renderBlock block) (initDoc width) data Doc = Doc { lines :: Seq Put , currentLine :: Put , space :: Integer , remainingSpace :: Integer , overflows :: Integer , currentMarkup :: Set MarkupMode } initDoc :: Integer -> Doc initDoc space = Doc { lines = Seq.empty , currentLine = return () , space = space , remainingSpace = space , overflows = 0 , currentMarkup = Set.empty } breakLine :: Doc -> Doc breakLine doc@(Doc{..}) = doc { remainingSpace = space , lines = lines |> currentLine , currentLine = return () } renderDoc :: Doc -> Put renderDoc Doc{..} = intersperse' (newls' 1) id lines' where lines' | remainingSpace == space = lines | otherwise = lines |> currentLine escSequence' :: [Word8] -> State Doc () escSequence' s = modify (\(doc@(Doc{..})) -> doc { currentLine = currentLine >> escSequence s }) setMarkup :: Set MarkupMode -> State Doc () setMarkup m = escSequence' [33, byte m] >> modify (\doc -> doc { currentMarkup = m }) where byte = foldr (.|.) zeroBits . Set.map bitMask bitMask Bold = 8 bitMask DoubleHeight = 16 bitMask DoubleWidth = 32 bitMask Underline = 128 bitMask _ = zeroBits renderBlock :: Block -> State Doc () renderBlock (VSpace n) = sequence_ . genericReplicate n $ modify' breakLine renderBlock (NewlSep xs) = intersperse' (modify' breakLine) renderBlock xs renderBlock (Line x) = renderLine x renderLine :: Line -> State Doc () renderLine (HSpace n) = modify' insertSpace where insertSpace doc@(Doc{..}) | remainingSpace > n = doc { remainingSpace = remainingSpace - n , currentLine = currentLine >> (sequence_ $ genericReplicate n $ encode' " ") } | remainingSpace == n = breakLine doc | otherwise = breakLine $ doc { overflows = overflows + 1 } renderLine (Markup ms l) | Set.null ms = renderLine l | otherwise = do prevMarkup <- gets currentMarkup setMarkup (prevMarkup <> ms) >> renderLine l >> setMarkup prevMarkup renderLine (JuxtaPos xs) = mapM_ renderLine xs renderLine (cotext . Line -> word) = modify' $ insertWord where insertWord doc | TL.null wordTail = checkBreak $ doc' | otherwise = checkBreak $ doc { remainingSpace = space doc - (word' `mod` space doc) , lines = (lines doc |> currentLine doc) <> cs , currentLine = c , overflows = overflows doc + (toInteger $ Seq.length cs) } where (wordInit, wordTail) = TL.splitAt (fromInteger $ remainingSpace doc) word word' = toInteger $ TL.length word wordInit' = toInteger $ TL.length wordInit wordTail' = toInteger $ TL.length wordTail doc' = insertInit doc insertInit doc@(Doc{..}) = doc { remainingSpace = remainingSpace - wordInit' , currentLine = currentLine >> encode'' wordInit } (cs :> c) = viewr . Seq.fromList . map encode'' $ TL.chunksOf (fromInteger $ space doc) word checkBreak doc@(Doc{..}) | remainingSpace == 0 = doc { remainingSpace = space , lines = lines |> currentLine , currentLine = return () } | otherwise = doc encode'' = encode' . TL.unpack