floskell-0.10.4: A flexible Haskell source code pretty printer

Safe HaskellNone
LanguageHaskell2010

Floskell.Config

Documentation

data Indent Source #

Instances
Eq Indent Source # 
Instance details

Defined in Floskell.Config

Methods

(==) :: Indent -> Indent -> Bool #

(/=) :: Indent -> Indent -> Bool #

Ord Indent Source # 
Instance details

Defined in Floskell.Config

Show Indent Source # 
Instance details

Defined in Floskell.Config

Generic Indent Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Indent :: Type -> Type #

Methods

from :: Indent -> Rep Indent x #

to :: Rep Indent x -> Indent #

ToJSON Indent Source # 
Instance details

Defined in Floskell.Config

FromJSON Indent Source # 
Instance details

Defined in Floskell.Config

type Rep Indent Source # 
Instance details

Defined in Floskell.Config

type Rep Indent = D1 (MetaData "Indent" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "Align" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IndentBy" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "AlignOrIndentBy" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

data LayoutContext Source #

Instances
Bounded LayoutContext Source # 
Instance details

Defined in Floskell.Config

Enum LayoutContext Source # 
Instance details

Defined in Floskell.Config

Eq LayoutContext Source # 
Instance details

Defined in Floskell.Config

Ord LayoutContext Source # 
Instance details

Defined in Floskell.Config

Show LayoutContext Source # 
Instance details

Defined in Floskell.Config

Generic LayoutContext Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep LayoutContext :: Type -> Type #

ToJSON LayoutContext Source # 
Instance details

Defined in Floskell.Config

FromJSON LayoutContext Source # 
Instance details

Defined in Floskell.Config

type Rep LayoutContext Source # 
Instance details

Defined in Floskell.Config

type Rep LayoutContext = D1 (MetaData "LayoutContext" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) ((C1 (MetaCons "Declaration" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Type" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Pattern" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Expression" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Other" PrefixI False) (U1 :: Type -> Type))))

data Location Source #

Constructors

Before 
After 
Instances
Bounded Location Source # 
Instance details

Defined in Floskell.Config

Enum Location Source # 
Instance details

Defined in Floskell.Config

Eq Location Source # 
Instance details

Defined in Floskell.Config

Ord Location Source # 
Instance details

Defined in Floskell.Config

Show Location Source # 
Instance details

Defined in Floskell.Config

Generic Location Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

type Rep Location Source # 
Instance details

Defined in Floskell.Config

type Rep Location = D1 (MetaData "Location" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "Before" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "After" PrefixI False) (U1 :: Type -> Type))

data WsLoc Source #

Constructors

WsNone 
WsBefore 
WsAfter 
WsBoth 
Instances
Bounded WsLoc Source # 
Instance details

Defined in Floskell.Config

Enum WsLoc Source # 
Instance details

Defined in Floskell.Config

Eq WsLoc Source # 
Instance details

Defined in Floskell.Config

Methods

(==) :: WsLoc -> WsLoc -> Bool #

(/=) :: WsLoc -> WsLoc -> Bool #

Ord WsLoc Source # 
Instance details

Defined in Floskell.Config

Methods

compare :: WsLoc -> WsLoc -> Ordering #

(<) :: WsLoc -> WsLoc -> Bool #

(<=) :: WsLoc -> WsLoc -> Bool #

(>) :: WsLoc -> WsLoc -> Bool #

(>=) :: WsLoc -> WsLoc -> Bool #

max :: WsLoc -> WsLoc -> WsLoc #

min :: WsLoc -> WsLoc -> WsLoc #

Show WsLoc Source # 
Instance details

Defined in Floskell.Config

Methods

showsPrec :: Int -> WsLoc -> ShowS #

show :: WsLoc -> String #

showList :: [WsLoc] -> ShowS #

Generic WsLoc Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep WsLoc :: Type -> Type #

Methods

from :: WsLoc -> Rep WsLoc x #

to :: Rep WsLoc x -> WsLoc #

ToJSON WsLoc Source # 
Instance details

Defined in Floskell.Config

FromJSON WsLoc Source # 
Instance details

Defined in Floskell.Config

type Rep WsLoc Source # 
Instance details

Defined in Floskell.Config

