brittany-0.9.0.1: Haskell source code formatter

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Brittany.Internal.Config.Types

Documentation

data CDebugConfig f Source #

Instances

CZipWith CDebugConfig Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CDebugConfig g -> CDebugConfig h -> CDebugConfig i #

Data (CDebugConfig Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CDebugConfig Identity -> c (CDebugConfig Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CDebugConfig Identity) #

toConstr :: CDebugConfig Identity -> Constr #

dataTypeOf :: CDebugConfig Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CDebugConfig Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CDebugConfig Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CDebugConfig Identity -> CDebugConfig Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CDebugConfig Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CDebugConfig Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CDebugConfig Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CDebugConfig Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CDebugConfig Identity -> m (CDebugConfig Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CDebugConfig Identity -> m (CDebugConfig Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CDebugConfig Identity -> m (CDebugConfig Identity) #

Show (CDebugConfig Option) Source # 
Show (CDebugConfig Identity) Source # 
Generic (CDebugConfig f) Source # 

Associated Types

type Rep (CDebugConfig f) :: * -> * #

Methods

from :: CDebugConfig f -> Rep (CDebugConfig f) x #

to :: Rep (CDebugConfig f) x -> CDebugConfig f #

Semigroup (CDebugConfig Option) Source # 
Semigroup (CDebugConfig Identity) Source # 
Monoid (CDebugConfig Option) Source # 
type Rep (CDebugConfig f) Source # 
type Rep (CDebugConfig f) = D1 * (MetaData "CDebugConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) (C1 * (MetaCons "DebugConfig" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_config") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_annotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_dconf_dump_ast_unknown") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_ast_full") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_raw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_simpl_alt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool))))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_simpl_floating") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_simpl_par") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_simpl_columns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_simpl_indent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dconf_dump_bridoc_final") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_dconf_roundtrip_exactprint_only") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))))))))

data CLayoutConfig f Source #

Instances

CZipWith CLayoutConfig Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CLayoutConfig g -> CLayoutConfig h -> CLayoutConfig i #

