Safe Haskell | None |
---|---|
Language | Haskell2010 |
Common pretty-printing utility functions
Synopsis
- parens :: String -> String
- parensT :: Text -> Text
- parensPos :: Emit gen => gen -> gen
- intercalate :: Monoid m => m -> [m] -> m
- class Monoid gen => Emit gen where
- emit :: Text -> gen
- addMapping :: SourceSpan -> gen
- data SMap = SMap Text SourcePos SourcePos
- newtype StrPos = StrPos (SourcePos, Text, [SMap])
- newtype PlainString = PlainString Text
- runPlainString :: PlainString -> Text
- addMapping' :: Emit gen => Maybe SourceSpan -> gen
- bumpPos :: SourcePos -> SMap -> SMap
- addPos :: SourcePos -> SourcePos -> SourcePos
- data PrinterState = PrinterState {}
- emptyPrinterState :: PrinterState
- blockIndent :: Int
- withIndent :: StateT PrinterState Maybe gen -> StateT PrinterState Maybe gen
- currentIndent :: Emit gen => StateT PrinterState Maybe gen
- prettyPrintMany :: Emit gen => (a -> StateT PrinterState Maybe gen) -> [a] -> StateT PrinterState Maybe gen
- objectKeyRequiresQuoting :: Text -> Bool
- before :: Box -> Box -> Box
- beforeWithSpace :: Box -> Box -> Box
- endWith :: Box -> Box -> Box
Documentation
intercalate :: Monoid m => m -> [m] -> m Source #
Generalize intercalate slightly for monoids
class Monoid gen => Emit gen where Source #
addMapping :: SourceSpan -> gen Source #
Instances
Emit PlainString Source # | |
Defined in Language.PureScript.Pretty.Common emit :: Text -> PlainString Source # addMapping :: SourceSpan -> PlainString Source # | |
Emit StrPos Source # | |
Defined in Language.PureScript.Pretty.Common emit :: Text -> StrPos Source # addMapping :: SourceSpan -> StrPos Source # |
String with length and source-map entries
Instances
Semigroup StrPos Source # | Make a monoid where append consists of concatenating the string part, adding the lengths appropriately and advancing source mappings on the right hand side to account for the length of the left. |
Monoid StrPos Source # | |
Emit StrPos Source # | |
Defined in Language.PureScript.Pretty.Common emit :: Text -> StrPos Source # addMapping :: SourceSpan -> StrPos Source # |
newtype PlainString Source #
Instances
Semigroup PlainString Source # | |
Defined in Language.PureScript.Pretty.Common (<>) :: PlainString -> PlainString -> PlainString # sconcat :: NonEmpty PlainString -> PlainString # stimes :: Integral b => b -> PlainString -> PlainString # | |
Monoid PlainString Source # | |
Defined in Language.PureScript.Pretty.Common mempty :: PlainString # mappend :: PlainString -> PlainString -> PlainString # mconcat :: [PlainString] -> PlainString # | |
Emit PlainString Source # | |
Defined in Language.PureScript.Pretty.Common emit :: Text -> PlainString Source # addMapping :: SourceSpan -> PlainString Source # |
runPlainString :: PlainString -> Text Source #
addMapping' :: Emit gen => Maybe SourceSpan -> gen Source #
data PrinterState Source #
blockIndent :: Int Source #
Number of characters per identation level
withIndent :: StateT PrinterState Maybe gen -> StateT PrinterState Maybe gen Source #
Pretty print with a new indentation level
currentIndent :: Emit gen => StateT PrinterState Maybe gen Source #
Get the current indentation level
prettyPrintMany :: Emit gen => (a -> StateT PrinterState Maybe gen) -> [a] -> StateT PrinterState Maybe gen Source #
Print many lines
objectKeyRequiresQuoting :: Text -> Bool Source #