Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | Isaac Elliott <isaace71295@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- showModule :: Module v a -> Text
- showStatement :: Statement v a -> Text
- showExpr :: Expr v a -> Text
- data RenderOutput a
- showRenderOutput :: RenderOutput a -> Text
- singleton :: PyToken () -> RenderOutput ()
- renderModule :: Module v a -> RenderOutput ()
- renderStatement :: Statement v a -> RenderOutput ()
- renderExpr :: Expr v a -> RenderOutput ()
- showQuoteType :: QuoteType -> Char
- showStringPrefix :: StringPrefix -> Text
- showBytesPrefix :: BytesPrefix -> Text
- showToken :: PyToken a -> Text
- showTokens :: [PyToken a] -> Text
- expandIndents :: PyToken a -> [PyToken ()]
- whitespaceTokens :: Whitespace -> [PyToken ()]
- commentTokens :: Comment a -> [PyToken ()]
- parens :: RenderOutput a -> RenderOutput a
- braces :: RenderOutput a -> RenderOutput a
- brackets :: RenderOutput a -> RenderOutput a
- renderWhitespace :: Whitespace -> RenderOutput ()
- renderCommaSep :: (a -> RenderOutput ()) -> CommaSep a -> RenderOutput ()
- renderCommaSep1 :: (a -> RenderOutput ()) -> CommaSep1 a -> RenderOutput ()
- renderCommaSep1' :: (a -> RenderOutput ()) -> CommaSep1' a -> RenderOutput ()
- renderIdent :: Ident v a -> RenderOutput ()
- renderComment :: Comment a -> RenderOutput ()
- renderModuleName :: ModuleName v a -> RenderOutput ()
- renderDot :: Dot -> RenderOutput ()
- renderRelativeModuleName :: RelativeModuleName v a -> RenderOutput ()
- renderImportAs :: (e a -> RenderOutput ()) -> ImportAs e v a -> RenderOutput ()
- renderImportTargets :: ImportTargets v a -> RenderOutput ()
- renderSimpleStatement :: SimpleStatement v a -> RenderOutput ()
- renderCompoundStatement :: CompoundStatement v a -> RenderOutput ()
- renderBlock :: Block v a -> RenderOutput ()
- renderIndent :: Indent -> RenderOutput ()
- renderIndents :: Indents a -> RenderOutput ()
- renderExceptAs :: ExceptAs v a -> RenderOutput ()
- renderArg :: (Expr v a -> RenderOutput ()) -> Arg v a -> RenderOutput ()
- renderParam :: Param v a -> RenderOutput ()
- renderParams :: CommaSep (Param v a) -> RenderOutput ()
- renderCompFor :: CompFor v a -> RenderOutput ()
- renderCompIf :: CompIf v a -> RenderOutput ()
- renderComprehension :: (e v a -> RenderOutput ()) -> Comprehension e v a -> RenderOutput ()
- renderBinOp :: BinOp a -> RenderOutput ()
- renderUnOp :: UnOp a -> RenderOutput ()
- renderSubscript :: Subscript v a -> RenderOutput ()
- renderPyChars :: QuoteType -> StringType -> [PyChar] -> Text
- escapeChars :: [(Char, Char)]
- intToHex :: Int -> Text
Common Functions
Rendering
data RenderOutput a Source #
A RenderOutput
is an intermediate form used during rendering
with efficient concatenation
Instances
Monad RenderOutput Source # | |
Defined in Language.Python.Internal.Render (>>=) :: RenderOutput a -> (a -> RenderOutput b) -> RenderOutput b # (>>) :: RenderOutput a -> RenderOutput b -> RenderOutput b # return :: a -> RenderOutput a # fail :: String -> RenderOutput a # | |
Functor RenderOutput Source # | |
Defined in Language.Python.Internal.Render fmap :: (a -> b) -> RenderOutput a -> RenderOutput b # (<$) :: a -> RenderOutput b -> RenderOutput a # | |
Applicative RenderOutput Source # | |
Defined in Language.Python.Internal.Render pure :: a -> RenderOutput a # (<*>) :: RenderOutput (a -> b) -> RenderOutput a -> RenderOutput b # liftA2 :: (a -> b -> c) -> RenderOutput a -> RenderOutput b -> RenderOutput c # (*>) :: RenderOutput a -> RenderOutput b -> RenderOutput b # (<*) :: RenderOutput a -> RenderOutput b -> RenderOutput a # |
showRenderOutput :: RenderOutput a -> Text Source #
Run a RenderOutput
to produce a final Text
.
These Text
s should then not be appended any more. All appending should
be done during the RenderOutput
phase.
singleton :: PyToken () -> RenderOutput () Source #
Render a single token as a RenderOutput
renderModule :: Module v a -> RenderOutput () Source #
renderStatement :: Statement v a -> RenderOutput () Source #
renderExpr :: Expr v a -> RenderOutput () Source #
Miscellany
showQuoteType :: QuoteType -> Char Source #
showStringPrefix :: StringPrefix -> Text Source #
showBytesPrefix :: BytesPrefix -> Text Source #
showTokens :: [PyToken a] -> Text Source #
expandIndents :: PyToken a -> [PyToken ()] Source #
whitespaceTokens :: Whitespace -> [PyToken ()] Source #
commentTokens :: Comment a -> [PyToken ()] Source #
parens :: RenderOutput a -> RenderOutput a Source #
braces :: RenderOutput a -> RenderOutput a Source #
brackets :: RenderOutput a -> RenderOutput a Source #
renderWhitespace :: Whitespace -> RenderOutput () Source #
renderCommaSep :: (a -> RenderOutput ()) -> CommaSep a -> RenderOutput () Source #
renderCommaSep1 :: (a -> RenderOutput ()) -> CommaSep1 a -> RenderOutput () Source #
renderCommaSep1' :: (a -> RenderOutput ()) -> CommaSep1' a -> RenderOutput () Source #
renderIdent :: Ident v a -> RenderOutput () Source #
renderComment :: Comment a -> RenderOutput () Source #
renderModuleName :: ModuleName v a -> RenderOutput () Source #
renderDot :: Dot -> RenderOutput () Source #
renderRelativeModuleName :: RelativeModuleName v a -> RenderOutput () Source #
renderImportAs :: (e a -> RenderOutput ()) -> ImportAs e v a -> RenderOutput () Source #
renderImportTargets :: ImportTargets v a -> RenderOutput () Source #
renderSimpleStatement :: SimpleStatement v a -> RenderOutput () Source #
renderCompoundStatement :: CompoundStatement v a -> RenderOutput () Source #
renderBlock :: Block v a -> RenderOutput () Source #
renderIndent :: Indent -> RenderOutput () Source #
renderIndents :: Indents a -> RenderOutput () Source #
renderExceptAs :: ExceptAs v a -> RenderOutput () Source #
renderArg :: (Expr v a -> RenderOutput ()) -> Arg v a -> RenderOutput () Source #
renderParam :: Param v a -> RenderOutput () Source #
renderParams :: CommaSep (Param v a) -> RenderOutput () Source #
renderCompFor :: CompFor v a -> RenderOutput () Source #
renderCompIf :: CompIf v a -> RenderOutput () Source #
renderComprehension :: (e v a -> RenderOutput ()) -> Comprehension e v a -> RenderOutput () Source #
renderBinOp :: BinOp a -> RenderOutput () Source #
renderUnOp :: UnOp a -> RenderOutput () Source #
renderSubscript :: Subscript v a -> RenderOutput () Source #
renderPyChars :: QuoteType -> StringType -> [PyChar] -> Text Source #
escapeChars :: [(Char, Char)] Source #