{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Floskell.Styles ( Style(..), styles ) where
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Text ( Text )
import Floskell.Config
data Style =
Style { Style -> Text
styleName :: !Text
, Style -> Text
styleAuthor :: !Text
, Style -> Text
styleDescription :: !Text
, Style -> Config
styleConfig :: !Config
}
chrisDoneCfg :: Config
chrisDoneCfg :: Config
chrisDoneCfg =
Config
defaultConfig { IndentConfig
cfgIndent :: IndentConfig
cfgIndent :: IndentConfig
cfgIndent, LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout, OpConfig
cfgOp :: OpConfig
cfgOp :: OpConfig
cfgOp, GroupConfig
cfgGroup :: GroupConfig
cfgGroup :: GroupConfig
cfgGroup, OptionConfig
cfgOptions :: OptionConfig
cfgOptions :: OptionConfig
cfgOptions }
where
cfgIndent :: IndentConfig
cfgIndent =
IndentConfig { cfgIndentOnside :: Int
cfgIndentOnside = Int
2
, cfgIndentDeriving :: Int
cfgIndentDeriving = Int
2
, cfgIndentWhere :: Int
cfgIndentWhere = Int
2
, cfgIndentApp :: Indent
cfgIndentApp = Indent
Align
, cfgIndentCase :: Indent
cfgIndentCase = Int -> Indent
IndentBy Int
2
, cfgIndentClass :: Indent
cfgIndentClass = Int -> Indent
IndentBy Int
2
, cfgIndentDo :: Indent
cfgIndentDo = Indent
Align
, cfgIndentIf :: Indent
cfgIndentIf = Int -> Indent
IndentBy Int
3
, cfgIndentLet :: Indent
cfgIndentLet = Indent
Align
, cfgIndentLetBinds :: Indent
cfgIndentLetBinds = Indent
Align
, cfgIndentLetIn :: Indent
cfgIndentLetIn = Indent
Align
, cfgIndentMultiIf :: Indent
cfgIndentMultiIf = Int -> Indent
IndentBy Int
2
, cfgIndentTypesig :: Indent
cfgIndentTypesig = Indent
Align
, cfgIndentWhereBinds :: Indent
cfgIndentWhereBinds = Indent
Align
, cfgIndentExportSpecList :: Indent
cfgIndentExportSpecList = Int -> Indent
IndentBy Int
2
, cfgIndentImportSpecList :: Indent
cfgIndentImportSpecList = Int -> Indent
AlignOrIndentBy Int
7
}
cfgLayout :: LayoutConfig
cfgLayout = LayoutConfig { cfgLayoutApp :: Layout
cfgLayoutApp = Layout
TryOneline
, cfgLayoutConDecls :: Layout
cfgLayoutConDecls = Layout
Vertical
, cfgLayoutDeclaration :: Layout
cfgLayoutDeclaration = Layout
TryOneline
, cfgLayoutExportSpecList :: Layout
cfgLayoutExportSpecList = Layout
TryOneline
, cfgLayoutIf :: Layout
cfgLayoutIf = Layout
Vertical
, cfgLayoutImportSpecList :: Layout
cfgLayoutImportSpecList = Layout
Flex
, cfgLayoutInfixApp :: Layout
cfgLayoutInfixApp = Layout
TryOneline
, cfgLayoutLet :: Layout
cfgLayoutLet = Layout
Vertical
, cfgLayoutListComp :: Layout
cfgLayoutListComp = Layout
Flex
, cfgLayoutRecord :: Layout
cfgLayoutRecord = Layout
Vertical
, cfgLayoutType :: Layout
cfgLayoutType = Layout
TryOneline
}
cfgOp :: OpConfig
cfgOp =
ConfigMap Whitespace -> OpConfig
OpConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault = WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsBefore Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
opWsOverrides
}
opWsOverrides :: [(ConfigMapKey, Whitespace)]
opWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") forall a. Maybe a
Nothing
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsNone Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
".") (forall a. a -> Maybe a
Just LayoutContext
Type)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"=") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"<-") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
":") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False)
]
cfgGroup :: GroupConfig
cfgGroup =
ConfigMap Whitespace -> GroupConfig
GroupConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault =
WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall {a}. [a]
groupWsOverrides
}
groupWsOverrides :: [a]
groupWsOverrides = []
cfgOptions :: OptionConfig
cfgOptions = OptionConfig { cfgOptionSortPragmas :: Bool
cfgOptionSortPragmas = Bool
False
, cfgOptionSplitLanguagePragmas :: Bool
cfgOptionSplitLanguagePragmas = Bool
False
, cfgOptionSortImports :: SortImportsRule
cfgOptionSortImports = SortImportsRule
NoImportSort
, cfgOptionSortImportLists :: Bool
cfgOptionSortImportLists = Bool
False
, cfgOptionAlignSumTypeDecl :: Bool
cfgOptionAlignSumTypeDecl = Bool
True
, cfgOptionFlexibleOneline :: Bool
cfgOptionFlexibleOneline = Bool
False
, cfgOptionPreserveVerticalSpace :: Bool
cfgOptionPreserveVerticalSpace = Bool
False
, cfgOptionDeclNoBlankLines :: Set DeclarationConstruct
cfgOptionDeclNoBlankLines = forall a. Set a
Set.empty
, cfgOptionAlignLetBindsAndInExpr :: Bool
cfgOptionAlignLetBindsAndInExpr = Bool
False
}
cramerCfg :: Config
cramerCfg :: Config
cramerCfg = Config
defaultConfig { AlignConfig
cfgAlign :: AlignConfig
cfgAlign :: AlignConfig
cfgAlign
, IndentConfig
cfgIndent :: IndentConfig
cfgIndent :: IndentConfig
cfgIndent
, LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout
, OpConfig
cfgOp :: OpConfig
cfgOp :: OpConfig
cfgOp
, GroupConfig
cfgGroup :: GroupConfig
cfgGroup :: GroupConfig
cfgGroup
, OptionConfig
cfgOptions :: OptionConfig
cfgOptions :: OptionConfig
cfgOptions
}
where
cfgAlign :: AlignConfig
cfgAlign = AlignConfig { cfgAlignLimits :: (Int, Int)
cfgAlignLimits = (Int
10, Int
25)
, cfgAlignCase :: Bool
cfgAlignCase = Bool
False
, cfgAlignClass :: Bool
cfgAlignClass = Bool
False
, cfgAlignImportModule :: Bool
cfgAlignImportModule = Bool
True
, cfgAlignImportSpec :: Bool
cfgAlignImportSpec = Bool
True
, cfgAlignLetBinds :: Bool
cfgAlignLetBinds = Bool
False
, cfgAlignMatches :: Bool
cfgAlignMatches = Bool
False
, cfgAlignRecordFields :: Bool
cfgAlignRecordFields = Bool
True
, cfgAlignWhere :: Bool
cfgAlignWhere = Bool
False
}
cfgIndent :: IndentConfig
cfgIndent =
IndentConfig { cfgIndentOnside :: Int
cfgIndentOnside = Int
4
, cfgIndentDeriving :: Int
cfgIndentDeriving = Int
4
, cfgIndentWhere :: Int
cfgIndentWhere = Int
2
, cfgIndentApp :: Indent
cfgIndentApp = Indent
Align
, cfgIndentCase :: Indent
cfgIndentCase = Int -> Indent
IndentBy Int
4
, cfgIndentClass :: Indent
cfgIndentClass = Int -> Indent
IndentBy Int
4
, cfgIndentDo :: Indent
cfgIndentDo = Int -> Indent
IndentBy Int
4
, cfgIndentIf :: Indent
cfgIndentIf = Indent
Align
, cfgIndentLet :: Indent
cfgIndentLet = Indent
Align
, cfgIndentLetBinds :: Indent
cfgIndentLetBinds = Indent
Align
, cfgIndentLetIn :: Indent
cfgIndentLetIn = Int -> Indent
IndentBy Int
4
, cfgIndentMultiIf :: Indent
cfgIndentMultiIf = Int -> Indent
IndentBy Int
4
, cfgIndentTypesig :: Indent
cfgIndentTypesig = Indent
Align
, cfgIndentWhereBinds :: Indent
cfgIndentWhereBinds = Int -> Indent
IndentBy Int
2
, cfgIndentExportSpecList :: Indent
cfgIndentExportSpecList = Int -> Indent
IndentBy Int
4
, cfgIndentImportSpecList :: Indent
cfgIndentImportSpecList = Int -> Indent
AlignOrIndentBy Int
17
}
cfgLayout :: LayoutConfig
cfgLayout = LayoutConfig { cfgLayoutApp :: Layout
cfgLayoutApp = Layout
TryOneline
, cfgLayoutConDecls :: Layout
cfgLayoutConDecls = Layout
TryOneline
, cfgLayoutDeclaration :: Layout
cfgLayoutDeclaration = Layout
Flex
, cfgLayoutExportSpecList :: Layout
cfgLayoutExportSpecList = Layout
TryOneline
, cfgLayoutIf :: Layout
cfgLayoutIf = Layout
TryOneline
, cfgLayoutImportSpecList :: Layout
cfgLayoutImportSpecList = Layout
Flex
, cfgLayoutInfixApp :: Layout
cfgLayoutInfixApp = Layout
Flex
, cfgLayoutLet :: Layout
cfgLayoutLet = Layout
TryOneline
, cfgLayoutListComp :: Layout
cfgLayoutListComp = Layout
TryOneline
, cfgLayoutRecord :: Layout
cfgLayoutRecord = Layout
TryOneline
, cfgLayoutType :: Layout
cfgLayoutType = Layout
TryOneline
}
cfgOp :: OpConfig
cfgOp =
ConfigMap Whitespace -> OpConfig
OpConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault = WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsBefore Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
opWsOverrides
}
opWsOverrides :: [(ConfigMapKey, Whitespace)]
opWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsBefore Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") forall a. Maybe a
Nothing
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsNone Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
".") (forall a. a -> Maybe a
Just LayoutContext
Type)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"=") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"$") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"@") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"->") (forall a. a -> Maybe a
Just LayoutContext
Expression)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False
)
]
cfgGroup :: GroupConfig
cfgGroup =
ConfigMap Whitespace -> GroupConfig
GroupConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault =
WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
groupWsOverrides
}
groupWsOverrides :: [(ConfigMapKey, Whitespace)]
groupWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just LayoutContext
Type), WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsAfter Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"$(") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[|") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[d|") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[p|") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[t|") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"(") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsAfter Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"(") (forall a. a -> Maybe a
Just LayoutContext
Other)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"[") (forall a. a -> Maybe a
Just LayoutContext
Type), WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False)
]
cfgOptions :: OptionConfig
cfgOptions =
OptionConfig { cfgOptionSortPragmas :: Bool
cfgOptionSortPragmas = Bool
True
, cfgOptionSplitLanguagePragmas :: Bool
cfgOptionSplitLanguagePragmas = Bool
True
, cfgOptionSortImports :: SortImportsRule
cfgOptionSortImports = SortImportsRule
SortImportsByPrefix
, cfgOptionSortImportLists :: Bool
cfgOptionSortImportLists = Bool
True
, cfgOptionAlignSumTypeDecl :: Bool
cfgOptionAlignSumTypeDecl = Bool
False
, cfgOptionFlexibleOneline :: Bool
cfgOptionFlexibleOneline = Bool
False
, cfgOptionPreserveVerticalSpace :: Bool
cfgOptionPreserveVerticalSpace = Bool
True
, cfgOptionDeclNoBlankLines :: Set DeclarationConstruct
cfgOptionDeclNoBlankLines = forall a. Set a
Set.empty
, cfgOptionAlignLetBindsAndInExpr :: Bool
cfgOptionAlignLetBindsAndInExpr = Bool
False
}
gibianskyCfg :: Config
gibianskyCfg :: Config
gibianskyCfg = Config
defaultConfig { AlignConfig
cfgAlign :: AlignConfig
cfgAlign :: AlignConfig
cfgAlign
, IndentConfig
cfgIndent :: IndentConfig
cfgIndent :: IndentConfig
cfgIndent
, LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout
, OpConfig
cfgOp :: OpConfig
cfgOp :: OpConfig
cfgOp
, GroupConfig
cfgGroup :: GroupConfig
cfgGroup :: GroupConfig
cfgGroup
, OptionConfig
cfgOptions :: OptionConfig
cfgOptions :: OptionConfig
cfgOptions
}
where
cfgAlign :: AlignConfig
cfgAlign = AlignConfig { cfgAlignLimits :: (Int, Int)
cfgAlignLimits = (Int
10, Int
25)
, cfgAlignCase :: Bool
cfgAlignCase = Bool
True
, cfgAlignClass :: Bool
cfgAlignClass = Bool
False
, cfgAlignImportModule :: Bool
cfgAlignImportModule = Bool
True
, cfgAlignImportSpec :: Bool
cfgAlignImportSpec = Bool
False
, cfgAlignLetBinds :: Bool
cfgAlignLetBinds = Bool
False
, cfgAlignMatches :: Bool
cfgAlignMatches = Bool
False
, cfgAlignRecordFields :: Bool
cfgAlignRecordFields = Bool
False
, cfgAlignWhere :: Bool
cfgAlignWhere = Bool
False
}
cfgIndent :: IndentConfig
cfgIndent =
IndentConfig { cfgIndentOnside :: Int
cfgIndentOnside = Int
2
, cfgIndentDeriving :: Int
cfgIndentDeriving = Int
2
, cfgIndentWhere :: Int
cfgIndentWhere = Int
2
, cfgIndentApp :: Indent
cfgIndentApp = Int -> Indent
IndentBy Int
2
, cfgIndentCase :: Indent
cfgIndentCase = Int -> Indent
IndentBy Int
2
, cfgIndentClass :: Indent
cfgIndentClass = Int -> Indent
IndentBy Int
2
, cfgIndentDo :: Indent
cfgIndentDo = Int -> Indent
IndentBy Int
2
, cfgIndentIf :: Indent
cfgIndentIf = Indent
Align
, cfgIndentLet :: Indent
cfgIndentLet = Indent
Align
, cfgIndentLetBinds :: Indent
cfgIndentLetBinds = Indent
Align
, cfgIndentLetIn :: Indent
cfgIndentLetIn = Indent
Align
, cfgIndentMultiIf :: Indent
cfgIndentMultiIf = Int -> Indent
IndentBy Int
2
, cfgIndentTypesig :: Indent
cfgIndentTypesig = Indent
Align
, cfgIndentWhereBinds :: Indent
cfgIndentWhereBinds = Int -> Indent
IndentBy Int
2
, cfgIndentExportSpecList :: Indent
cfgIndentExportSpecList = Int -> Indent
IndentBy Int
4
, cfgIndentImportSpecList :: Indent
cfgIndentImportSpecList = Indent
Align
}
cfgLayout :: LayoutConfig
cfgLayout = LayoutConfig { cfgLayoutApp :: Layout
cfgLayoutApp = Layout
TryOneline
, cfgLayoutConDecls :: Layout
cfgLayoutConDecls = Layout
Vertical
, cfgLayoutDeclaration :: Layout
cfgLayoutDeclaration = Layout
Flex
, cfgLayoutExportSpecList :: Layout
cfgLayoutExportSpecList = Layout
TryOneline
, cfgLayoutIf :: Layout
cfgLayoutIf = Layout
Vertical
, cfgLayoutImportSpecList :: Layout
cfgLayoutImportSpecList = Layout
Flex
, cfgLayoutInfixApp :: Layout
cfgLayoutInfixApp = Layout
TryOneline
, cfgLayoutLet :: Layout
cfgLayoutLet = Layout
Vertical
, cfgLayoutListComp :: Layout
cfgLayoutListComp = Layout
TryOneline
, cfgLayoutRecord :: Layout
cfgLayoutRecord = Layout
TryOneline
, cfgLayoutType :: Layout
cfgLayoutType = Layout
TryOneline
}
cfgOp :: OpConfig
cfgOp =
ConfigMap Whitespace -> OpConfig
OpConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault = WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsBefore Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
opWsOverrides
}
opWsOverrides :: [(ConfigMapKey, Whitespace)]
opWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsBefore Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") forall a. Maybe a
Nothing
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsNone Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
".") (forall a. a -> Maybe a
Just LayoutContext
Type)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"=") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
":") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False)
]
cfgGroup :: GroupConfig
cfgGroup =
ConfigMap Whitespace -> GroupConfig
GroupConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault =
WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
groupWsOverrides
}
groupWsOverrides :: [(ConfigMapKey, Whitespace)]
groupWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"{") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False) ]
cfgOptions :: OptionConfig
cfgOptions = OptionConfig { cfgOptionSortPragmas :: Bool
cfgOptionSortPragmas = Bool
False
, cfgOptionSplitLanguagePragmas :: Bool
cfgOptionSplitLanguagePragmas = Bool
False
, cfgOptionSortImports :: SortImportsRule
cfgOptionSortImports = SortImportsRule
NoImportSort
, cfgOptionSortImportLists :: Bool
cfgOptionSortImportLists = Bool
False
, cfgOptionAlignSumTypeDecl :: Bool
cfgOptionAlignSumTypeDecl = Bool
False
, cfgOptionFlexibleOneline :: Bool
cfgOptionFlexibleOneline = Bool
False
, cfgOptionPreserveVerticalSpace :: Bool
cfgOptionPreserveVerticalSpace = Bool
False
, cfgOptionDeclNoBlankLines :: Set DeclarationConstruct
cfgOptionDeclNoBlankLines = forall a. Set a
Set.empty
, cfgOptionAlignLetBindsAndInExpr :: Bool
cfgOptionAlignLetBindsAndInExpr = Bool
False
}
johanTibellCfg :: Config
johanTibellCfg :: Config
johanTibellCfg =
Config
defaultConfig { IndentConfig
cfgIndent :: IndentConfig
cfgIndent :: IndentConfig
cfgIndent, LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout :: LayoutConfig
cfgLayout, OpConfig
cfgOp :: OpConfig
cfgOp :: OpConfig
cfgOp, GroupConfig
cfgGroup :: GroupConfig
cfgGroup :: GroupConfig
cfgGroup, OptionConfig
cfgOptions :: OptionConfig
cfgOptions :: OptionConfig
cfgOptions }
where
cfgIndent :: IndentConfig
cfgIndent =
IndentConfig { cfgIndentOnside :: Int
cfgIndentOnside = Int
4
, cfgIndentDeriving :: Int
cfgIndentDeriving = Int
4
, cfgIndentWhere :: Int
cfgIndentWhere = Int
2
, cfgIndentApp :: Indent
cfgIndentApp = Int -> Indent
IndentBy Int
4
, cfgIndentCase :: Indent
cfgIndentCase = Int -> Indent
IndentBy Int
4
, cfgIndentClass :: Indent
cfgIndentClass = Int -> Indent
IndentBy Int
4
, cfgIndentDo :: Indent
cfgIndentDo = Int -> Indent
IndentBy Int
4
, cfgIndentIf :: Indent
cfgIndentIf = Int -> Indent
IndentBy Int
4
, cfgIndentLet :: Indent
cfgIndentLet = Indent
Align
, cfgIndentLetBinds :: Indent
cfgIndentLetBinds = Indent
Align
, cfgIndentLetIn :: Indent
cfgIndentLetIn = Indent
Align
, cfgIndentMultiIf :: Indent
cfgIndentMultiIf = Int -> Indent
IndentBy Int
2
, cfgIndentTypesig :: Indent
cfgIndentTypesig = Indent
Align
, cfgIndentWhereBinds :: Indent
cfgIndentWhereBinds = Int -> Indent
IndentBy Int
2
, cfgIndentExportSpecList :: Indent
cfgIndentExportSpecList = Int -> Indent
IndentBy Int
2
, cfgIndentImportSpecList :: Indent
cfgIndentImportSpecList = Int -> Indent
AlignOrIndentBy Int
7
}
cfgLayout :: LayoutConfig
cfgLayout = LayoutConfig { cfgLayoutApp :: Layout
cfgLayoutApp = Layout
TryOneline
, cfgLayoutConDecls :: Layout
cfgLayoutConDecls = Layout
Vertical
, cfgLayoutDeclaration :: Layout
cfgLayoutDeclaration = Layout
TryOneline
, cfgLayoutExportSpecList :: Layout
cfgLayoutExportSpecList = Layout
TryOneline
, cfgLayoutIf :: Layout
cfgLayoutIf = Layout
Vertical
, cfgLayoutImportSpecList :: Layout
cfgLayoutImportSpecList = Layout
Flex
, cfgLayoutInfixApp :: Layout
cfgLayoutInfixApp = Layout
TryOneline
, cfgLayoutLet :: Layout
cfgLayoutLet = Layout
Vertical
, cfgLayoutListComp :: Layout
cfgLayoutListComp = Layout
Flex
, cfgLayoutRecord :: Layout
cfgLayoutRecord = Layout
Vertical
, cfgLayoutType :: Layout
cfgLayoutType = Layout
TryOneline
}
cfgOp :: OpConfig
cfgOp =
ConfigMap Whitespace -> OpConfig
OpConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault = WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsBefore Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
opWsOverrides
}
opWsOverrides :: [(ConfigMapKey, Whitespace)]
opWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsBefore Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") forall a. Maybe a
Nothing
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
True
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
".") (forall a. a -> Maybe a
Just LayoutContext
Type)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
)
, (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"=") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
":") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
",") (forall a. a -> Maybe a
Just LayoutContext
Other)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsBefore Bool
False
)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"record") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
)
]
cfgGroup :: GroupConfig
cfgGroup =
ConfigMap Whitespace -> GroupConfig
GroupConfig ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault =
WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False
, cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
groupWsOverrides
}
groupWsOverrides :: [(ConfigMapKey, Whitespace)]
groupWsOverrides =
[ (Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"{") forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False)
, ( Maybe Text -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (forall a. a -> Maybe a
Just Text
"{") (forall a. a -> Maybe a
Just LayoutContext
Pattern)
, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsNone WsLoc
WsNone Bool
False
)
]
cfgOptions :: OptionConfig
cfgOptions = OptionConfig { cfgOptionSortPragmas :: Bool
cfgOptionSortPragmas = Bool
False
, cfgOptionSplitLanguagePragmas :: Bool
cfgOptionSplitLanguagePragmas = Bool
False
, cfgOptionSortImports :: SortImportsRule
cfgOptionSortImports = SortImportsRule
NoImportSort
, cfgOptionSortImportLists :: Bool
cfgOptionSortImportLists = Bool
False
, cfgOptionAlignSumTypeDecl :: Bool
cfgOptionAlignSumTypeDecl = Bool
True
, cfgOptionFlexibleOneline :: Bool
cfgOptionFlexibleOneline = Bool
True
, cfgOptionPreserveVerticalSpace :: Bool
cfgOptionPreserveVerticalSpace = Bool
False
, cfgOptionDeclNoBlankLines :: Set DeclarationConstruct
cfgOptionDeclNoBlankLines = forall a. Set a
Set.empty
, cfgOptionAlignLetBindsAndInExpr :: Bool
cfgOptionAlignLetBindsAndInExpr = Bool
False
}
base :: Style
base :: Style
base = Style { styleName :: Text
styleName = Text
"base"
, styleAuthor :: Text
styleAuthor = Text
"Enno Cramer"
, styleDescription :: Text
styleDescription = Text
"Configurable formatting style"
, styleConfig :: Config
styleConfig = Config
defaultConfig
}
chrisDone :: Style
chrisDone :: Style
chrisDone = Style { styleName :: Text
styleName = Text
"chris-done"
, styleAuthor :: Text
styleAuthor = Text
"Chris Done"
, styleDescription :: Text
styleDescription = Text
"Chris Done's style"
, styleConfig :: Config
styleConfig = Config
chrisDoneCfg
}
cramer :: Style
cramer :: Style
cramer = Style { styleName :: Text
styleName = Text
"cramer"
, styleAuthor :: Text
styleAuthor = Text
"Enno Cramer"
, styleDescription :: Text
styleDescription = Text
"Enno Cramer's style"
, styleConfig :: Config
styleConfig = Config
cramerCfg
}
gibiansky :: Style
gibiansky :: Style
gibiansky = Style { styleName :: Text
styleName = Text
"gibiansky"
, styleAuthor :: Text
styleAuthor = Text
"Andrew Gibiansky"
, styleDescription :: Text
styleDescription = Text
"Andrew Gibiansky's style"
, styleConfig :: Config
styleConfig = Config
gibianskyCfg
}
johanTibell :: Style
johanTibell :: Style
johanTibell = Style { styleName :: Text
styleName = Text
"johan-tibell"
, styleAuthor :: Text
styleAuthor = Text
"Johan Tibell"
, styleDescription :: Text
styleDescription = Text
"Johan Tibell's style"
, styleConfig :: Config
styleConfig = Config
johanTibellCfg
}
styles :: [Style]
styles :: [Style]
styles = [ Style
base, Style
chrisDone, Style
johanTibell, Style
gibiansky, Style
cramer ]