module Text.Chatty.Typograph where
import Control.Monad
import Control.Monad.Trans.Class
import Data.Char
import Text.Chatty.Interactor
import Text.Chatty.Printer
import Text.Chatty.Scanner
import Text.Chatty.Scanner.Buffered
simpleTypesetter :: (Functor m,MonadScanner m,MonadPrinter m) => Int -> m ()
simpleTypesetter width = void $ runScannerBufferT (typeset width) ""
where scanw = mscannable >>= \b -> if not b then return [] else do
k <- mpeek1
if isSpace k then return [] else do
mscan1
ks <- scanw
return (k:ks)
skipw :: BufferedScanner m => m Int
skipw = mscannable >>= \b -> if not b then return 0 else do
k <- mpeek1
if not (isSpace k) then return 0 else do
mscan1
w <- skipw
return (w + if k == '\n' then 1 else 0)
tsetw i w
| length w < i = mprint (w ++ " ") >> typeset (i 1 length w)
| length w == i = mprintLn w >> typeset width
| length w > width && i == width = mprintLn (take i w) >> tsetw width (drop i w)
| otherwise = mprintLn "" >> tsetw width w
typeset i = mscannable >>= \b -> when b $ do
ls <- skipw
if ls > 0
then forM_ [1..ls] (const $ mprintLn "") >> typeset width
else do
w <- scanw
tsetw i w