brittany-0.12.1.1: Haskell source code formatter

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Brittany.Internal.Config

Synopsis

Documentation

data CConfig f Source #

Constructors

Config 

Fields

Instances
CFunctor CConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

cMap :: (forall a. f a -> g a) -> CConfig f -> CConfig g #

CZipWith CConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

Data (CConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

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

toConstr :: CConfig Option -> Constr #

dataTypeOf :: CConfig Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

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 # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Show (CConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Generic (CConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Associated Types

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

Methods

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

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

Semigroup (CConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Semigroup (CConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Monoid (CConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

ToJSON (CConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

ToJSON (CConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

type Rep (CConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

type Rep (CConfig f) = D1 (MetaData "CConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.12.1.1-o2Aq9z1eWL9KvxdcHFz6v" False) (C1 (MetaCons "Config" PrefixI True) (((S1 (MetaSel (Just "_conf_version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int))) :*: S1 (MetaSel (Just "_conf_debug") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CDebugConfig f))) :*: (S1 (MetaSel (Just "_conf_layout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CLayoutConfig f)) :*: S1 (MetaSel (Just "_conf_errorHandling") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CErrorHandlingConfig f)))) :*: ((S1 (MetaSel (Just "_conf_forward") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CForwardOptions f)) :*: S1 (MetaSel (Just "_conf_preprocessor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CPreProcessorConfig f))) :*: (S1 (MetaSel (Just "_conf_roundtrip_exactprint_only") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 (MetaSel (Just "_conf_obfuscate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool)))))))

data CDebugConfig f Source #

Instances
CFunctor CDebugConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

cMap :: (forall a. f a -> g a) -> CDebugConfig f -> CDebugConfig g #

CZipWith CDebugConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

Data (CDebugConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

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

toConstr :: CDebugConfig Option -> Constr #

dataTypeOf :: CDebugConfig Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CDebugConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

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 # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Show (CDebugConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Generic (CDebugConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Associated Types

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

Methods

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

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

Semigroup (CDebugConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Semigroup (CDebugConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Monoid (CDebugConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

ToJSON (CDebugConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

ToJSON (CDebugConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CDebugConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CDebugConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

type Rep (CDebugConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

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

data CLayoutConfig f Source #

Constructors

LayoutConfig 

Fields

Instances
CFunctor CLayoutConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

cMap :: (forall a. f a -> g a) -> CLayoutConfig f -> CLayoutConfig g #

CZipWith CLayoutConfig Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

Data (CLayoutConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Methods

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

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

toConstr :: CLayoutConfig Option -> Constr #

dataTypeOf :: CLayoutConfig Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CLayoutConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

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 # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Show (CLayoutConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Generic (CLayoutConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Associated Types

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

Semigroup (CLayoutConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Semigroup (CLayoutConfig Identity) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

Monoid (CLayoutConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

ToJSON (CLayoutConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

ToJSON (CLayoutConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CLayoutConfig Maybe) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

FromJSON (CLayoutConfig Option) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types.Instances

type Rep (CLayoutConfig f) Source # 
Instance details

Defined in Language.Haskell.Brittany.Internal.Config.Types

type Rep (CLayoutConfig f) = D1 (MetaData "CLayoutConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.12.1.1-o2Aq9z1eWL9KvxdcHFz6v" False) (C1 (MetaCons "LayoutConfig" PrefixI True) ((((S1 (MetaSel (Just "_lconfig_cols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int))) :*: S1 (MetaSel (Just "_lconfig_indentPolicy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last IndentPolicy)))) :*: (S1 (MetaSel (Just "_lconfig_indentAmount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int))) :*: S1 (MetaSel (Just "_lconfig_indentWhereSpecial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))))) :*: ((S1 (MetaSel (Just "_lconfig_indentListSpecial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 (MetaSel (Just "_lconfig_importColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int)))) :*: (S1 (MetaSel (Just "_lconfig_importAsColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int))) :*: S1 (MetaSel (Just "_lconfig_altChooser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last AltChooser)))))) :*: (((S1 (MetaSel (Just "_lconfig_columnAlignMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last ColumnAlignMode))) :*: S1 (MetaSel (Just "_lconfig_alignmentLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Int)))) :*: (S1 (MetaSel (Just "_lconfig_alignmentBreakOnMultiline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 (MetaSel (Just "_lconfig_hangingTypeSignature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))))) :*: ((S1 (MetaSel (Just "_lconfig_reformatModulePreamble") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 (MetaSel (Just "_lconfig_allowSingleLineExportList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool)))) :*: (S1 (MetaSel (Just "_lconfig_allowHangingQuasiQuotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 (MetaSel (Just "_lconfig_experimentalSemicolonNewlines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Last Bool))))))))

readConfig :: MonadIO m => FilePath -> MaybeT m (Maybe (CConfig Option)) Source #

Reads a config from a file. If the file does not exist, returns Nothing. If the file exists and parsing fails, prints to stderr and aborts the MaybeT. Otherwise succeed via Just. If the second parameter is True and the file does not exist, writes the staticDefaultConfig to the file.

userConfigPath :: IO FilePath Source #

Looks for a user-global config file and return its path. If there is no global config in a system, one will be created.

findLocalConfigPath :: FilePath -> IO (Maybe FilePath) Source #

Searches for a local (per-project) brittany config starting from a given directory

readConfigs Source #

Arguments

:: CConfig Option

Explicit options, take highest priority

-> [FilePath]

List of config files to load and merge, highest priority first

-> MaybeT IO Config 

Reads specified configs.

readConfigsWithUserConfig Source #

Arguments

:: CConfig Option

Explicit options, take highest priority

-> [FilePath]

List of config files to load and merge, highest priority first

-> MaybeT IO Config 

Reads provided configs but also applies the user default configuration (with lowest priority)