brittany-0.13.1.1: Haskell source code formatter
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Brittany

Synopsis

Documentation

parsePrintModule :: Config -> Text -> IO (Either [BrittanyError] Text) Source #

Exposes the transformation in an pseudo-pure fashion. The signature contains IO due to the GHC API not exposing a pure parsing function, but there should be no observable effects.

Note that this function ignores/resets all config values regarding debugging, i.e. it will never use trace/write to stderr.

Note that the ghc parsing function used internally currently is wrapped in mask_, so cannot be killed easily. If you don't control the input, you may wish to put some proper upper bound on the input's size as a timeout won't do.

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)

data CConfig f Source #

Constructors

Config 

Fields

Instances

Instances details
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 :: forall r r'. (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 :: forall r r'. (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.13.1.1-Jy7sLKH71HuBBZp3S53aXI" '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_disable_formatting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 ('MetaSel ('Just "_conf_obfuscate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool))))))))

data CDebugConfig f Source #

Instances

Instances details
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 :: forall r r'. (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 :: forall r r'. (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.13.1.1-Jy7sLKH71HuBBZp3S53aXI" '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

Instances details
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 :: forall r r'. (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 :: forall r r'. (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.13.1.1-Jy7sLKH71HuBBZp3S53aXI" '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))))))))

data CErrorHandlingConfig f Source #

Constructors

ErrorHandlingConfig 

Fields

Instances

Instances details
CFunctor CErrorHandlingConfig Source # 
Instance details

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

Methods

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

CZipWith CErrorHandlingConfig Source # 
Instance details

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

Methods

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

Data (CErrorHandlingConfig 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) -> CErrorHandlingConfig Option -> c (CErrorHandlingConfig Option) #

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

toConstr :: CErrorHandlingConfig Option -> Constr #

dataTypeOf :: CErrorHandlingConfig Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CErrorHandlingConfig 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) -> 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 :: forall r r'. (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 # 
Instance details

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

Show (CErrorHandlingConfig Identity) Source # 
Instance details

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

Generic (CErrorHandlingConfig f) Source # 
Instance details

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

Associated Types

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

Semigroup (CErrorHandlingConfig Option) Source # 
Instance details

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

Semigroup (CErrorHandlingConfig Identity) Source # 
Instance details

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

Monoid (CErrorHandlingConfig Option) Source # 
Instance details

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

ToJSON (CErrorHandlingConfig Maybe) Source # 
Instance details

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

ToJSON (CErrorHandlingConfig Option) Source # 
Instance details

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

FromJSON (CErrorHandlingConfig Maybe) Source # 
Instance details

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

FromJSON (CErrorHandlingConfig Option) Source # 
Instance details

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

type Rep (CErrorHandlingConfig f) Source # 
Instance details

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

type Rep (CErrorHandlingConfig f) = D1 ('MetaData "CErrorHandlingConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.13.1.1-Jy7sLKH71HuBBZp3S53aXI" 'False) (C1 ('MetaCons "ErrorHandlingConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_econf_produceOutputOnErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool))) :*: S1 ('MetaSel ('Just "_econf_Werror") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool)))) :*: (S1 ('MetaSel ('Just "_econf_ExactPrintFallback") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last ExactPrintFallbackMode))) :*: S1 ('MetaSel ('Just "_econf_omit_output_valid_check") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool))))))

data CForwardOptions f Source #

Constructors

ForwardOptions 

Fields

Instances

Instances details
CFunctor CForwardOptions Source # 
Instance details

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

Methods

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

CZipWith CForwardOptions Source # 
Instance details

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

Methods

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

Data (CForwardOptions 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) -> CForwardOptions Option -> c (CForwardOptions Option) #

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

toConstr :: CForwardOptions Option -> Constr #

dataTypeOf :: CForwardOptions Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CForwardOptions 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) -> 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 :: forall r r'. (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 # 
Instance details

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

Show (CForwardOptions Identity) Source # 
Instance details

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

Generic (CForwardOptions f) Source # 
Instance details

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

Associated Types

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

Semigroup (CForwardOptions Option) Source # 
Instance details

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

Semigroup (CForwardOptions Identity) Source # 
Instance details

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

Monoid (CForwardOptions Option) Source # 
Instance details

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

ToJSON (CForwardOptions Maybe) Source # 
Instance details

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

ToJSON (CForwardOptions Option) Source # 
Instance details

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

FromJSON (CForwardOptions Maybe) Source # 
Instance details

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

FromJSON (CForwardOptions Option) Source # 
Instance details

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

type Rep (CForwardOptions f) Source # 
Instance details

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

type Rep (CForwardOptions f) = D1 ('MetaData "CForwardOptions" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.13.1.1-Jy7sLKH71HuBBZp3S53aXI" 'False) (C1 ('MetaCons "ForwardOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "_options_ghc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f [String]))))

data CPreProcessorConfig f Source #

Instances

Instances details
CFunctor CPreProcessorConfig Source # 
Instance details

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

Methods

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

CZipWith CPreProcessorConfig Source # 
Instance details

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

Methods

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

Data (CPreProcessorConfig 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) -> CPreProcessorConfig Option -> c (CPreProcessorConfig Option) #

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

toConstr :: CPreProcessorConfig Option -> Constr #

dataTypeOf :: CPreProcessorConfig Option -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (CPreProcessorConfig 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) -> 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 :: forall r r'. (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 # 
Instance details

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

Show (CPreProcessorConfig Identity) Source # 
Instance details

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

Generic (CPreProcessorConfig f) Source # 
Instance details

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

Associated Types

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

Semigroup (CPreProcessorConfig Option) Source # 
Instance details

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

Semigroup (CPreProcessorConfig Identity) Source # 
Instance details

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

Monoid (CPreProcessorConfig Option) Source # 
Instance details

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

ToJSON (CPreProcessorConfig Maybe) Source # 
Instance details

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

ToJSON (CPreProcessorConfig Option) Source # 
Instance details

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

FromJSON (CPreProcessorConfig Maybe) Source # 
Instance details

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

FromJSON (CPreProcessorConfig Option) Source # 
Instance details

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

type Rep (CPreProcessorConfig f) Source # 
Instance details

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

type Rep (CPreProcessorConfig f) = D1 ('MetaData "CPreProcessorConfig" "Language.Haskell.Brittany.Internal.Config.Types" "brittany-0.13.1.1-Jy7sLKH71HuBBZp3S53aXI" 'False) (C1 ('MetaCons "PreProcessorConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ppconf_CPPMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last CPPMode))) :*: S1 ('MetaSel ('Just "_ppconf_hackAroundIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Last Bool)))))

data BrittanyError Source #

Constructors

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

forall ast.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