| 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
Synopsis
- newtype LineNum = LineNum {}
- data PrinterState = PrinterState {}
- printerState :: LineNum -> NestLevel -> PrinterState
- addOutput :: MonadState PrinterState m => OutputType -> m Output
- addOutputs :: MonadState PrinterState m => [OutputType] -> m [Output]
- initPrinterState :: PrinterState
- putSurroundExpr :: MonadState PrinterState m => OutputType -> OutputType -> CommaSeparated [Expr] -> m [Output]
- putCommaSep :: forall m. MonadState PrinterState m => CommaSeparated [Expr] -> m [Output]
- putComma :: MonadState PrinterState m => m [Output]
- doIndent :: MonadState PrinterState m => m [Output]
- newLine :: MonadState PrinterState m => m Output
- newLineAndDoIndent :: MonadState PrinterState m => m [Output]
- addToNestLevel :: MonadState PrinterState m => NestLevel -> m ()
- addToCurrentLine :: MonadState PrinterState m => LineNum -> m ()
- putExpression :: MonadState PrinterState m => Expr -> m [Output]
- runPrinterState :: PrinterState -> [Expr] -> [Output]
- runInitPrinterState :: [Expr] -> [Output]
- expressionsToOutputs :: [Expr] -> [Output]
- modificationsExprList :: [Expr] -> [Expr]
- removeEmptyInnerCommaSeparatedExprList :: [Expr] -> [Expr]
- removeEmptyInnerCommaSeparatedExpr :: Expr -> Expr
- removeEmptyInnerCommaSeparated :: CommaSeparated [Expr] -> CommaSeparated [Expr]
- removeEmptyList :: forall a. [[a]] -> [[a]]
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 :}
Instances
| Eq LineNum Source # | |
| Data LineNum Source # | |
| 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 # | |
| Ord LineNum Source # | |
| Defined in Text.Pretty.Simple.Internal.ExprToOutput | |
| Read LineNum Source # | |
| Show LineNum Source # | |
| Generic LineNum Source # | |
| type Rep LineNum Source # | |
| Defined in Text.Pretty.Simple.Internal.ExprToOutput | |
data PrinterState Source #
Constructors
| PrinterState | |
Instances
printerState :: LineNum -> NestLevel -> PrinterState Source #
Smart-constructor for PrinterState.
addOutput :: MonadState PrinterState m => OutputType -> m Output Source #
addOutputs :: MonadState PrinterState m => [OutputType] -> m [Output] 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
putCommaSep :: forall m. MonadState PrinterState m => CommaSeparated [Expr] -> m [Output] Source #
putComma :: MonadState PrinterState m => m [Output] Source #
doIndent :: MonadState PrinterState m => m [Output] Source #
newLine :: MonadState PrinterState m => m Output Source #
newLineAndDoIndent :: MonadState PrinterState m => m [Output] Source #
addToNestLevel :: MonadState PrinterState m => NestLevel -> m () Source #
addToCurrentLine :: MonadState PrinterState m => LineNum -> m () Source #
putExpression :: MonadState PrinterState m => Expr -> m [Output] Source #
runPrinterState :: PrinterState -> [Expr] -> [Output] Source #
runInitPrinterState :: [Expr] -> [Output] Source #
expressionsToOutputs :: [Expr] -> [Output] 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]]