type Rep WsLoc = D1 (MetaData "WsLoc" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) ((C1 (MetaCons "WsNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WsBefore" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WsAfter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WsBoth" PrefixI False) (U1 :: Type -> Type)))

data Whitespace Source #

Constructors

Whitespace 
Instances
Show Whitespace Source # 
Instance details

Defined in Floskell.Config

Generic Whitespace Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Whitespace :: Type -> Type #

ToJSON Whitespace Source # 
Instance details

Defined in Floskell.Config

FromJSON Whitespace Source # 
Instance details

Defined in Floskell.Config

type Rep Whitespace Source # 
Instance details

Defined in Floskell.Config

type Rep Whitespace = D1 (MetaData "Whitespace" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "Whitespace" PrefixI True) (S1 (MetaSel (Just "wsSpaces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WsLoc) :*: (S1 (MetaSel (Just "wsLinebreaks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WsLoc) :*: S1 (MetaSel (Just "wsForceLinebreak") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

data Layout Source #

Constructors

Flex 
Vertical 
TryOneline 
Instances
Bounded Layout Source # 
Instance details

Defined in Floskell.Config

Enum Layout Source # 
Instance details

Defined in Floskell.Config

Eq Layout Source # 
Instance details

Defined in Floskell.Config

Methods

(==) :: Layout -> Layout -> Bool #

(/=) :: Layout -> Layout -> Bool #

Ord Layout Source # 
Instance details

Defined in Floskell.Config

Show Layout Source # 
Instance details

Defined in Floskell.Config

Generic Layout Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Layout :: Type -> Type #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

ToJSON Layout Source # 
Instance details

Defined in Floskell.Config

FromJSON Layout Source # 
Instance details

Defined in Floskell.Config

type Rep Layout Source # 
Instance details

Defined in Floskell.Config

type Rep Layout = D1 (MetaData "Layout" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "Flex" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Vertical" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TryOneline" PrefixI False) (U1 :: Type -> Type)))

data ConfigMap a Source #

Constructors

ConfigMap 
Instances
Generic (ConfigMap a) Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep (ConfigMap a) :: Type -> Type #

Methods

from :: ConfigMap a -> Rep (ConfigMap a) x #

to :: Rep (ConfigMap a) x -> ConfigMap a #

ToJSON a => ToJSON (ConfigMap a) Source # 
Instance details

Defined in Floskell.Config

FromJSON a => FromJSON (ConfigMap a) Source # 
Instance details

Defined in Floskell.Config

type Rep (ConfigMap a) Source # 
Instance details

Defined in Floskell.Config

type Rep (ConfigMap a) = D1 (MetaData "ConfigMap" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "ConfigMap" PrefixI True) (S1 (MetaSel (Just "cfgMapDefault") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "cfgMapOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map ConfigMapKey a))))

data PenaltyConfig Source #

Instances
Generic PenaltyConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep PenaltyConfig :: Type -> Type #

ToJSON PenaltyConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON PenaltyConfig Source # 
Instance details

Defined in Floskell.Config

Default PenaltyConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: PenaltyConfig #

type Rep PenaltyConfig Source # 
Instance details

Defined in Floskell.Config

type Rep PenaltyConfig = D1 (MetaData "PenaltyConfig" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "PenaltyConfig" PrefixI True) ((S1 (MetaSel (Just "penaltyMaxLineLength") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "penaltyLinebreak") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "penaltyIndent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "penaltyOverfull") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "penaltyOverfullOnce") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))

data AlignConfig Source #

Instances
Generic AlignConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep AlignConfig :: Type -> Type #

ToJSON AlignConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON AlignConfig Source # 
Instance details

Defined in Floskell.Config

Default AlignConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: AlignConfig #

type Rep AlignConfig Source # 
Instance details

Defined in Floskell.Config

data IndentConfig Source #

Instances
Generic IndentConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep IndentConfig :: Type -> Type #

ToJSON IndentConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON IndentConfig Source # 
Instance details

Defined in Floskell.Config

Default IndentConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: IndentConfig #

type Rep IndentConfig Source # 
Instance details

Defined in Floskell.Config

type Rep IndentConfig = D1 (MetaData "IndentConfig" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "IndentConfig" PrefixI True) ((((S1 (MetaSel (Just "cfgIndentOnside") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "cfgIndentDeriving") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "cfgIndentWhere") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "cfgIndentApp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent))) :*: ((S1 (MetaSel (Just "cfgIndentCase") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent)) :*: (S1 (MetaSel (Just "cfgIndentDo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentExportSpecList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent)))) :*: (((S1 (MetaSel (Just "cfgIndentIf") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentImportSpecList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent)) :*: (S1 (MetaSel (Just "cfgIndentLet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentLetBinds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent))) :*: ((S1 (MetaSel (Just "cfgIndentLetIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentMultiIf") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent)) :*: (S1 (MetaSel (Just "cfgIndentTypesig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent) :*: S1 (MetaSel (Just "cfgIndentWhereBinds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Indent))))))

data LayoutConfig Source #

Instances
Generic LayoutConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep LayoutConfig :: Type -> Type #

ToJSON LayoutConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON LayoutConfig Source # 
Instance details

Defined in Floskell.Config

Default LayoutConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: LayoutConfig #

type Rep LayoutConfig Source # 
Instance details

Defined in Floskell.Config

newtype OpConfig Source #

Constructors

OpConfig 
Instances
Generic OpConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep OpConfig :: Type -> Type #

Methods

from :: OpConfig -> Rep OpConfig x #

to :: Rep OpConfig x -> OpConfig #

ToJSON OpConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON OpConfig Source # 
Instance details

Defined in Floskell.Config

Default OpConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: OpConfig #

type Rep OpConfig Source # 
Instance details

Defined in Floskell.Config

type Rep OpConfig = D1 (MetaData "OpConfig" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" True) (C1 (MetaCons "OpConfig" PrefixI True) (S1 (MetaSel (Just "unOpConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConfigMap Whitespace))))

newtype GroupConfig Source #

Instances
Generic GroupConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep GroupConfig :: Type -> Type #

ToJSON GroupConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON GroupConfig Source # 
Instance details

Defined in Floskell.Config

Default GroupConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: GroupConfig #

type Rep GroupConfig Source # 
Instance details

Defined in Floskell.Config

type Rep GroupConfig = D1 (MetaData "GroupConfig" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" True) (C1 (MetaCons "GroupConfig" PrefixI True) (S1 (MetaSel (Just "unGroupConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConfigMap Whitespace))))

data ImportsGroupOrder Source #

Instances
Generic ImportsGroupOrder Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep ImportsGroupOrder :: Type -> Type #

ToJSON ImportsGroupOrder Source # 
Instance details

Defined in Floskell.Config

FromJSON ImportsGroupOrder Source # 
Instance details

Defined in Floskell.Config

type Rep ImportsGroupOrder Source # 
Instance details

Defined in Floskell.Config

type Rep ImportsGroupOrder = D1 (MetaData "ImportsGroupOrder" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "ImportsGroupKeep" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ImportsGroupSorted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ImportsGroupGrouped" PrefixI False) (U1 :: Type -> Type)))

data ImportsGroup Source #

Instances
Generic ImportsGroup Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep ImportsGroup :: Type -> Type #

ToJSON ImportsGroup Source # 
Instance details

Defined in Floskell.Config

FromJSON ImportsGroup Source # 
Instance details

Defined in Floskell.Config

type Rep ImportsGroup Source # 
Instance details

Defined in Floskell.Config

type Rep ImportsGroup = D1 (MetaData "ImportsGroup" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "ImportsGroup" PrefixI True) (S1 (MetaSel (Just "importsPrefixes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [String]) :*: S1 (MetaSel (Just "importsOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ImportsGroupOrder)))

data DeclarationConstruct Source #

Instances
Eq DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

Ord DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

Generic DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep DeclarationConstruct :: Type -> Type #

ToJSON DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

FromJSON DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

type Rep DeclarationConstruct Source # 
Instance details

Defined in Floskell.Config

type Rep DeclarationConstruct = D1 (MetaData "DeclarationConstruct" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) ((C1 (MetaCons "DeclModule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeclClass" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DeclInstance" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeclWhere" PrefixI False) (U1 :: Type -> Type)))

data OptionConfig Source #

Instances
Generic OptionConfig Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep OptionConfig :: Type -> Type #

ToJSON OptionConfig Source # 
Instance details

Defined in Floskell.Config

FromJSON OptionConfig Source # 
Instance details

Defined in Floskell.Config

Default OptionConfig Source # 
Instance details

Defined in Floskell.Config

Methods

def :: OptionConfig #

type Rep OptionConfig Source # 
Instance details

Defined in Floskell.Config

type Rep OptionConfig = D1 (MetaData "OptionConfig" "Floskell.Config" "floskell-0.10.4-61DVe506XlqJmKSQSzQ9Hv" False) (C1 (MetaCons "OptionConfig" PrefixI True) (((S1 (MetaSel (Just "cfgOptionSortPragmas") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "cfgOptionSplitLanguagePragmas") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) :*: (S1 (MetaSel (Just "cfgOptionSortImports") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SortImportsRule) :*: S1 (MetaSel (Just "cfgOptionSortImportLists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) :*: ((S1 (MetaSel (Just "cfgOptionAlignSumTypeDecl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "cfgOptionFlexibleOneline") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) :*: (S1 (MetaSel (Just "cfgOptionPreserveVerticalSpace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "cfgOptionDeclNoBlankLines") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set DeclarationConstruct))))))

data Config Source #

Instances
Generic Config Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

ToJSON Config Source # 
Instance details

Defined in Floskell.Config

FromJSON Config Source # 
Instance details

Defined in Floskell.Config

Default Config Source # 
Instance details

Defined in Floskell.Config

Methods

def :: Config #

type Rep Config Source # 
Instance details

Defined in Floskell.Config