| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.Brittany.Internal.Types
Documentation
type PPM = MultiRWS '[Map AnnKey Anns, Config, Anns] '[Builder, [BrittanyError], Seq String] '[] Source #
data LayoutState Source #
Constructors
| LayoutState | |
Fields
| |
Instances
lstate_baseY :: LayoutState -> Int Source #
lstate_indLevel :: LayoutState -> Int Source #
data BrittanyError Source #
Constructors
| ErrorInput String | parsing failed |
| ErrorUnusedComment String | internal error: some comment went missing |
| LayoutWarning String | some warning |
| Data ast => ErrorUnknownNode String ast | internal error: pretty-printing is not implemented for type of node in the syntax-tree |
| ErrorOutputCheck | checking the output for syntactic validity failed |
data BriSpacing Source #
Constructors
| BriSpacing | |
Fields | |
Constructors
| BrIndentNone | |
| BrIndentRegular | |
| BrIndentSpecial Int |
type ToBriDocM = MultiRWS '[Config, Anns] '[[BrittanyError], Seq String] '[NodeAllocIndex] Source #
Constructors
Constructors
| BDFEmpty | |
| BDFLit !Text | |
| BDFSeq [f (BriDocF f)] | |
| BDFCols ColSig [f (BriDocF f)] | |
| BDFSeparator | |
| BDFAddBaseY BrIndent (f (BriDocF f)) | |
| BDFBaseYPushCur (f (BriDocF f)) | |
| BDFBaseYPop (f (BriDocF f)) | |
| BDFIndentLevelPushCur (f (BriDocF f)) | |
| BDFIndentLevelPop (f (BriDocF f)) | |
| BDFPar | |
Fields
| |
| BDFAlt [f (BriDocF f)] | BDAddIndent BrIndent (BriDocF f) | BDNewline |
| BDFForwardLineMode (f (BriDocF f)) | |
| BDFExternal AnnKey (Set AnnKey) Bool Text | |
| BDFAnnotationPrior AnnKey (f (BriDocF f)) | |
| BDFAnnotationKW AnnKey (Maybe AnnKeywordId) (f (BriDocF f)) | |
| BDFAnnotationRest AnnKey (f (BriDocF f)) | |
| BDFLines [f (BriDocF f)] | |
| BDFEnsureIndent BrIndent (f (BriDocF f)) | |
| BDFForceMultiline (f (BriDocF f)) | |
| BDFForceSingleline (f (BriDocF f)) | |
| BDFNonBottomSpacing (f (BriDocF f)) | |
| BDFSetParSpacing (f (BriDocF f)) | |
| BDFForceParSpacing (f (BriDocF f)) | |
| BDFDebug String (f (BriDocF f)) | |
type BriDocNumbered = (Int, BriDocFInt) Source #
newtype NodeAllocIndex Source #
Constructors
| NodeAllocIndex Int |
isNotEmpty :: BriDoc -> Bool Source #
briDocSeqSpine :: BriDoc -> () Source #
briDocForceSpine :: BriDoc -> BriDoc Source #
data VerticalSpacingPar Source #
Instances
data VerticalSpacing Source #
Constructors
| VerticalSpacing | |
Fields
| |
Instances
newtype LineModeValidity a Source #
Constructors
| LineModeValidity (Maybe a) |
pattern LineModeValid :: forall t. t -> LineModeValidity t Source #
pattern LineModeInvalid :: forall t. LineModeValidity t Source #