pretty-simple-0.1.0.0: Simple pretty printer for any datatype with a 'Show' instance.

Copyright(c) Dennis Gosnell 2016
LicenseBSD-style (see LICENSE file)
Maintainercdep.illabout@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Pretty.Simple.Internal.Printer

Description

 

Synopsis

Documentation

>>> import Control.Monad.State (State)
>>> :{
let test :: PrinterState -> State PrinterState a -> PrinterState
    test initState state = execState state initState
    testInit :: State PrinterState a -> PrinterState
    testInit = test initPrinterState
:}

data PrinterState Source #

Instances

Eq PrinterState Source # 
Data PrinterState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrinterState -> c PrinterState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrinterState #

toConstr :: PrinterState -> Constr #

dataTypeOf :: PrinterState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PrinterState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrinterState) #

gmapT :: (forall b. Data b => b -> b) -> PrinterState -> PrinterState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrinterState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrinterState -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrinterState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrinterState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrinterState -> m PrinterState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrinterState -> m PrinterState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrinterState -> m PrinterState #

Show PrinterState Source # 
Generic PrinterState Source # 

Associated Types

type Rep PrinterState :: * -> * #

type Rep PrinterState Source # 
type Rep PrinterState = D1 (MetaData "PrinterState" "Text.Pretty.Simple.Internal.Printer" "pretty-simple-0.1.0.0-97nh4kIYK85IEGMrhjvVIt" False) (C1 (MetaCons "PrinterState" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_currLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "_currCharOnLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "_indentStack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])) (S1 (MetaSel (Just Symbol "_printerString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

latestIndent :: Lens' PrinterState Int Source #

This assumes that the indent stack is not empty.

putSurroundExpr Source #

Arguments

:: MonadState PrinterState m 
=> String

starting character ([ or { or ()

-> String

ending character (] or } or ))

-> CommaSeparated [Expr]

comma separated inner expression.

-> m () 

Print a surrounding expression (like [] or {} or ()).

If the CommaSeparated expressions are empty, just print the start and end markers.

>>> testInit $ putSurroundExpr "[" "]" (CommaSeparated [])
PrinterState {_currLine = 0, _currCharOnLine = 2, _indentStack = [0], _printerString = "[]"}
>>> let state = printerState 1 5 [5,0] "\nhello"
>>> test state $ putSurroundExpr "(" ")" (CommaSeparated [[]])
PrinterState {_currLine = 1, _currCharOnLine = 7, _indentStack = [5,0], _printerString = "\nhello()"}

If there is only one expression, then just print it it all on one line, with spaces around the expressions.

>>> testInit $ putSurroundExpr "{" "}" (CommaSeparated [[Other "hello", Other "bye"]])
PrinterState {_currLine = 0, _currCharOnLine = 12, _indentStack = [0], _printerString = "{ hellobye }"}

If there are multiple expressions, and this is indent level 0, then print out normally and put each expression on a different line with a comma. No indentation happens.

>>> comma = [[Other "hello"], [Other "bye"]]
>>> testInit $ putSurroundExpr "[" "]" (CommaSeparated comma)
PrinterState {_currLine = 2, _currCharOnLine = 1, _indentStack = [0], _printerString = "[ hello\n, bye\n]"}