| Copyright | (c) Dennis Gosnell 2016 |
|---|---|
| License | BSD-style (see LICENSE file) |
| Maintainer | cdep.illabout@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Pretty.Simple.Internal.ExprToOutput
Description
- newtype LineNum = LineNum {}
- data PrinterState = PrinterState {
- _currLine :: !LineNum
- _nestLevel :: !NestLevel
- _outputList :: !(Seq Output)
- outputList :: Lens' PrinterState (Seq Output)
- nestLevel :: Lens' PrinterState NestLevel
- currLine :: Lens' PrinterState LineNum
- printerState :: LineNum -> NestLevel -> Seq Output -> PrinterState
- addOutput :: MonadState PrinterState m => OutputType -> m ()
- addOutputs :: MonadState PrinterState m => Seq OutputType -> m ()
- initPrinterState :: PrinterState
- putSurroundExpr :: MonadState PrinterState m => OutputType -> OutputType -> CommaSeparated [Expr] -> m ()
- putCommaSep :: forall m. MonadState PrinterState m => CommaSeparated [Expr] -> m ()
- putComma :: MonadState PrinterState m => m ()
- howManyLines :: [Expr] -> LineNum
- doIndent :: MonadState PrinterState m => m ()
- newLine :: MonadState PrinterState m => m ()
- newLineAndDoIndent :: MonadState PrinterState m => m ()
- putExpression :: MonadState PrinterState m => Expr -> m ()
- runPrinterState :: PrinterState -> [Expr] -> PrinterState
- runInitPrinterState :: [Expr] -> PrinterState
- expressionsToOutputs :: [Expr] -> Seq Output
- modificationsExprList :: [Expr] -> [Expr]
- removeEmptyInnerCommaSeparatedExprList :: [Expr] -> [Expr]
- removeEmptyInnerCommaSeparatedExpr :: Expr -> Expr
- removeEmptyInnerCommaSeparated :: CommaSeparated [Expr] -> CommaSeparated [Expr]
- removeEmptyList :: forall a. [[a]] -> [[a]]
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 #
Constructors
| PrinterState | |
Fields
| |
Instances
outputList :: Lens' PrinterState (Seq Output) Source #
printerState :: LineNum -> NestLevel -> Seq Output -> PrinterState Source #
Smart-constructor for PrinterState.
addOutput :: MonadState PrinterState m => OutputType -> m () Source #
addOutputs :: MonadState PrinterState m => Seq OutputType -> m () Source #
Arguments
| :: MonadState PrinterState m | |
| => OutputType | |
| -> OutputType | |
| -> 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 = LineNum {unLineNum = 0}, _nestLevel = NestLevel {_unNestLevel = -1}, _outputList = fromList [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"]])PrinterState {_currLine = LineNum {unLineNum = 0}, _nestLevel = NestLevel {_unNestLevel = -1}, _outputList = fromList [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
putCommaSep :: forall m. MonadState PrinterState m => CommaSeparated [Expr] -> m () Source #
putComma :: MonadState PrinterState m => m () Source #
howManyLines :: [Expr] -> LineNum Source #
doIndent :: MonadState PrinterState m => m () Source #
newLine :: MonadState PrinterState m => m () Source #
newLineAndDoIndent :: MonadState PrinterState m => m () Source #
putExpression :: MonadState PrinterState m => Expr -> m () Source #
runPrinterState :: PrinterState -> [Expr] -> PrinterState Source #
runInitPrinterState :: [Expr] -> PrinterState Source #
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.
removeEmptyInnerCommaSeparatedExprList :: [Expr] -> [Expr] Source #
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]]