Data (CLayoutConfig Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CLayoutConfig Identity -> c (CLayoutConfig Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CLayoutConfig Identity) #

toConstr :: CLayoutConfig Identity -> Constr #

dataTypeOf :: CLayoutConfig Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CLayoutConfig Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CLayoutConfig Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CLayoutConfig Identity -> CLayoutConfig Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CLayoutConfig Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CLayoutConfig Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CLayoutConfig Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CLayoutConfig Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CLayoutConfig Identity -> m (CLayoutConfig Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CLayoutConfig Identity -> m (CLayoutConfig Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CLayoutConfig Identity -> m (CLayoutConfig Identity) #

Show (CLayoutConfig Option) Source # 
Show (CLayoutConfig Identity) Source # 
Generic (CLayoutConfig f) Source # 

Associated Types

type Rep (CLayoutConfig f) :: * -> * #

Semigroup (CLayoutConfig Option) Source # 
Semigroup (CLayoutConfig Identity) Source # 
Monoid (CLayoutConfig Option) Source # 
type Rep (CLayoutConfig f) Source # 
type Rep (CLayoutConfig f) = D1 * (MetaData "CLayoutConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) (C1 * (MetaCons "LayoutConfig" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_cols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Int)))) (S1 * (MetaSel (Just Symbol "_lconfig_indentPolicy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last IndentPolicy))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_indentAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_indentWhereSpecial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_lconfig_indentListSpecial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool))))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_importColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_altChooser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last AltChooser)))) (S1 * (MetaSel (Just Symbol "_lconfig_columnAlignMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last ColumnAlignMode)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_alignmentLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lconfig_alignmentBreakOnMultiline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_lconfig_hangingTypeSignature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))))))))

data CForwardOptions f Source #

Constructors

ForwardOptions 

Fields

Instances

CZipWith CForwardOptions Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CForwardOptions g -> CForwardOptions h -> CForwardOptions i #

Data (CForwardOptions Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CForwardOptions Identity -> c (CForwardOptions Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CForwardOptions Identity) #

toConstr :: CForwardOptions Identity -> Constr #

dataTypeOf :: CForwardOptions Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CForwardOptions Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CForwardOptions Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CForwardOptions Identity -> CForwardOptions Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CForwardOptions Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CForwardOptions Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CForwardOptions Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CForwardOptions Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CForwardOptions Identity -> m (CForwardOptions Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CForwardOptions Identity -> m (CForwardOptions Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CForwardOptions Identity -> m (CForwardOptions Identity) #

Show (CForwardOptions Option) Source # 
Show (CForwardOptions Identity) Source # 
Generic (CForwardOptions f) Source # 

Associated Types

type Rep (CForwardOptions f) :: * -> * #

Semigroup (CForwardOptions Option) Source # 
Semigroup (CForwardOptions Identity) Source # 
Monoid (CForwardOptions Option) Source # 
type Rep (CForwardOptions f) Source # 
type Rep (CForwardOptions f) = D1 * (MetaData "CForwardOptions" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) (C1 * (MetaCons "ForwardOptions" PrefixI True) (S1 * (MetaSel (Just Symbol "_options_ghc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f [String]))))

data CErrorHandlingConfig f Source #

Constructors

ErrorHandlingConfig 

Fields

Instances

CZipWith CErrorHandlingConfig Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CErrorHandlingConfig g -> CErrorHandlingConfig h -> CErrorHandlingConfig i #

Data (CErrorHandlingConfig Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CErrorHandlingConfig Identity -> c (CErrorHandlingConfig Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CErrorHandlingConfig Identity) #

toConstr :: CErrorHandlingConfig Identity -> Constr #

dataTypeOf :: CErrorHandlingConfig Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CErrorHandlingConfig Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CErrorHandlingConfig Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CErrorHandlingConfig Identity -> CErrorHandlingConfig Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CErrorHandlingConfig Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CErrorHandlingConfig Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CErrorHandlingConfig Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CErrorHandlingConfig Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CErrorHandlingConfig Identity -> m (CErrorHandlingConfig Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CErrorHandlingConfig Identity -> m (CErrorHandlingConfig Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CErrorHandlingConfig Identity -> m (CErrorHandlingConfig Identity) #

Show (CErrorHandlingConfig Option) Source # 
Show (CErrorHandlingConfig Identity) Source # 
Generic (CErrorHandlingConfig f) Source # 
Semigroup (CErrorHandlingConfig Option) Source # 
Semigroup (CErrorHandlingConfig Identity) Source # 
Monoid (CErrorHandlingConfig Option) Source # 
type Rep (CErrorHandlingConfig f) Source # 
type Rep (CErrorHandlingConfig f) = D1 * (MetaData "CErrorHandlingConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) (C1 * (MetaCons "ErrorHandlingConfig" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_econf_produceOutputOnErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))) (S1 * (MetaSel (Just Symbol "_econf_Werror") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_econf_ExactPrintFallback") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last ExactPrintFallbackMode)))) (S1 * (MetaSel (Just Symbol "_econf_omit_output_valid_check") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool)))))))

data CPreProcessorConfig f Source #

Instances

CZipWith CPreProcessorConfig Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CPreProcessorConfig g -> CPreProcessorConfig h -> CPreProcessorConfig i #

Data (CPreProcessorConfig Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CPreProcessorConfig Identity -> c (CPreProcessorConfig Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CPreProcessorConfig Identity) #

toConstr :: CPreProcessorConfig Identity -> Constr #

dataTypeOf :: CPreProcessorConfig Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CPreProcessorConfig Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CPreProcessorConfig Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CPreProcessorConfig Identity -> CPreProcessorConfig Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CPreProcessorConfig Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CPreProcessorConfig Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CPreProcessorConfig Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CPreProcessorConfig Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CPreProcessorConfig Identity -> m (CPreProcessorConfig Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CPreProcessorConfig Identity -> m (CPreProcessorConfig Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CPreProcessorConfig Identity -> m (CPreProcessorConfig Identity) #

Show (CPreProcessorConfig Option) Source # 
Show (CPreProcessorConfig Identity) Source # 
Generic (CPreProcessorConfig f) Source # 

Associated Types

type Rep (CPreProcessorConfig f) :: * -> * #

Semigroup (CPreProcessorConfig Option) Source # 
Semigroup (CPreProcessorConfig Identity) Source # 
Monoid (CPreProcessorConfig Option) Source # 
type Rep (CPreProcessorConfig f) Source # 
type Rep (CPreProcessorConfig f) = D1 * (MetaData "CPreProcessorConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) (C1 * (MetaCons "PreProcessorConfig" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ppconf_CPPMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last CPPMode)))) (S1 * (MetaSel (Just Symbol "_ppconf_hackAroundIncludes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f (Last Bool))))))

data CConfig f Source #

Instances

CZipWith CConfig Source # 

Methods

cZipWith :: (forall a. g a -> h a -> i a) -> CConfig g -> CConfig h -> CConfig i #

Data (CConfig Identity) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CConfig Identity -> c (CConfig Identity) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CConfig Identity) #

toConstr :: CConfig Identity -> Constr #

dataTypeOf :: CConfig Identity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CConfig Identity)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CConfig Identity)) #

