pretty-simple-3.2.1.0: pretty printer for data types 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.ExprToOutput

Description

 
Synopsis

Documentation

>>> :set -XOverloadedStrings
>>> import Control.Monad.State (State)
>>> :{
let test :: PrinterState -> State PrinterState [Output] -> [Output]
    test initState state = evalState state initState
    testInit :: State PrinterState [Output] -> [Output]
    testInit = test initPrinterState
:}

newtype LineNum Source #

Newtype around Int to represent a line number. After a newline, the LineNum will increase by 1.

Constructors

LineNum 

Fields

Instances
Eq LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Methods

(==) :: LineNum -> LineNum -> Bool #

(/=) :: LineNum -> LineNum -> Bool #

Data LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Methods

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

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

toConstr :: LineNum -> Constr #

dataTypeOf :: LineNum -> DataType #

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

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

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

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

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

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

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

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

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

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

Num LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Ord LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Read LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Show LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Generic LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Associated Types

type Rep LineNum :: Type -> Type #

Methods

from :: LineNum -> Rep LineNum x #

to :: Rep LineNum x -> LineNum #

type Rep LineNum Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

type Rep LineNum = D1 (MetaData "LineNum" "Text.Pretty.Simple.Internal.ExprToOutput" "pretty-simple-3.2.1.0-6EOQECgFtDN28V0lneasr4" True) (C1 (MetaCons "LineNum" PrefixI True) (S1 (MetaSel (Just "unLineNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data PrinterState Source #

Constructors

PrinterState 
Instances
Eq PrinterState Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Data PrinterState Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

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 # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Generic PrinterState Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

Associated Types

type Rep PrinterState :: Type -> Type #

type Rep PrinterState Source # 
Instance details

Defined in Text.Pretty.Simple.Internal.ExprToOutput

type Rep PrinterState = D1 (MetaData "PrinterState" "Text.Pretty.Simple.Internal.ExprToOutput" "pretty-simple-3.2.1.0-6EOQECgFtDN28V0lneasr4" False) (C1 (MetaCons "PrinterState" PrefixI True) (S1 (MetaSel (Just "currLine") SourceUnpack SourceStrict DecidedStrict) (Rec0 LineNum) :*: S1 (MetaSel (Just "nestLevel") SourceUnpack SourceStrict DecidedStrict) (Rec0 NestLevel)))

putSurroundExpr Source #

Arguments

:: MonadState PrinterState m 
=> OutputType 
-> OutputType 
-> CommaSeparated [Expr]

comma separated inner expression.

-> m [Output] 

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

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

>>> testInit $ putSurroundExpr "[" "]" (CommaSeparated [])
[Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOpenBracket},Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputCloseBracket}]

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

>>> testInit $ putSurroundExpr "{" "}" (CommaSeparated [[Other "hello"]])
[Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOpenBrace},Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOther " "},Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOther "hello"},Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputOther " "},Output {outputNestLevel = NestLevel {unNestLevel = 0}, outputOutputType = OutputCloseBrace}]

If there is only one expression, but it will print out on multiple lines, then go to newline and print out on multiple lines.

>>> 1 + 1  -- TODO: Example here.
2

If there are multiple expressions, then first go to a newline. Print out on multiple lines.

>>> 1 + 1  -- TODO: Example here.
2

modificationsExprList :: [Expr] -> [Expr] Source #

A function that performs optimizations and modifications to a list of input Exprs.

An sample of an optimization is removeEmptyInnerCommaSeparatedExprList which removes empty inner lists in a CommaSeparated value.

removeEmptyList :: forall a. [[a]] -> [[a]] Source #

Remove empty lists from a list of lists.

>>> removeEmptyList [[1,2,3], [], [4,5]]
[[1,2,3],[4,5]]
>>> removeEmptyList [[]]
[]
>>> removeEmptyList [[1]]
[[1]]
>>> removeEmptyList [[1,2], [10,20], [100,200]]
[[1,2],[10,20],[100,200]]