| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
LText.Document
Synopsis
- data Document = Document {
- documentArity :: [Text]
- documentBody :: [DocumentBody]
- data DocumentBody
- = RawText [Text]
- | Expression Expr
- repackDocument :: [DocumentBody] -> [DocumentBody]
- parseDocument :: MonadParse m => Text -> m (Document, Maybe (Text, Text))
- printDocument :: MonadPrettyPrint m => Maybe (Text, Text) -> Document -> m Text
- fromDocument :: FilePath -> Document -> Expr
- data PrintError
- data PrintabilityMode
- decorateUnprintable :: Expr -> Expr
- isAnyUnprintable :: Expr -> Bool
- handlePrintError :: PrintError -> IO a
- toDocument :: MonadThrow m => Expr -> m Document
- fetchDocument :: FilePath -> IO Expr
- rawDocument :: FilePath -> IO Expr
Documentation
A parsed document
Constructors
| Document | |
Fields
| |
data DocumentBody Source #
The body of a document is either a block of raw text, or an ltext expression.
Constructors
| RawText [Text] | |
| Expression Expr |
Instances
| Arbitrary DocumentBody Source # | |
Defined in LText.Document | |
| Show DocumentBody Source # | |
Defined in LText.Document Methods showsPrec :: Int -> DocumentBody -> ShowS # show :: DocumentBody -> String # showList :: [DocumentBody] -> ShowS # | |
| Eq DocumentBody Source # | |
Defined in LText.Document | |
repackDocument :: [DocumentBody] -> [DocumentBody] Source #
Concatenates adjacent RawText blocks
Takes a raw text file and returns the parsed document, and left and right delimiters if it has arity.
Given a document, generate an expression (without thinking too hard about it)
data PrintError Source #
Constructors
| ConcatExprText Expr | |
| NoExplicitDelimiters |
Instances
| Exception PrintError Source # | |
Defined in LText.Document Methods toException :: PrintError -> SomeException # fromException :: SomeException -> Maybe PrintError # displayException :: PrintError -> String # | |
| Generic PrintError Source # | |
Defined in LText.Document Associated Types type Rep PrintError :: Type -> Type # | |
| Show PrintError Source # | |
Defined in LText.Document Methods showsPrec :: Int -> PrintError -> ShowS # show :: PrintError -> String # showList :: [PrintError] -> ShowS # | |
| Eq PrintError Source # | |
Defined in LText.Document | |
| type Rep PrintError Source # | |
Defined in LText.Document type Rep PrintError = D1 ('MetaData "PrintError" "LText.Document" "ltext-0.1.5-2mWRDtVcy1xDs2drGHsToO" 'False) (C1 ('MetaCons "ConcatExprText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)) :+: C1 ('MetaCons "NoExplicitDelimiters" 'PrefixI 'False) (U1 :: Type -> Type)) | |
data PrintabilityMode Source #
Constructors
| InsideConcat | |
| InsideExpr |
decorateUnprintable :: Expr -> Expr Source #
isAnyUnprintable :: Expr -> Bool Source #
handlePrintError :: PrintError -> IO a Source #
toDocument :: MonadThrow m => Expr -> m Document Source #