gmapT :: (forall b. Data b => b -> b) -> CConfig Identity -> CConfig Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CConfig Identity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CConfig Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> CConfig Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CConfig Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CConfig Identity -> m (CConfig Identity) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CConfig Identity -> m (CConfig Identity) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CConfig Identity -> m (CConfig Identity) #

Show (CConfig Option) Source # 
Show (CConfig Identity) Source # 
Generic (CConfig f) Source # 

Associated Types

type Rep (CConfig f) :: * -> * #

Methods

from :: CConfig f -> Rep (CConfig f) x #

to :: Rep (CConfig f) x -> CConfig f #

Semigroup (CConfig Option) Source # 
Semigroup (CConfig Identity) Source # 
Monoid (CConfig Option) Source # 
type Rep (CConfig f) Source # 

data IndentPolicy Source #

Instances

Eq IndentPolicy Source # 
Data IndentPolicy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IndentPolicy -> c IndentPolicy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IndentPolicy #

toConstr :: IndentPolicy -> Constr #

dataTypeOf :: IndentPolicy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IndentPolicy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IndentPolicy) #

gmapT :: (forall b. Data b => b -> b) -> IndentPolicy -> IndentPolicy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IndentPolicy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IndentPolicy -> r #

gmapQ :: (forall d. Data d => d -> u) -> IndentPolicy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IndentPolicy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IndentPolicy -> m IndentPolicy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IndentPolicy -> m IndentPolicy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IndentPolicy -> m IndentPolicy #

Show IndentPolicy Source # 
Generic IndentPolicy Source # 

Associated Types

type Rep IndentPolicy :: * -> * #

type Rep IndentPolicy Source # 
type Rep IndentPolicy = D1 * (MetaData "IndentPolicy" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) ((:+:) * (C1 * (MetaCons "IndentPolicyLeft" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IndentPolicyFree" PrefixI False) (U1 *)) (C1 * (MetaCons "IndentPolicyMultiple" PrefixI False) (U1 *))))

data AltChooser Source #

Instances

Data AltChooser Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AltChooser -> c AltChooser #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AltChooser #

toConstr :: AltChooser -> Constr #

dataTypeOf :: AltChooser -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AltChooser) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltChooser) #

gmapT :: (forall b. Data b => b -> b) -> AltChooser -> AltChooser #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AltChooser -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AltChooser -> r #

gmapQ :: (forall d. Data d => d -> u) -> AltChooser -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AltChooser -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AltChooser -> m AltChooser #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AltChooser -> m AltChooser #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AltChooser -> m AltChooser #

Show AltChooser Source # 
Generic AltChooser Source # 

Associated Types

type Rep AltChooser :: * -> * #

type Rep AltChooser Source # 
type Rep AltChooser = D1 * (MetaData "AltChooser" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) ((:+:) * (C1 * (MetaCons "AltChooserSimpleQuick" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AltChooserShallowBest" PrefixI False) (U1 *)) (C1 * (MetaCons "AltChooserBoundedSearch" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))

data ColumnAlignMode Source #

Constructors

ColumnAlignModeDisabled

Make no column alignments whatsoever

ColumnAlignModeUnanimously

Make column alignments only if it does not cause overflow for any of the affected lines.

ColumnAlignModeMajority Float

If at least (ratio::Float) of the aligned elements have sufficient space for the alignment, act like ColumnAlignModeAnimously; otherwise act like ColumnAlignModeDisabled.

ColumnAlignModeAnimouslyScale Int

Scale back columns to some degree if their sum leads to overflow. This is done in a linear fashion. The Int specifies additional columns to be added to column maximum for scaling calculation purposes.

ColumnAlignModeAnimously

Decide on a case-by-case basis if alignment would cause overflow. If it does, cancel all alignments for this (nested) column description. ColumnAlignModeAnimouslySome -- potentially to implement

ColumnAlignModeAlways

Always respect column alignments, even if it makes stuff overflow.

Instances

Data ColumnAlignMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColumnAlignMode -> c ColumnAlignMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColumnAlignMode #

toConstr :: ColumnAlignMode -> Constr #

dataTypeOf :: ColumnAlignMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ColumnAlignMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColumnAlignMode) #

gmapT :: (forall b. Data b => b -> b) -> ColumnAlignMode -> ColumnAlignMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlignMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlignMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ColumnAlignMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColumnAlignMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColumnAlignMode -> m ColumnAlignMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlignMode -> m ColumnAlignMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlignMode -> m ColumnAlignMode #

Show ColumnAlignMode Source # 
Generic ColumnAlignMode Source # 
type Rep ColumnAlignMode Source # 
type Rep ColumnAlignMode = D1 * (MetaData "ColumnAlignMode" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ColumnAlignModeDisabled" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ColumnAlignModeUnanimously" PrefixI False) (U1 *)) (C1 * (MetaCons "ColumnAlignModeMajority" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Float))))) ((:+:) * (C1 * (MetaCons "ColumnAlignModeAnimouslyScale" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "ColumnAlignModeAnimously" PrefixI False) (U1 *)) (C1 * (MetaCons "ColumnAlignModeAlways" PrefixI False) (U1 *)))))

