Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data PerItemConfig Source #
PerItemConfig | |
|
Instances
Data PerItemConfig Source # | |
Defined in Language.Haskell.Brittany.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PerItemConfig -> c PerItemConfig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PerItemConfig # toConstr :: PerItemConfig -> Constr # dataTypeOf :: PerItemConfig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PerItemConfig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PerItemConfig) # gmapT :: (forall b. Data b => b -> b) -> PerItemConfig -> PerItemConfig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PerItemConfig -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PerItemConfig -> r # gmapQ :: (forall d. Data d => d -> u) -> PerItemConfig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PerItemConfig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PerItemConfig -> m PerItemConfig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PerItemConfig -> m PerItemConfig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PerItemConfig -> m PerItemConfig # |
type PPM = MultiRWS '[Map AnnKey Anns, PerItemConfig, Config, Anns] '[Builder, [BrittanyError], Seq String] '[] Source #
newtype TopLevelDeclNameMap Source #
data LayoutState Source #
LayoutState | |
|
Instances
Show LayoutState Source # | |
Defined in Language.Haskell.Brittany.Internal.Types showsPrec :: Int -> LayoutState -> ShowS # show :: LayoutState -> String # showList :: [LayoutState] -> ShowS # |
lstate_baseY :: LayoutState -> Int Source #
lstate_indLevel :: LayoutState -> Int Source #
data BrittanyError Source #
ErrorInput String | parsing failed |
ErrorUnusedComment String | internal error: some comment went missing |
ErrorMacroConfig String String | in-source config string parsing error; first argument is the parser output and second the corresponding, ill-formed input. |
LayoutWarning String | some warning |
Data ast => ErrorUnknownNode String (GenLocated SrcSpan ast) | internal error: pretty-printing is not implemented for type of node in the syntax-tree |
ErrorOutputCheck | checking the output for syntactic validity failed |
Instances
Eq ColSig Source # | |
Data ColSig Source # | |
Defined in Language.Haskell.Brittany.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSig -> c ColSig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSig # toConstr :: ColSig -> Constr # dataTypeOf :: ColSig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSig) # gmapT :: (forall b. Data b => b -> b) -> ColSig -> ColSig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSig -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSig -> r # gmapQ :: (forall d. Data d => d -> u) -> ColSig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColSig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig # | |
Ord ColSig Source # | |
Show ColSig Source # | |
Instances
Eq BrIndent Source # | |
Data BrIndent Source # | |
Defined in Language.Haskell.Brittany.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BrIndent -> c BrIndent # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BrIndent # toConstr :: BrIndent -> Constr # dataTypeOf :: BrIndent -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BrIndent) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BrIndent) # gmapT :: (forall b. Data b => b -> b) -> BrIndent -> BrIndent # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BrIndent -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BrIndent -> r # gmapQ :: (forall d. Data d => d -> u) -> BrIndent -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BrIndent -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent # | |
Ord BrIndent Source # | |
Defined in Language.Haskell.Brittany.Internal.Types | |
Show BrIndent Source # | |
type ToBriDocM = MultiRWS '[Config, Anns] '[[BrittanyError], Seq String] '[NodeAllocIndex] Source #
data DocMultiLine Source #
Instances
Eq DocMultiLine Source # | |
Defined in Language.Haskell.Brittany.Internal.Types (==) :: DocMultiLine -> DocMultiLine -> Bool # (/=) :: DocMultiLine -> DocMultiLine -> Bool # |
Instances
Eq BriDoc Source # | |
Data BriDoc Source # | |
Defined in Language.Haskell.Brittany.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BriDoc -> c BriDoc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BriDoc # toConstr :: BriDoc -> Constr # dataTypeOf :: BriDoc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BriDoc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BriDoc) # gmapT :: (forall b. Data b => b -> b) -> BriDoc -> BriDoc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BriDoc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BriDoc -> r # gmapQ :: (forall d. Data d => d -> u) -> BriDoc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BriDoc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc # | |
Ord BriDoc Source # | |
Uniplate BriDoc Source # | |
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 | |
| |
BDFAlt [f (BriDocF f)] | BDAddIndent BrIndent (BriDocF f) | BDNewline |
BDFForwardLineMode (f (BriDocF f)) | |
BDFExternal AnnKey (Set AnnKey) Bool Text | |
BDFPlain !Text | |
BDFAnnotationPrior AnnKey (f (BriDocF f)) | |
BDFAnnotationKW AnnKey (Maybe AnnKeywordId) (f (BriDocF f)) | |
BDFAnnotationRest AnnKey (f (BriDocF f)) | |
BDFMoveToKWDP AnnKey AnnKeywordId Bool (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)) |
Instances
Data (BriDocF ((,) Int)) Source # | |
Defined in Language.Haskell.Brittany.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BriDocF ((,) Int) -> c (BriDocF ((,) Int)) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BriDocF ((,) Int)) # toConstr :: BriDocF ((,) Int) -> Constr # dataTypeOf :: BriDocF ((,) Int) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BriDocF ((,) Int))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BriDocF ((,) Int))) # gmapT :: (forall b. Data b => b -> b) -> BriDocF ((,) Int) -> BriDocF ((,) Int) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BriDocF ((,) Int) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BriDocF ((,) Int) -> r # gmapQ :: (forall d. Data d => d -> u) -> BriDocF ((,) Int) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BriDocF ((,) Int) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) # |
type BriDocNumbered = (Int, BriDocFInt) Source #
newtype NodeAllocIndex Source #
isNotEmpty :: BriDoc -> Bool Source #
briDocSeqSpine :: BriDoc -> () Source #
briDocForceSpine :: BriDoc -> BriDoc Source #
data VerticalSpacingPar Source #
Instances
Eq VerticalSpacingPar Source # | |
Defined in Language.Haskell.Brittany.Internal.Types (==) :: VerticalSpacingPar -> VerticalSpacingPar -> Bool # (/=) :: VerticalSpacingPar -> VerticalSpacingPar -> Bool # | |
Show VerticalSpacingPar Source # | |
Defined in Language.Haskell.Brittany.Internal.Types showsPrec :: Int -> VerticalSpacingPar -> ShowS # show :: VerticalSpacingPar -> String # showList :: [VerticalSpacingPar] -> ShowS # |
data VerticalSpacing Source #
Instances
Eq VerticalSpacing Source # | |
Defined in Language.Haskell.Brittany.Internal.Types (==) :: VerticalSpacing -> VerticalSpacing -> Bool # (/=) :: VerticalSpacing -> VerticalSpacing -> Bool # | |
Show VerticalSpacing Source # | |
Defined in Language.Haskell.Brittany.Internal.Types showsPrec :: Int -> VerticalSpacing -> ShowS # show :: VerticalSpacing -> String # showList :: [VerticalSpacing] -> ShowS # |
newtype LineModeValidity a Source #
Instances
pattern LineModeValid :: forall t. t -> LineModeValidity t Source #
pattern LineModeInvalid :: forall t. LineModeValidity t Source #