data CPPMode Source #

Instances

Data CPPMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CPPMode -> c CPPMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CPPMode #

toConstr :: CPPMode -> Constr #

dataTypeOf :: CPPMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CPPMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CPPMode) #

gmapT :: (forall b. Data b => b -> b) -> CPPMode -> CPPMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CPPMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CPPMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> CPPMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CPPMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CPPMode -> m CPPMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CPPMode -> m CPPMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CPPMode -> m CPPMode #

Show CPPMode Source # 
Generic CPPMode Source # 

Associated Types

type Rep CPPMode :: * -> * #

Methods

from :: CPPMode -> Rep CPPMode x #

to :: Rep CPPMode x -> CPPMode #

type Rep CPPMode Source # 
type Rep CPPMode = D1 * (MetaData "CPPMode" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) ((:+:) * (C1 * (MetaCons "CPPModeAbort" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CPPModeWarn" PrefixI False) (U1 *)) (C1 * (MetaCons "CPPModeNowarn" PrefixI False) (U1 *))))

data ExactPrintFallbackMode Source #

Instances

Data ExactPrintFallbackMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExactPrintFallbackMode -> c ExactPrintFallbackMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExactPrintFallbackMode #

toConstr :: ExactPrintFallbackMode -> Constr #

dataTypeOf :: ExactPrintFallbackMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExactPrintFallbackMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExactPrintFallbackMode) #

gmapT :: (forall b. Data b => b -> b) -> ExactPrintFallbackMode -> ExactPrintFallbackMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExactPrintFallbackMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExactPrintFallbackMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExactPrintFallbackMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExactPrintFallbackMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExactPrintFallbackMode -> m ExactPrintFallbackMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExactPrintFallbackMode -> m ExactPrintFallbackMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExactPrintFallbackMode -> m ExactPrintFallbackMode #

Show ExactPrintFallbackMode Source # 
Generic ExactPrintFallbackMode Source # 
type Rep ExactPrintFallbackMode Source # 
type Rep ExactPrintFallbackMode = D1 * (MetaData "ExactPrintFallbackMode" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.9.0.1-LQfkzb1o8NR2qnt27g7r0g" False) ((:+:) * (C1 * (MetaCons "ExactPrintFallbackModeNever" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ExactPrintFallbackModeInline" PrefixI False) (U1 *)) (C1 * (MetaCons "ExactPrintFallbackModeRisky" PrefixI False) (U1 *))))

cMap :: CZipWith k => (forall a. f a -> g a) -> k f -> k g Source #