{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Floskell.Config
    ( Indent(..)
    , LayoutContext(..)
    , Location(..)
    , WsLoc(..)
    , Whitespace(..)
    , Layout(..)
    , ConfigMapKey(..)
    , ConfigMap(..)
    , PenaltyConfig(..)
    , AlignConfig(..)
    , IndentConfig(..)
    , LayoutConfig(..)
    , OpConfig(..)
    , GroupConfig(..)
    , ImportsGroupOrder(..)
    , ImportsGroup(..)
    , SortImportsRule(..)
    , DeclarationConstruct(..)
    , OptionConfig(..)
    , Config(..)
    , defaultConfig
    , safeConfig
    , cfgMapFind
    , cfgOpWs
    , cfgGroupWs
    , inWs
    , wsSpace
    , wsLinebreak
    ) where

import           Data.Aeson
                 ( FromJSON(..), ToJSON(..), genericParseJSON, genericToJSON )
import qualified Data.Aeson         as JSON
import           Data.Aeson.Types   as JSON
                 ( Options(..), camelTo2, typeMismatch )
import           Data.ByteString    ( ByteString )
import           Data.Default       ( Default(..) )
import qualified Data.HashMap.Lazy  as HashMap
import           Data.Map.Strict    ( Map )
import qualified Data.Map.Strict    as Map
import           Data.Set           ( Set )
import qualified Data.Set           as Set
import qualified Data.Text          as T
import qualified Data.Text.Encoding as T ( decodeUtf8, encodeUtf8 )

import           GHC.Generics

data Indent = Align | IndentBy !Int | AlignOrIndentBy !Int
    deriving ( Indent -> Indent -> Bool
(Indent -> Indent -> Bool)
-> (Indent -> Indent -> Bool) -> Eq Indent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Indent -> Indent -> Bool
$c/= :: Indent -> Indent -> Bool
== :: Indent -> Indent -> Bool
$c== :: Indent -> Indent -> Bool
Eq, Eq Indent
Eq Indent
-> (Indent -> Indent -> Ordering)
-> (Indent -> Indent -> Bool)
-> (Indent -> Indent -> Bool)
-> (Indent -> Indent -> Bool)
-> (Indent -> Indent -> Bool)
-> (Indent -> Indent -> Indent)
-> (Indent -> Indent -> Indent)
-> Ord Indent
Indent -> Indent -> Bool
Indent -> Indent -> Ordering
Indent -> Indent -> Indent
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Indent -> Indent -> Indent
$cmin :: Indent -> Indent -> Indent
max :: Indent -> Indent -> Indent
$cmax :: Indent -> Indent -> Indent
>= :: Indent -> Indent -> Bool
$c>= :: Indent -> Indent -> Bool
> :: Indent -> Indent -> Bool
$c> :: Indent -> Indent -> Bool
<= :: Indent -> Indent -> Bool
$c<= :: Indent -> Indent -> Bool
< :: Indent -> Indent -> Bool
$c< :: Indent -> Indent -> Bool
compare :: Indent -> Indent -> Ordering
$ccompare :: Indent -> Indent -> Ordering
$cp1Ord :: Eq Indent
Ord, Int -> Indent -> ShowS
[Indent] -> ShowS
Indent -> String
(Int -> Indent -> ShowS)
-> (Indent -> String) -> ([Indent] -> ShowS) -> Show Indent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Indent] -> ShowS
$cshowList :: [Indent] -> ShowS
show :: Indent -> String
$cshow :: Indent -> String
showsPrec :: Int -> Indent -> ShowS
$cshowsPrec :: Int -> Indent -> ShowS
Show, (forall x. Indent -> Rep Indent x)
-> (forall x. Rep Indent x -> Indent) -> Generic Indent
forall x. Rep Indent x -> Indent
forall x. Indent -> Rep Indent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Indent x -> Indent
$cfrom :: forall x. Indent -> Rep Indent x
Generic )

data LayoutContext = Declaration | Type | Pattern | Expression | Other
    deriving ( LayoutContext -> LayoutContext -> Bool
(LayoutContext -> LayoutContext -> Bool)
-> (LayoutContext -> LayoutContext -> Bool) -> Eq LayoutContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutContext -> LayoutContext -> Bool
$c/= :: LayoutContext -> LayoutContext -> Bool
== :: LayoutContext -> LayoutContext -> Bool
$c== :: LayoutContext -> LayoutContext -> Bool
Eq, Eq LayoutContext
Eq LayoutContext
-> (LayoutContext -> LayoutContext -> Ordering)
-> (LayoutContext -> LayoutContext -> Bool)
-> (LayoutContext -> LayoutContext -> Bool)
-> (LayoutContext -> LayoutContext -> Bool)
-> (LayoutContext -> LayoutContext -> Bool)
-> (LayoutContext -> LayoutContext -> LayoutContext)
-> (LayoutContext -> LayoutContext -> LayoutContext)
-> Ord LayoutContext
LayoutContext -> LayoutContext -> Bool
LayoutContext -> LayoutContext -> Ordering
LayoutContext -> LayoutContext -> LayoutContext
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LayoutContext -> LayoutContext -> LayoutContext
$cmin :: LayoutContext -> LayoutContext -> LayoutContext
max :: LayoutContext -> LayoutContext -> LayoutContext
$cmax :: LayoutContext -> LayoutContext -> LayoutContext
>= :: LayoutContext -> LayoutContext -> Bool
$c>= :: LayoutContext -> LayoutContext -> Bool
> :: LayoutContext -> LayoutContext -> Bool
$c> :: LayoutContext -> LayoutContext -> Bool
<= :: LayoutContext -> LayoutContext -> Bool
$c<= :: LayoutContext -> LayoutContext -> Bool
< :: LayoutContext -> LayoutContext -> Bool
$c< :: LayoutContext -> LayoutContext -> Bool
compare :: LayoutContext -> LayoutContext -> Ordering
$ccompare :: LayoutContext -> LayoutContext -> Ordering
$cp1Ord :: Eq LayoutContext
Ord, LayoutContext
LayoutContext -> LayoutContext -> Bounded LayoutContext
forall a. a -> a -> Bounded a
maxBound :: LayoutContext
$cmaxBound :: LayoutContext
minBound :: LayoutContext
$cminBound :: LayoutContext
Bounded, Int -> LayoutContext
LayoutContext -> Int
LayoutContext -> [LayoutContext]
LayoutContext -> LayoutContext
LayoutContext -> LayoutContext -> [LayoutContext]
LayoutContext -> LayoutContext -> LayoutContext -> [LayoutContext]
(LayoutContext -> LayoutContext)
-> (LayoutContext -> LayoutContext)
-> (Int -> LayoutContext)
-> (LayoutContext -> Int)
-> (LayoutContext -> [LayoutContext])
-> (LayoutContext -> LayoutContext -> [LayoutContext])
-> (LayoutContext -> LayoutContext -> [LayoutContext])
-> (LayoutContext
    -> LayoutContext -> LayoutContext -> [LayoutContext])
-> Enum LayoutContext
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LayoutContext -> LayoutContext -> LayoutContext -> [LayoutContext]
$cenumFromThenTo :: LayoutContext -> LayoutContext -> LayoutContext -> [LayoutContext]
enumFromTo :: LayoutContext -> LayoutContext -> [LayoutContext]
$cenumFromTo :: LayoutContext -> LayoutContext -> [LayoutContext]
enumFromThen :: LayoutContext -> LayoutContext -> [LayoutContext]
$cenumFromThen :: LayoutContext -> LayoutContext -> [LayoutContext]
enumFrom :: LayoutContext -> [LayoutContext]
$cenumFrom :: LayoutContext -> [LayoutContext]
fromEnum :: LayoutContext -> Int
$cfromEnum :: LayoutContext -> Int
toEnum :: Int -> LayoutContext
$ctoEnum :: Int -> LayoutContext
pred :: LayoutContext -> LayoutContext
$cpred :: LayoutContext -> LayoutContext
succ :: LayoutContext -> LayoutContext
$csucc :: LayoutContext -> LayoutContext
Enum, Int -> LayoutContext -> ShowS
[LayoutContext] -> ShowS
LayoutContext -> String
(Int -> LayoutContext -> ShowS)
-> (LayoutContext -> String)
-> ([LayoutContext] -> ShowS)
-> Show LayoutContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LayoutContext] -> ShowS
$cshowList :: [LayoutContext] -> ShowS
show :: LayoutContext -> String
$cshow :: LayoutContext -> String
showsPrec :: Int -> LayoutContext -> ShowS
$cshowsPrec :: Int -> LayoutContext -> ShowS
Show, (forall x. LayoutContext -> Rep LayoutContext x)
-> (forall x. Rep LayoutContext x -> LayoutContext)
-> Generic LayoutContext
forall x. Rep LayoutContext x -> LayoutContext
forall x. LayoutContext -> Rep LayoutContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LayoutContext x -> LayoutContext
$cfrom :: forall x. LayoutContext -> Rep LayoutContext x
Generic )

data Location = Before | After
    deriving ( Location -> Location -> Bool
(Location -> Location -> Bool)
-> (Location -> Location -> Bool) -> Eq Location
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Location -> Location -> Bool
$c/= :: Location -> Location -> Bool
== :: Location -> Location -> Bool
$c== :: Location -> Location -> Bool
Eq, Eq Location
Eq Location
-> (Location -> Location -> Ordering)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Location)
-> (Location -> Location -> Location)
-> Ord Location
Location -> Location -> Bool
Location -> Location -> Ordering
Location -> Location -> Location
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Location -> Location -> Location
$cmin :: Location -> Location -> Location
max :: Location -> Location -> Location
$cmax :: Location -> Location -> Location
>= :: Location -> Location -> Bool
$c>= :: Location -> Location -> Bool
> :: Location -> Location -> Bool
$c> :: Location -> Location -> Bool
<= :: Location -> Location -> Bool
$c<= :: Location -> Location -> Bool
< :: Location -> Location -> Bool
$c< :: Location -> Location -> Bool
compare :: Location -> Location -> Ordering
$ccompare :: Location -> Location -> Ordering
$cp1Ord :: Eq Location
Ord, Location
Location -> Location -> Bounded Location
forall a. a -> a -> Bounded a
maxBound :: Location
$cmaxBound :: Location
minBound :: Location
$cminBound :: Location
Bounded, Int -> Location
Location -> Int
Location -> [Location]
Location -> Location
Location -> Location -> [Location]
Location -> Location -> Location -> [Location]
(Location -> Location)
-> (Location -> Location)
-> (Int -> Location)
-> (Location -> Int)
-> (Location -> [Location])
-> (Location -> Location -> [Location])
-> (Location -> Location -> [Location])
-> (Location -> Location -> Location -> [Location])
-> Enum Location
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Location -> Location -> Location -> [Location]
$cenumFromThenTo :: Location -> Location -> Location -> [Location]
enumFromTo :: Location -> Location -> [Location]
$cenumFromTo :: Location -> Location -> [Location]
enumFromThen :: Location -> Location -> [Location]
$cenumFromThen :: Location -> Location -> [Location]
enumFrom :: Location -> [Location]
$cenumFrom :: Location -> [Location]
fromEnum :: Location -> Int
$cfromEnum :: Location -> Int
toEnum :: Int -> Location
$ctoEnum :: Int -> Location
pred :: Location -> Location
$cpred :: Location -> Location
succ :: Location -> Location
$csucc :: Location -> Location
Enum, Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Location] -> ShowS
$cshowList :: [Location] -> ShowS
show :: Location -> String
$cshow :: Location -> String
showsPrec :: Int -> Location -> ShowS
$cshowsPrec :: Int -> Location -> ShowS
Show, (forall x. Location -> Rep Location x)
-> (forall x. Rep Location x -> Location) -> Generic Location
forall x. Rep Location x -> Location
forall x. Location -> Rep Location x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Location x -> Location
$cfrom :: forall x. Location -> Rep Location x
Generic )

data WsLoc = WsNone | WsBefore | WsAfter | WsBoth
    deriving ( WsLoc -> WsLoc -> Bool
(WsLoc -> WsLoc -> Bool) -> (WsLoc -> WsLoc -> Bool) -> Eq WsLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WsLoc -> WsLoc -> Bool
$c/= :: WsLoc -> WsLoc -> Bool
== :: WsLoc -> WsLoc -> Bool
$c== :: WsLoc -> WsLoc -> Bool
Eq, Eq WsLoc
Eq WsLoc
-> (WsLoc -> WsLoc -> Ordering)
-> (WsLoc -> WsLoc -> Bool)
-> (WsLoc -> WsLoc -> Bool)
-> (WsLoc -> WsLoc -> Bool)
-> (WsLoc -> WsLoc -> Bool)
-> (WsLoc -> WsLoc -> WsLoc)
-> (WsLoc -> WsLoc -> WsLoc)
-> Ord WsLoc
WsLoc -> WsLoc -> Bool
WsLoc -> WsLoc -> Ordering
WsLoc -> WsLoc -> WsLoc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WsLoc -> WsLoc -> WsLoc
$cmin :: WsLoc -> WsLoc -> WsLoc
max :: WsLoc -> WsLoc -> WsLoc
$cmax :: WsLoc -> WsLoc -> WsLoc
>= :: WsLoc -> WsLoc -> Bool
$c>= :: WsLoc -> WsLoc -> Bool
> :: WsLoc -> WsLoc -> Bool
$c> :: WsLoc -> WsLoc -> Bool
<= :: WsLoc -> WsLoc -> Bool
$c<= :: WsLoc -> WsLoc -> Bool
< :: WsLoc -> WsLoc -> Bool
$c< :: WsLoc -> WsLoc -> Bool
compare :: WsLoc -> WsLoc -> Ordering
$ccompare :: WsLoc -> WsLoc -> Ordering
$cp1Ord :: Eq WsLoc
Ord, WsLoc
WsLoc -> WsLoc -> Bounded WsLoc
forall a. a -> a -> Bounded a
maxBound :: WsLoc
$cmaxBound :: WsLoc
minBound :: WsLoc
$cminBound :: WsLoc
Bounded, Int -> WsLoc
WsLoc -> Int
WsLoc -> [WsLoc]
WsLoc -> WsLoc
WsLoc -> WsLoc -> [WsLoc]
WsLoc -> WsLoc -> WsLoc -> [WsLoc]
(WsLoc -> WsLoc)
-> (WsLoc -> WsLoc)
-> (Int -> WsLoc)
-> (WsLoc -> Int)
-> (WsLoc -> [WsLoc])
-> (WsLoc -> WsLoc -> [WsLoc])
-> (WsLoc -> WsLoc -> [WsLoc])
-> (WsLoc -> WsLoc -> WsLoc -> [WsLoc])
-> Enum WsLoc
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: WsLoc -> WsLoc -> WsLoc -> [WsLoc]
$cenumFromThenTo :: WsLoc -> WsLoc -> WsLoc -> [WsLoc]
enumFromTo :: WsLoc -> WsLoc -> [WsLoc]
$cenumFromTo :: WsLoc -> WsLoc -> [WsLoc]
enumFromThen :: WsLoc -> WsLoc -> [WsLoc]
$cenumFromThen :: WsLoc -> WsLoc -> [WsLoc]
enumFrom :: WsLoc -> [WsLoc]
$cenumFrom :: WsLoc -> [WsLoc]
fromEnum :: WsLoc -> Int
$cfromEnum :: WsLoc -> Int
toEnum :: Int -> WsLoc
$ctoEnum :: Int -> WsLoc
pred :: WsLoc -> WsLoc
$cpred :: WsLoc -> WsLoc
succ :: WsLoc -> WsLoc
$csucc :: WsLoc -> WsLoc
Enum, Int -> WsLoc -> ShowS
[WsLoc] -> ShowS
WsLoc -> String
(Int -> WsLoc -> ShowS)
-> (WsLoc -> String) -> ([WsLoc] -> ShowS) -> Show WsLoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WsLoc] -> ShowS
$cshowList :: [WsLoc] -> ShowS
show :: WsLoc -> String
$cshow :: WsLoc -> String
showsPrec :: Int -> WsLoc -> ShowS
$cshowsPrec :: Int -> WsLoc -> ShowS
Show, (forall x. WsLoc -> Rep WsLoc x)
-> (forall x. Rep WsLoc x -> WsLoc) -> Generic WsLoc
forall x. Rep WsLoc x -> WsLoc
forall x. WsLoc -> Rep WsLoc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WsLoc x -> WsLoc
$cfrom :: forall x. WsLoc -> Rep WsLoc x
Generic )

data Whitespace = Whitespace { Whitespace -> WsLoc
wsSpaces         :: !WsLoc
                             , Whitespace -> WsLoc
wsLinebreaks     :: !WsLoc
                             , Whitespace -> Bool
wsForceLinebreak :: !Bool
                             }
    deriving ( Int -> Whitespace -> ShowS
[Whitespace] -> ShowS
Whitespace -> String
(Int -> Whitespace -> ShowS)
-> (Whitespace -> String)
-> ([Whitespace] -> ShowS)
-> Show Whitespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Whitespace] -> ShowS
$cshowList :: [Whitespace] -> ShowS
show :: Whitespace -> String
$cshow :: Whitespace -> String
showsPrec :: Int -> Whitespace -> ShowS
$cshowsPrec :: Int -> Whitespace -> ShowS
Show, (forall x. Whitespace -> Rep Whitespace x)
-> (forall x. Rep Whitespace x -> Whitespace) -> Generic Whitespace
forall x. Rep Whitespace x -> Whitespace
forall x. Whitespace -> Rep Whitespace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Whitespace x -> Whitespace
$cfrom :: forall x. Whitespace -> Rep Whitespace x
Generic )

data Layout = Flex | Vertical | TryOneline
    deriving ( Layout -> Layout -> Bool
(Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool) -> Eq Layout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Layout -> Layout -> Bool
$c/= :: Layout -> Layout -> Bool
== :: Layout -> Layout -> Bool
$c== :: Layout -> Layout -> Bool
Eq, Eq Layout
Eq Layout
-> (Layout -> Layout -> Ordering)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool)
-> (Layout -> Layout -> Layout)
-> (Layout -> Layout -> Layout)
-> Ord Layout
Layout -> Layout -> Bool
Layout -> Layout -> Ordering
Layout -> Layout -> Layout
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Layout -> Layout -> Layout
$cmin :: Layout -> Layout -> Layout
max :: Layout -> Layout -> Layout
$cmax :: Layout -> Layout -> Layout
>= :: Layout -> Layout -> Bool
$c>= :: Layout -> Layout -> Bool
> :: Layout -> Layout -> Bool
$c> :: Layout -> Layout -> Bool
<= :: Layout -> Layout -> Bool
$c<= :: Layout -> Layout -> Bool
< :: Layout -> Layout -> Bool
$c< :: Layout -> Layout -> Bool
compare :: Layout -> Layout -> Ordering
$ccompare :: Layout -> Layout -> Ordering
$cp1Ord :: Eq Layout
Ord, Layout
Layout -> Layout -> Bounded Layout
forall a. a -> a -> Bounded a
maxBound :: Layout
$cmaxBound :: Layout
minBound :: Layout
$cminBound :: Layout
Bounded, Int -> Layout
Layout -> Int
Layout -> [Layout]
Layout -> Layout
Layout -> Layout -> [Layout]
Layout -> Layout -> Layout -> [Layout]
(Layout -> Layout)
-> (Layout -> Layout)
-> (Int -> Layout)
-> (Layout -> Int)
-> (Layout -> [Layout])
-> (Layout -> Layout -> [Layout])
-> (Layout -> Layout -> [Layout])
-> (Layout -> Layout -> Layout -> [Layout])
-> Enum Layout
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Layout -> Layout -> Layout -> [Layout]
$cenumFromThenTo :: Layout -> Layout -> Layout -> [Layout]
enumFromTo :: Layout -> Layout -> [Layout]
$cenumFromTo :: Layout -> Layout -> [Layout]
enumFromThen :: Layout -> Layout -> [Layout]
$cenumFromThen :: Layout -> Layout -> [Layout]
enumFrom :: Layout -> [Layout]
$cenumFrom :: Layout -> [Layout]
fromEnum :: Layout -> Int
$cfromEnum :: Layout -> Int
toEnum :: Int -> Layout
$ctoEnum :: Int -> Layout
pred :: Layout -> Layout
$cpred :: Layout -> Layout
succ :: Layout -> Layout
$csucc :: Layout -> Layout
Enum, Int -> Layout -> ShowS
[Layout] -> ShowS
Layout -> String
(Int -> Layout -> ShowS)
-> (Layout -> String) -> ([Layout] -> ShowS) -> Show Layout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Layout] -> ShowS
$cshowList :: [Layout] -> ShowS
show :: Layout -> String
$cshow :: Layout -> String
showsPrec :: Int -> Layout -> ShowS
$cshowsPrec :: Int -> Layout -> ShowS
Show, (forall x. Layout -> Rep Layout x)
-> (forall x. Rep Layout x -> Layout) -> Generic Layout
forall x. Rep Layout x -> Layout
forall x. Layout -> Rep Layout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Layout x -> Layout
$cfrom :: forall x. Layout -> Rep Layout x
Generic )

data ConfigMapKey = ConfigMapKey !(Maybe ByteString) !(Maybe LayoutContext)
    deriving ( ConfigMapKey -> ConfigMapKey -> Bool
(ConfigMapKey -> ConfigMapKey -> Bool)
-> (ConfigMapKey -> ConfigMapKey -> Bool) -> Eq ConfigMapKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigMapKey -> ConfigMapKey -> Bool
$c/= :: ConfigMapKey -> ConfigMapKey -> Bool
== :: ConfigMapKey -> ConfigMapKey -> Bool
$c== :: ConfigMapKey -> ConfigMapKey -> Bool
Eq, Eq ConfigMapKey
Eq ConfigMapKey
-> (ConfigMapKey -> ConfigMapKey -> Ordering)
-> (ConfigMapKey -> ConfigMapKey -> Bool)
-> (ConfigMapKey -> ConfigMapKey -> Bool)
-> (ConfigMapKey -> ConfigMapKey -> Bool)
-> (ConfigMapKey -> ConfigMapKey -> Bool)
-> (ConfigMapKey -> ConfigMapKey -> ConfigMapKey)
-> (ConfigMapKey -> ConfigMapKey -> ConfigMapKey)
-> Ord ConfigMapKey
ConfigMapKey -> ConfigMapKey -> Bool
ConfigMapKey -> ConfigMapKey -> Ordering
ConfigMapKey -> ConfigMapKey -> ConfigMapKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConfigMapKey -> ConfigMapKey -> ConfigMapKey
$cmin :: ConfigMapKey -> ConfigMapKey -> ConfigMapKey
max :: ConfigMapKey -> ConfigMapKey -> ConfigMapKey
$cmax :: ConfigMapKey -> ConfigMapKey -> ConfigMapKey
>= :: ConfigMapKey -> ConfigMapKey -> Bool
$c>= :: ConfigMapKey -> ConfigMapKey -> Bool
> :: ConfigMapKey -> ConfigMapKey -> Bool
$c> :: ConfigMapKey -> ConfigMapKey -> Bool
<= :: ConfigMapKey -> ConfigMapKey -> Bool
$c<= :: ConfigMapKey -> ConfigMapKey -> Bool
< :: ConfigMapKey -> ConfigMapKey -> Bool
$c< :: ConfigMapKey -> ConfigMapKey -> Bool
compare :: ConfigMapKey -> ConfigMapKey -> Ordering
$ccompare :: ConfigMapKey -> ConfigMapKey -> Ordering
$cp1Ord :: Eq ConfigMapKey
Ord, Int -> ConfigMapKey -> ShowS
[ConfigMapKey] -> ShowS
ConfigMapKey -> String
(Int -> ConfigMapKey -> ShowS)
-> (ConfigMapKey -> String)
-> ([ConfigMapKey] -> ShowS)
-> Show ConfigMapKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigMapKey] -> ShowS
$cshowList :: [ConfigMapKey] -> ShowS
show :: ConfigMapKey -> String
$cshow :: ConfigMapKey -> String
showsPrec :: Int -> ConfigMapKey -> ShowS
$cshowsPrec :: Int -> ConfigMapKey -> ShowS
Show )

data ConfigMap a =
    ConfigMap { ConfigMap a -> a
cfgMapDefault :: !a, ConfigMap a -> Map ConfigMapKey a
cfgMapOverrides :: !(Map ConfigMapKey a) }
    deriving ( (forall x. ConfigMap a -> Rep (ConfigMap a) x)
-> (forall x. Rep (ConfigMap a) x -> ConfigMap a)
-> Generic (ConfigMap a)
forall x. Rep (ConfigMap a) x -> ConfigMap a
forall x. ConfigMap a -> Rep (ConfigMap a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ConfigMap a) x -> ConfigMap a
forall a x. ConfigMap a -> Rep (ConfigMap a) x
$cto :: forall a x. Rep (ConfigMap a) x -> ConfigMap a
$cfrom :: forall a x. ConfigMap a -> Rep (ConfigMap a) x
Generic )

data PenaltyConfig = PenaltyConfig { PenaltyConfig -> Int
penaltyMaxLineLength :: !Int
                                   , PenaltyConfig -> Int
penaltyLinebreak     :: !Int
                                   , PenaltyConfig -> Int
penaltyIndent        :: !Int
                                   , PenaltyConfig -> Int
penaltyOverfull      :: !Int
                                   , PenaltyConfig -> Int
penaltyOverfullOnce  :: !Int
                                   }
    deriving ( (forall x. PenaltyConfig -> Rep PenaltyConfig x)
-> (forall x. Rep PenaltyConfig x -> PenaltyConfig)
-> Generic PenaltyConfig
forall x. Rep PenaltyConfig x -> PenaltyConfig
forall x. PenaltyConfig -> Rep PenaltyConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PenaltyConfig x -> PenaltyConfig
$cfrom :: forall x. PenaltyConfig -> Rep PenaltyConfig x
Generic )

instance Default PenaltyConfig where
    def :: PenaltyConfig
def = PenaltyConfig :: Int -> Int -> Int -> Int -> Int -> PenaltyConfig
PenaltyConfig { penaltyMaxLineLength :: Int
penaltyMaxLineLength = Int
80
                        , penaltyLinebreak :: Int
penaltyLinebreak     = Int
100
                        , penaltyIndent :: Int
penaltyIndent        = Int
1
                        , penaltyOverfull :: Int
penaltyOverfull      = Int
10
                        , penaltyOverfullOnce :: Int
penaltyOverfullOnce  = Int
200
                        }

data AlignConfig =
    AlignConfig { AlignConfig -> (Int, Int)
cfgAlignLimits       :: !(Int, Int)
                , AlignConfig -> Bool
cfgAlignCase         :: !Bool
                , AlignConfig -> Bool
cfgAlignClass        :: !Bool
                , AlignConfig -> Bool
cfgAlignImportModule :: !Bool
                , AlignConfig -> Bool
cfgAlignImportSpec   :: !Bool
                , AlignConfig -> Bool
cfgAlignLetBinds     :: !Bool
                , AlignConfig -> Bool
cfgAlignMatches      :: !Bool
                , AlignConfig -> Bool
cfgAlignRecordFields :: !Bool
                , AlignConfig -> Bool
cfgAlignWhere        :: !Bool
                }
    deriving ( (forall x. AlignConfig -> Rep AlignConfig x)
-> (forall x. Rep AlignConfig x -> AlignConfig)
-> Generic AlignConfig
forall x. Rep AlignConfig x -> AlignConfig
forall x. AlignConfig -> Rep AlignConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AlignConfig x -> AlignConfig
$cfrom :: forall x. AlignConfig -> Rep AlignConfig x
Generic )

instance Default AlignConfig where
    def :: AlignConfig
def = AlignConfig :: (Int, Int)
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> AlignConfig
AlignConfig { cfgAlignLimits :: (Int, Int)
cfgAlignLimits       = (Int
10, Int
25)
                      , cfgAlignCase :: Bool
cfgAlignCase         = Bool
False
                      , cfgAlignClass :: Bool
cfgAlignClass        = Bool
False
                      , cfgAlignImportModule :: Bool
cfgAlignImportModule = Bool
False
                      , 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
                      }

data IndentConfig =
    IndentConfig { IndentConfig -> Int
cfgIndentOnside :: !Int
                 , IndentConfig -> Int
cfgIndentDeriving :: !Int
                 , IndentConfig -> Int
cfgIndentWhere :: !Int
                 , IndentConfig -> Indent
cfgIndentApp :: !Indent
                 , IndentConfig -> Indent
cfgIndentCase :: !Indent
                 , IndentConfig -> Indent
cfgIndentClass :: !Indent
                 , IndentConfig -> Indent
cfgIndentDo :: !Indent
                 , IndentConfig -> Indent
cfgIndentExportSpecList :: !Indent
                 , IndentConfig -> Indent
cfgIndentIf :: !Indent
                 , IndentConfig -> Indent
cfgIndentImportSpecList :: !Indent
                 , IndentConfig -> Indent
cfgIndentLet :: !Indent
                 , IndentConfig -> Indent
cfgIndentLetBinds :: !Indent
                 , IndentConfig -> Indent
cfgIndentLetIn :: !Indent
                 , IndentConfig -> Indent
cfgIndentMultiIf :: !Indent
                 , IndentConfig -> Indent
cfgIndentTypesig :: !Indent
                 , IndentConfig -> Indent
cfgIndentWhereBinds :: !Indent
                 }
    deriving ( (forall x. IndentConfig -> Rep IndentConfig x)
-> (forall x. Rep IndentConfig x -> IndentConfig)
-> Generic IndentConfig
forall x. Rep IndentConfig x -> IndentConfig
forall x. IndentConfig -> Rep IndentConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IndentConfig x -> IndentConfig
$cfrom :: forall x. IndentConfig -> Rep IndentConfig x
Generic )

instance Default IndentConfig where
    def :: IndentConfig
def = IndentConfig :: Int
-> Int
-> Int
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> Indent
-> IndentConfig
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
                       , cfgIndentExportSpecList :: Indent
cfgIndentExportSpecList = Int -> Indent
IndentBy Int
4
                       , cfgIndentIf :: Indent
cfgIndentIf = Int -> Indent
IndentBy Int
4
                       , cfgIndentImportSpecList :: Indent
cfgIndentImportSpecList = Int -> Indent
IndentBy Int
4
                       , cfgIndentLet :: Indent
cfgIndentLet = Int -> Indent
IndentBy Int
4
                       , cfgIndentLetBinds :: Indent
cfgIndentLetBinds = Int -> Indent
IndentBy Int
4
                       , cfgIndentLetIn :: Indent
cfgIndentLetIn = Int -> Indent
IndentBy Int
4
                       , cfgIndentMultiIf :: Indent
cfgIndentMultiIf = Int -> Indent
IndentBy Int
4
                       , cfgIndentTypesig :: Indent
cfgIndentTypesig = Int -> Indent
IndentBy Int
4
                       , cfgIndentWhereBinds :: Indent
cfgIndentWhereBinds = Int -> Indent
IndentBy Int
2
                       }

data LayoutConfig =
    LayoutConfig { LayoutConfig -> Layout
cfgLayoutApp :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutConDecls :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutDeclaration :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutExportSpecList :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutIf :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutImportSpecList :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutInfixApp :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutLet :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutListComp :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutRecord :: !Layout
                 , LayoutConfig -> Layout
cfgLayoutType :: !Layout
                 }
    deriving ( (forall x. LayoutConfig -> Rep LayoutConfig x)
-> (forall x. Rep LayoutConfig x -> LayoutConfig)
-> Generic LayoutConfig
forall x. Rep LayoutConfig x -> LayoutConfig
forall x. LayoutConfig -> Rep LayoutConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LayoutConfig x -> LayoutConfig
$cfrom :: forall x. LayoutConfig -> Rep LayoutConfig x
Generic )

instance Default LayoutConfig where
    def :: LayoutConfig
def = LayoutConfig :: Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> Layout
-> LayoutConfig
LayoutConfig { cfgLayoutApp :: Layout
cfgLayoutApp = Layout
Flex
                       , cfgLayoutConDecls :: Layout
cfgLayoutConDecls = Layout
Flex
                       , cfgLayoutDeclaration :: Layout
cfgLayoutDeclaration = Layout
Flex
                       , cfgLayoutExportSpecList :: Layout
cfgLayoutExportSpecList = Layout
Flex
                       , cfgLayoutIf :: Layout
cfgLayoutIf = Layout
Flex
                       , cfgLayoutImportSpecList :: Layout
cfgLayoutImportSpecList = Layout
Flex
                       , cfgLayoutInfixApp :: Layout
cfgLayoutInfixApp = Layout
Flex
                       , cfgLayoutLet :: Layout
cfgLayoutLet = Layout
Flex
                       , cfgLayoutListComp :: Layout
cfgLayoutListComp = Layout
Flex
                       , cfgLayoutRecord :: Layout
cfgLayoutRecord = Layout
Flex
                       , cfgLayoutType :: Layout
cfgLayoutType = Layout
Flex
                       }

newtype OpConfig = OpConfig { OpConfig -> ConfigMap Whitespace
unOpConfig :: ConfigMap Whitespace }
    deriving ( (forall x. OpConfig -> Rep OpConfig x)
-> (forall x. Rep OpConfig x -> OpConfig) -> Generic OpConfig
forall x. Rep OpConfig x -> OpConfig
forall x. OpConfig -> Rep OpConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpConfig x -> OpConfig
$cfrom :: forall x. OpConfig -> Rep OpConfig x
Generic )

instance Default OpConfig where
    def :: OpConfig
def =
        ConfigMap Whitespace -> OpConfig
OpConfig ConfigMap :: forall a. a -> Map ConfigMapKey a -> ConfigMap a
ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault   = WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsBefore Bool
False
                           , cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = Map ConfigMapKey Whitespace
forall k a. Map k a
Map.empty
                           }

newtype GroupConfig = GroupConfig { GroupConfig -> ConfigMap Whitespace
unGroupConfig :: ConfigMap Whitespace }
    deriving ( (forall x. GroupConfig -> Rep GroupConfig x)
-> (forall x. Rep GroupConfig x -> GroupConfig)
-> Generic GroupConfig
forall x. Rep GroupConfig x -> GroupConfig
forall x. GroupConfig -> Rep GroupConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupConfig x -> GroupConfig
$cfrom :: forall x. GroupConfig -> Rep GroupConfig x
Generic )

instance Default GroupConfig where
    def :: GroupConfig
def = ConfigMap Whitespace -> GroupConfig
GroupConfig ConfigMap :: forall a. a -> Map ConfigMapKey a -> ConfigMap a
ConfigMap { cfgMapDefault :: Whitespace
cfgMapDefault   =
                                      WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsAfter Bool
False
                                , cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = Map ConfigMapKey Whitespace
forall k a. Map k a
Map.empty
                                }

data ImportsGroupOrder =
    ImportsGroupKeep | ImportsGroupSorted | ImportsGroupGrouped
    deriving ( (forall x. ImportsGroupOrder -> Rep ImportsGroupOrder x)
-> (forall x. Rep ImportsGroupOrder x -> ImportsGroupOrder)
-> Generic ImportsGroupOrder
forall x. Rep ImportsGroupOrder x -> ImportsGroupOrder
forall x. ImportsGroupOrder -> Rep ImportsGroupOrder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportsGroupOrder x -> ImportsGroupOrder
$cfrom :: forall x. ImportsGroupOrder -> Rep ImportsGroupOrder x
Generic )

data ImportsGroup = ImportsGroup { ImportsGroup -> [String]
importsPrefixes :: ![String]
                                 , ImportsGroup -> ImportsGroupOrder
importsOrder    :: !ImportsGroupOrder
                                 }
    deriving ( (forall x. ImportsGroup -> Rep ImportsGroup x)
-> (forall x. Rep ImportsGroup x -> ImportsGroup)
-> Generic ImportsGroup
forall x. Rep ImportsGroup x -> ImportsGroup
forall x. ImportsGroup -> Rep ImportsGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportsGroup x -> ImportsGroup
$cfrom :: forall x. ImportsGroup -> Rep ImportsGroup x
Generic )

data SortImportsRule =
    NoImportSort | SortImportsByPrefix | SortImportsByGroups ![ImportsGroup]

data DeclarationConstruct = DeclModule | DeclClass | DeclInstance | DeclWhere
    deriving ( DeclarationConstruct -> DeclarationConstruct -> Bool
(DeclarationConstruct -> DeclarationConstruct -> Bool)
-> (DeclarationConstruct -> DeclarationConstruct -> Bool)
-> Eq DeclarationConstruct
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c/= :: DeclarationConstruct -> DeclarationConstruct -> Bool
== :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c== :: DeclarationConstruct -> DeclarationConstruct -> Bool
Eq, Eq DeclarationConstruct
Eq DeclarationConstruct
-> (DeclarationConstruct -> DeclarationConstruct -> Ordering)
-> (DeclarationConstruct -> DeclarationConstruct -> Bool)
-> (DeclarationConstruct -> DeclarationConstruct -> Bool)
-> (DeclarationConstruct -> DeclarationConstruct -> Bool)
-> (DeclarationConstruct -> DeclarationConstruct -> Bool)
-> (DeclarationConstruct
    -> DeclarationConstruct -> DeclarationConstruct)
-> (DeclarationConstruct
    -> DeclarationConstruct -> DeclarationConstruct)
-> Ord DeclarationConstruct
DeclarationConstruct -> DeclarationConstruct -> Bool
DeclarationConstruct -> DeclarationConstruct -> Ordering
DeclarationConstruct
-> DeclarationConstruct -> DeclarationConstruct
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DeclarationConstruct
-> DeclarationConstruct -> DeclarationConstruct
$cmin :: DeclarationConstruct
-> DeclarationConstruct -> DeclarationConstruct
max :: DeclarationConstruct
-> DeclarationConstruct -> DeclarationConstruct
$cmax :: DeclarationConstruct
-> DeclarationConstruct -> DeclarationConstruct
>= :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c>= :: DeclarationConstruct -> DeclarationConstruct -> Bool
> :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c> :: DeclarationConstruct -> DeclarationConstruct -> Bool
<= :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c<= :: DeclarationConstruct -> DeclarationConstruct -> Bool
< :: DeclarationConstruct -> DeclarationConstruct -> Bool
$c< :: DeclarationConstruct -> DeclarationConstruct -> Bool
compare :: DeclarationConstruct -> DeclarationConstruct -> Ordering
$ccompare :: DeclarationConstruct -> DeclarationConstruct -> Ordering
$cp1Ord :: Eq DeclarationConstruct
Ord, (forall x. DeclarationConstruct -> Rep DeclarationConstruct x)
-> (forall x. Rep DeclarationConstruct x -> DeclarationConstruct)
-> Generic DeclarationConstruct
forall x. Rep DeclarationConstruct x -> DeclarationConstruct
forall x. DeclarationConstruct -> Rep DeclarationConstruct x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeclarationConstruct x -> DeclarationConstruct
$cfrom :: forall x. DeclarationConstruct -> Rep DeclarationConstruct x
Generic )

data OptionConfig =
    OptionConfig { OptionConfig -> Bool
cfgOptionSortPragmas            :: !Bool
                 , OptionConfig -> Bool
cfgOptionSplitLanguagePragmas   :: !Bool
                 , OptionConfig -> SortImportsRule
cfgOptionSortImports            :: !SortImportsRule
                 , OptionConfig -> Bool
cfgOptionSortImportLists        :: !Bool
                 , OptionConfig -> Bool
cfgOptionAlignSumTypeDecl       :: !Bool
                 , OptionConfig -> Bool
cfgOptionFlexibleOneline        :: !Bool
                 , OptionConfig -> Bool
cfgOptionPreserveVerticalSpace  :: !Bool
                 , OptionConfig -> Set DeclarationConstruct
cfgOptionDeclNoBlankLines       :: !(Set DeclarationConstruct)
                 , OptionConfig -> Bool
cfgOptionAlignLetBindsAndInExpr :: !Bool
                 }
    deriving ( (forall x. OptionConfig -> Rep OptionConfig x)
-> (forall x. Rep OptionConfig x -> OptionConfig)
-> Generic OptionConfig
forall x. Rep OptionConfig x -> OptionConfig
forall x. OptionConfig -> Rep OptionConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OptionConfig x -> OptionConfig
$cfrom :: forall x. OptionConfig -> Rep OptionConfig x
Generic )

instance Default OptionConfig where
    def :: OptionConfig
def = OptionConfig :: Bool
-> Bool
-> SortImportsRule
-> Bool
-> Bool
-> Bool
-> Bool
-> Set DeclarationConstruct
-> Bool
-> OptionConfig
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       = Set DeclarationConstruct
forall a. Set a
Set.empty
                       , cfgOptionAlignLetBindsAndInExpr :: Bool
cfgOptionAlignLetBindsAndInExpr = Bool
False
                       }

data Config = Config { Config -> PenaltyConfig
cfgPenalty :: !PenaltyConfig
                     , Config -> AlignConfig
cfgAlign   :: !AlignConfig
                     , Config -> IndentConfig
cfgIndent  :: !IndentConfig
                     , Config -> LayoutConfig
cfgLayout  :: !LayoutConfig
                     , Config -> OpConfig
cfgOp      :: !OpConfig
                     , Config -> GroupConfig
cfgGroup   :: !GroupConfig
                     , Config -> OptionConfig
cfgOptions :: !OptionConfig
                     }
    deriving ( (forall x. Config -> Rep Config x)
-> (forall x. Rep Config x -> Config) -> Generic Config
forall x. Rep Config x -> Config
forall x. Config -> Rep Config x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Config x -> Config
$cfrom :: forall x. Config -> Rep Config x
Generic )

instance Default Config where
    def :: Config
def = Config :: PenaltyConfig
-> AlignConfig
-> IndentConfig
-> LayoutConfig
-> OpConfig
-> GroupConfig
-> OptionConfig
-> Config
Config { cfgPenalty :: PenaltyConfig
cfgPenalty = PenaltyConfig
forall a. Default a => a
def
                 , cfgAlign :: AlignConfig
cfgAlign   = AlignConfig
forall a. Default a => a
def
                 , cfgIndent :: IndentConfig
cfgIndent  = IndentConfig
forall a. Default a => a
def
                 , cfgLayout :: LayoutConfig
cfgLayout  = LayoutConfig
forall a. Default a => a
def
                 , cfgOp :: OpConfig
cfgOp      = OpConfig
forall a. Default a => a
def
                 , cfgGroup :: GroupConfig
cfgGroup   = GroupConfig
forall a. Default a => a
def
                 , cfgOptions :: OptionConfig
cfgOptions = OptionConfig
forall a. Default a => a
def
                 }

defaultConfig :: Config
defaultConfig :: Config
defaultConfig =
    Config
forall a. Default a => a
def { cfgOp :: OpConfig
cfgOp    = ConfigMap Whitespace -> OpConfig
OpConfig ((OpConfig -> ConfigMap Whitespace
unOpConfig OpConfig
forall a. Default a => a
def) { cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides =
                                                      [(ConfigMapKey, Whitespace)] -> Map ConfigMapKey Whitespace
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
opWsOverrides
                                                })
        , cfgGroup :: GroupConfig
cfgGroup = ConfigMap Whitespace -> GroupConfig
GroupConfig ((GroupConfig -> ConfigMap Whitespace
unGroupConfig GroupConfig
forall a. Default a => a
def) { cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides = [(ConfigMapKey, Whitespace)] -> Map ConfigMapKey Whitespace
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ConfigMapKey, Whitespace)]
groupWsOverrides
                                                      })
        }
  where
    opWsOverrides :: [(ConfigMapKey, Whitespace)]
opWsOverrides =
        [ (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
",") Maybe LayoutContext
forall a. Maybe a
Nothing, WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsBefore Bool
False)
        , ( Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"record") Maybe LayoutContext
forall a. Maybe a
Nothing
          , WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
          )
        , ( Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
".") (LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Type)
          , WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsAfter WsLoc
WsAfter Bool
False
          )
        ]

    groupWsOverrides :: [(ConfigMapKey, Whitespace)]
groupWsOverrides =
        [ (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"[") (LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Type), WsLoc -> WsLoc -> Bool -> Whitespace
Whitespace WsLoc
WsBoth WsLoc
WsNone Bool
False)
        ]

safeConfig :: Config -> Config
safeConfig :: Config -> Config
safeConfig Config
cfg = Config
cfg { cfgGroup :: GroupConfig
cfgGroup = GroupConfig
group, cfgOp :: OpConfig
cfgOp = OpConfig
op }
  where
    group :: GroupConfig
group = ConfigMap Whitespace -> GroupConfig
GroupConfig (ConfigMap Whitespace -> GroupConfig)
-> ConfigMap Whitespace -> GroupConfig
forall a b. (a -> b) -> a -> b
$
        ConfigMap Whitespace
-> [(ByteString, LayoutContext, WsLoc)] -> ConfigMap Whitespace
forall (t :: * -> *).
Foldable t =>
ConfigMap Whitespace
-> t (ByteString, LayoutContext, WsLoc) -> ConfigMap Whitespace
updateOverrides (GroupConfig -> ConfigMap Whitespace
unGroupConfig (GroupConfig -> ConfigMap Whitespace)
-> GroupConfig -> ConfigMap Whitespace
forall a b. (a -> b) -> a -> b
$ Config -> GroupConfig
cfgGroup Config
cfg)
                        [ (ByteString
"(#", LayoutContext
Expression, WsLoc
WsBoth), (ByteString
"(#", LayoutContext
Pattern, WsLoc
WsBoth) ]

    op :: OpConfig
op = ConfigMap Whitespace -> OpConfig
OpConfig (ConfigMap Whitespace -> OpConfig)
-> ConfigMap Whitespace -> OpConfig
forall a b. (a -> b) -> a -> b
$
        ConfigMap Whitespace
-> [(ByteString, LayoutContext, WsLoc)] -> ConfigMap Whitespace
forall (t :: * -> *).
Foldable t =>
ConfigMap Whitespace
-> t (ByteString, LayoutContext, WsLoc) -> ConfigMap Whitespace
updateOverrides (OpConfig -> ConfigMap Whitespace
unOpConfig (OpConfig -> ConfigMap Whitespace)
-> OpConfig -> ConfigMap Whitespace
forall a b. (a -> b) -> a -> b
$ Config -> OpConfig
cfgOp Config
cfg)
                        [ (ByteString
".", LayoutContext
Expression, WsLoc
WsBoth), (ByteString
"@", LayoutContext
Pattern, WsLoc
WsNone) ]

    updateOverrides :: ConfigMap Whitespace
-> t (ByteString, LayoutContext, WsLoc) -> ConfigMap Whitespace
updateOverrides ConfigMap Whitespace
config t (ByteString, LayoutContext, WsLoc)
overrides =
        ConfigMap Whitespace
config { cfgMapOverrides :: Map ConfigMapKey Whitespace
cfgMapOverrides =
                     (Map ConfigMapKey Whitespace
 -> (ByteString, LayoutContext, WsLoc)
 -> Map ConfigMapKey Whitespace)
-> Map ConfigMapKey Whitespace
-> t (ByteString, LayoutContext, WsLoc)
-> Map ConfigMapKey Whitespace
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (ConfigMap Whitespace
-> Map ConfigMapKey Whitespace
-> (ByteString, LayoutContext, WsLoc)
-> Map ConfigMapKey Whitespace
updateWs ConfigMap Whitespace
config) (ConfigMap Whitespace -> Map ConfigMapKey Whitespace
forall a. ConfigMap a -> Map ConfigMapKey a
cfgMapOverrides ConfigMap Whitespace
config) t (ByteString, LayoutContext, WsLoc)
overrides
               }

    updateWs :: ConfigMap Whitespace
-> Map ConfigMapKey Whitespace
-> (ByteString, LayoutContext, WsLoc)
-> Map ConfigMapKey Whitespace
updateWs ConfigMap Whitespace
config Map ConfigMapKey Whitespace
m (ByteString
key, LayoutContext
ctx, WsLoc
ws) =
        (Whitespace -> Whitespace -> Whitespace)
-> ConfigMapKey
-> Whitespace
-> Map ConfigMapKey Whitespace
-> Map ConfigMapKey Whitespace
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith ((Whitespace -> Whitespace -> Whitespace)
-> Whitespace -> Whitespace -> Whitespace
forall a b c. (a -> b -> c) -> b -> a -> c
flip Whitespace -> Whitespace -> Whitespace
forall a b. a -> b -> a
const)
                       (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
key) (LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
ctx))
                       (LayoutContext -> ByteString -> ConfigMap Whitespace -> Whitespace
forall a. LayoutContext -> ByteString -> ConfigMap a -> a
cfgMapFind LayoutContext
ctx ByteString
key ConfigMap Whitespace
config) { wsSpaces :: WsLoc
wsSpaces = WsLoc
ws }
                       Map ConfigMapKey Whitespace
m

cfgMapFind :: LayoutContext -> ByteString -> ConfigMap a -> a
cfgMapFind :: LayoutContext -> ByteString -> ConfigMap a -> a
cfgMapFind LayoutContext
ctx ByteString
key ConfigMap{a
Map ConfigMapKey a
cfgMapOverrides :: Map ConfigMapKey a
cfgMapDefault :: a
cfgMapOverrides :: forall a. ConfigMap a -> Map ConfigMapKey a
cfgMapDefault :: forall a. ConfigMap a -> a
..} =
    let value :: a
value = a
cfgMapDefault
        value' :: a
value' = a -> ConfigMapKey -> Map ConfigMapKey a -> a
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault a
value
                                     (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey Maybe ByteString
forall a. Maybe a
Nothing (LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
ctx))
                                     Map ConfigMapKey a
cfgMapOverrides
        value'' :: a
value'' = a -> ConfigMapKey -> Map ConfigMapKey a -> a
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault a
value'
                                      (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
key) Maybe LayoutContext
forall a. Maybe a
Nothing)
                                      Map ConfigMapKey a
cfgMapOverrides
        value''' :: a
value''' = a -> ConfigMapKey -> Map ConfigMapKey a -> a
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault a
value''
                                       (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
key) (LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
ctx))
                                       Map ConfigMapKey a
cfgMapOverrides
    in
        a
value'''

cfgOpWs :: LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs :: LayoutContext -> ByteString -> OpConfig -> Whitespace
cfgOpWs LayoutContext
ctx ByteString
op = LayoutContext -> ByteString -> ConfigMap Whitespace -> Whitespace
forall a. LayoutContext -> ByteString -> ConfigMap a -> a
cfgMapFind LayoutContext
ctx ByteString
op (ConfigMap Whitespace -> Whitespace)
-> (OpConfig -> ConfigMap Whitespace) -> OpConfig -> Whitespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OpConfig -> ConfigMap Whitespace
unOpConfig

cfgGroupWs :: LayoutContext -> ByteString -> GroupConfig -> Whitespace
cfgGroupWs :: LayoutContext -> ByteString -> GroupConfig -> Whitespace
cfgGroupWs LayoutContext
ctx ByteString
op = LayoutContext -> ByteString -> ConfigMap Whitespace -> Whitespace
forall a. LayoutContext -> ByteString -> ConfigMap a -> a
cfgMapFind LayoutContext
ctx ByteString
op (ConfigMap Whitespace -> Whitespace)
-> (GroupConfig -> ConfigMap Whitespace)
-> GroupConfig
-> Whitespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GroupConfig -> ConfigMap Whitespace
unGroupConfig

inWs :: Location -> WsLoc -> Bool
inWs :: Location -> WsLoc -> Bool
inWs Location
_ WsLoc
WsBoth = Bool
True
inWs Location
Before WsLoc
WsBefore = Bool
True
inWs Location
After WsLoc
WsAfter = Bool
True
inWs Location
_ WsLoc
_ = Bool
False

wsSpace :: Location -> Whitespace -> Bool
wsSpace :: Location -> Whitespace -> Bool
wsSpace Location
loc Whitespace
ws = Location
loc Location -> WsLoc -> Bool
`inWs` Whitespace -> WsLoc
wsSpaces Whitespace
ws

wsLinebreak :: Location -> Whitespace -> Bool
wsLinebreak :: Location -> Whitespace -> Bool
wsLinebreak Location
loc Whitespace
ws = Location
loc Location -> WsLoc -> Bool
`inWs` Whitespace -> WsLoc
wsLinebreaks Whitespace
ws

------------------------------------------------------------------------
readMaybe :: Read a => String -> Maybe a
readMaybe :: String -> Maybe a
readMaybe String
str = case ReadS a
forall a. Read a => ReadS a
reads String
str of
    [ (a
x, String
"") ] -> a -> Maybe a
forall a. a -> Maybe a
Just a
x
    [(a, String)]
_ -> Maybe a
forall a. Maybe a
Nothing

enumOptions :: Int -> Options
enumOptions :: Int -> Options
enumOptions Int
n =
    Options
JSON.defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = Char -> ShowS
JSON.camelTo2 Char
'-' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
n }

recordOptions :: Int -> Options
recordOptions :: Int -> Options
recordOptions Int
n =
    Options
JSON.defaultOptions { fieldLabelModifier :: ShowS
fieldLabelModifier = Char -> ShowS
JSON.camelTo2 Char
'-' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
n
                        , unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True
                        }

instance ToJSON Indent where
    toJSON :: Indent -> Value
toJSON Indent
i = Text -> Value
JSON.String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ case Indent
i of
        Indent
Align -> Text
"align"
        IndentBy Int
x -> Text
"indent-by " Text -> Text -> Text
`T.append` String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
x)
        AlignOrIndentBy Int
x -> Text
"align-or-indent-by " Text -> Text -> Text
`T.append` String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
x)

instance FromJSON Indent where
    parseJSON :: Value -> Parser Indent
parseJSON v :: Value
v@(JSON.String Text
t) = Parser Indent
-> (Indent -> Parser Indent) -> Maybe Indent -> Parser Indent
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Value -> Parser Indent
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"Indent" Value
v) Indent -> Parser Indent
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Indent -> Parser Indent) -> Maybe Indent -> Parser Indent
forall a b. (a -> b) -> a -> b
$
        if Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"align"
        then Indent -> Maybe Indent
forall a. a -> Maybe a
Just Indent
Align
        else if Text
"indent-by " Text -> Text -> Bool
`T.isPrefixOf` Text
t
             then Int -> Indent
IndentBy (Int -> Indent) -> Maybe Int -> Maybe Indent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
10 Text
t)
             else if Text
"align-or-indent-by " Text -> Text -> Bool
`T.isPrefixOf` Text
t
                  then Int -> Indent
AlignOrIndentBy (Int -> Indent) -> Maybe Int -> Maybe Indent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
19 Text
t)
                  else Maybe Indent
forall a. Maybe a
Nothing

    parseJSON Value
v = String -> Value -> Parser Indent
forall a. String -> Value -> Parser a
JSON.typeMismatch String
"Indent" Value
v

instance ToJSON LayoutContext where
    toJSON :: LayoutContext -> Value
toJSON = Options -> LayoutContext -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
enumOptions Int
0)

instance FromJSON LayoutContext where
    parseJSON :: Value -> Parser LayoutContext
parseJSON = Options -> Value -> Parser LayoutContext
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
enumOptions Int
0)

instance ToJSON WsLoc where
    toJSON :: WsLoc -> Value
toJSON = Options -> WsLoc -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
enumOptions Int
2)

instance FromJSON WsLoc where
    parseJSON :: Value -> Parser WsLoc
parseJSON = Options -> Value -> Parser WsLoc
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
enumOptions Int
2)

instance ToJSON Whitespace where
    toJSON :: Whitespace -> Value
toJSON = Options -> Whitespace -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
2)

instance FromJSON Whitespace where
    parseJSON :: Value -> Parser Whitespace
parseJSON = Options -> Value -> Parser Whitespace
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
2)

instance ToJSON Layout where
    toJSON :: Layout -> Value
toJSON = Options -> Layout -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
enumOptions Int
0)

instance FromJSON Layout where
    parseJSON :: Value -> Parser Layout
parseJSON = Options -> Value -> Parser Layout
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
enumOptions Int
0)

layoutToText :: LayoutContext -> T.Text
layoutToText :: LayoutContext -> Text
layoutToText LayoutContext
Declaration = Text
"declaration"
layoutToText LayoutContext
Type = Text
"type"
layoutToText LayoutContext
Pattern = Text
"pattern"
layoutToText LayoutContext
Expression = Text
"expression"
layoutToText LayoutContext
Other = Text
"other"

textToLayout :: T.Text -> Maybe LayoutContext
textToLayout :: Text -> Maybe LayoutContext
textToLayout Text
"declaration" = LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Declaration
textToLayout Text
"type" = LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Type
textToLayout Text
"pattern" = LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Pattern
textToLayout Text
"expression" = LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Expression
textToLayout Text
"other" = LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just LayoutContext
Other
textToLayout Text
_ = Maybe LayoutContext
forall a. Maybe a
Nothing

keyToText :: ConfigMapKey -> T.Text
keyToText :: ConfigMapKey -> Text
keyToText (ConfigMapKey Maybe ByteString
Nothing Maybe LayoutContext
Nothing) = Text
"default"
keyToText (ConfigMapKey (Just ByteString
n) Maybe LayoutContext
Nothing) = ByteString -> Text
T.decodeUtf8 ByteString
n
keyToText (ConfigMapKey Maybe ByteString
Nothing (Just LayoutContext
l)) = Text
"* in " Text -> Text -> Text
`T.append` LayoutContext -> Text
layoutToText LayoutContext
l
keyToText (ConfigMapKey (Just ByteString
n) (Just LayoutContext
l)) =
    ByteString -> Text
T.decodeUtf8 ByteString
n Text -> Text -> Text
`T.append` Text
" in " Text -> Text -> Text
`T.append` LayoutContext -> Text
layoutToText LayoutContext
l

textToKey :: T.Text -> Maybe ConfigMapKey
textToKey :: Text -> Maybe ConfigMapKey
textToKey Text
t = case Text -> Text -> [Text]
T.splitOn Text
" in " Text
t of
    [ Text
"default" ] -> ConfigMapKey -> Maybe ConfigMapKey
forall a. a -> Maybe a
Just (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey Maybe ByteString
forall a. Maybe a
Nothing Maybe LayoutContext
forall a. Maybe a
Nothing)
    [ Text
"*", Text
"*" ] -> ConfigMapKey -> Maybe ConfigMapKey
forall a. a -> Maybe a
Just (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey Maybe ByteString
forall a. Maybe a
Nothing Maybe LayoutContext
forall a. Maybe a
Nothing)
    [ Text
name ] -> ConfigMapKey -> Maybe ConfigMapKey
forall a. a -> Maybe a
Just (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
name)) Maybe LayoutContext
forall a. Maybe a
Nothing)
    [ Text
name, Text
"*" ] -> ConfigMapKey -> Maybe ConfigMapKey
forall a. a -> Maybe a
Just (Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
name)) Maybe LayoutContext
forall a. Maybe a
Nothing)
    [ Text
"*", Text
layout ] -> Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey Maybe ByteString
forall a. Maybe a
Nothing (Maybe LayoutContext -> ConfigMapKey)
-> (LayoutContext -> Maybe LayoutContext)
-> LayoutContext
-> ConfigMapKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just (LayoutContext -> ConfigMapKey)
-> Maybe LayoutContext -> Maybe ConfigMapKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe LayoutContext
textToLayout Text
layout
    [ Text
name, Text
layout ] -> Maybe ByteString -> Maybe LayoutContext -> ConfigMapKey
ConfigMapKey (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
name)) (Maybe LayoutContext -> ConfigMapKey)
-> (LayoutContext -> Maybe LayoutContext)
-> LayoutContext
-> ConfigMapKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayoutContext -> Maybe LayoutContext
forall a. a -> Maybe a
Just
        (LayoutContext -> ConfigMapKey)
-> Maybe LayoutContext -> Maybe ConfigMapKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe LayoutContext
textToLayout Text
layout
    [Text]
_ -> Maybe ConfigMapKey
forall a. Maybe a
Nothing

instance ToJSON a => ToJSON (ConfigMap a) where
    toJSON :: ConfigMap a -> Value
toJSON ConfigMap{a
Map ConfigMapKey a
cfgMapOverrides :: Map ConfigMapKey a
cfgMapDefault :: a
cfgMapOverrides :: forall a. ConfigMap a -> Map ConfigMapKey a
cfgMapDefault :: forall a. ConfigMap a -> a
..} = Map Text a -> Value
forall a. ToJSON a => a -> Value
toJSON (Map Text a -> Value) -> Map Text a -> Value
forall a b. (a -> b) -> a -> b
$ Text -> a -> Map Text a -> Map Text a
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Text
"default" a
cfgMapDefault (Map Text a -> Map Text a) -> Map Text a -> Map Text a
forall a b. (a -> b) -> a -> b
$
        (ConfigMapKey -> Text) -> Map ConfigMapKey a -> Map Text a
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys ConfigMapKey -> Text
keyToText Map ConfigMapKey a
cfgMapOverrides

instance FromJSON a => FromJSON (ConfigMap a) where
    parseJSON :: Value -> Parser (ConfigMap a)
parseJSON Value
value = do
        HashMap Text a
o <- Value -> Parser (HashMap Text a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value
        a
cfgMapDefault <- Parser a -> (a -> Parser a) -> Maybe a -> Parser a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Missing key: default") a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> Parser a) -> Maybe a -> Parser a
forall a b. (a -> b) -> a -> b
$
            Text -> HashMap Text a -> Maybe a
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"default" HashMap Text a
o
        Map ConfigMapKey a
cfgMapOverrides <- (String -> Parser (Map ConfigMapKey a))
-> ([(ConfigMapKey, a)] -> Parser (Map ConfigMapKey a))
-> Either String [(ConfigMapKey, a)]
-> Parser (Map ConfigMapKey a)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser (Map ConfigMapKey a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Map ConfigMapKey a -> Parser (Map ConfigMapKey a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map ConfigMapKey a -> Parser (Map ConfigMapKey a))
-> ([(ConfigMapKey, a)] -> Map ConfigMapKey a)
-> [(ConfigMapKey, a)]
-> Parser (Map ConfigMapKey a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ConfigMapKey, a)] -> Map ConfigMapKey a
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList) (Either String [(ConfigMapKey, a)] -> Parser (Map ConfigMapKey a))
-> Either String [(ConfigMapKey, a)] -> Parser (Map ConfigMapKey a)
forall a b. (a -> b) -> a -> b
$ ((Text, a) -> Either String (ConfigMapKey, a))
-> [(Text, a)] -> Either String [(ConfigMapKey, a)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Text, a) -> Either String (ConfigMapKey, a)
forall b. (Text, b) -> Either String (ConfigMapKey, b)
toKey ([(Text, a)] -> Either String [(ConfigMapKey, a)])
-> [(Text, a)] -> Either String [(ConfigMapKey, a)]
forall a b. (a -> b) -> a -> b
$
            HashMap Text a -> [(Text, a)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList (HashMap Text a -> [(Text, a)]) -> HashMap Text a -> [(Text, a)]
forall a b. (a -> b) -> a -> b
$ Text -> HashMap Text a -> HashMap Text a
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HashMap.delete Text
"default" HashMap Text a
o
        ConfigMap a -> Parser (ConfigMap a)
forall (m :: * -> *) a. Monad m => a -> m a
return ConfigMap :: forall a. a -> Map ConfigMapKey a -> ConfigMap a
ConfigMap { a
Map ConfigMapKey a
cfgMapOverrides :: Map ConfigMapKey a
cfgMapDefault :: a
cfgMapOverrides :: Map ConfigMapKey a
cfgMapDefault :: a
.. }
      where
        toKey :: (Text, b) -> Either String (ConfigMapKey, b)
toKey (Text
k, b
v) = case Text -> Maybe ConfigMapKey
textToKey Text
k of
            Just ConfigMapKey
k' -> (ConfigMapKey, b) -> Either String (ConfigMapKey, b)
forall a b. b -> Either a b
Right (ConfigMapKey
k', b
v)
            Maybe ConfigMapKey
Nothing -> String -> Either String (ConfigMapKey, b)
forall a b. a -> Either a b
Left (String
"Invalid key: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
k)

instance ToJSON PenaltyConfig where
    toJSON :: PenaltyConfig -> Value
toJSON = Options -> PenaltyConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
7)

instance FromJSON PenaltyConfig where
    parseJSON :: Value -> Parser PenaltyConfig
parseJSON = Options -> Value -> Parser PenaltyConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
7)

instance ToJSON AlignConfig where
    toJSON :: AlignConfig -> Value
toJSON = Options -> AlignConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
8)

instance FromJSON AlignConfig where
    parseJSON :: Value -> Parser AlignConfig
parseJSON = Options -> Value -> Parser AlignConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
8)

instance ToJSON IndentConfig where
    toJSON :: IndentConfig -> Value
toJSON = Options -> IndentConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
9)

instance FromJSON IndentConfig where
    parseJSON :: Value -> Parser IndentConfig
parseJSON = Options -> Value -> Parser IndentConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
9)

instance ToJSON LayoutConfig where
    toJSON :: LayoutConfig -> Value
toJSON = Options -> LayoutConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
9)

instance FromJSON LayoutConfig where
    parseJSON :: Value -> Parser LayoutConfig
parseJSON = Options -> Value -> Parser LayoutConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
9)

instance ToJSON OpConfig where
    toJSON :: OpConfig -> Value
toJSON = Options -> OpConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
0)

instance FromJSON OpConfig where
    parseJSON :: Value -> Parser OpConfig
parseJSON = Options -> Value -> Parser OpConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
0)

instance ToJSON GroupConfig where
    toJSON :: GroupConfig -> Value
toJSON = Options -> GroupConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
0)

instance FromJSON GroupConfig where
    parseJSON :: Value -> Parser GroupConfig
parseJSON = Options -> Value -> Parser GroupConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
0)

instance ToJSON ImportsGroupOrder where
    toJSON :: ImportsGroupOrder -> Value
toJSON = Options -> ImportsGroupOrder -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
enumOptions Int
12)

instance FromJSON ImportsGroupOrder where
    parseJSON :: Value -> Parser ImportsGroupOrder
parseJSON = Options -> Value -> Parser ImportsGroupOrder
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
enumOptions Int
12)

instance ToJSON ImportsGroup where
    toJSON :: ImportsGroup -> Value
toJSON = Options -> ImportsGroup -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
7)

instance FromJSON ImportsGroup where
    parseJSON :: Value -> Parser ImportsGroup
parseJSON x :: Value
x@JSON.Array{} =
        [String] -> ImportsGroupOrder -> ImportsGroup
ImportsGroup ([String] -> ImportsGroupOrder -> ImportsGroup)
-> Parser [String] -> Parser (ImportsGroupOrder -> ImportsGroup)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [String]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x Parser (ImportsGroupOrder -> ImportsGroup)
-> Parser ImportsGroupOrder -> Parser ImportsGroup
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ImportsGroupOrder -> Parser ImportsGroupOrder
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImportsGroupOrder
ImportsGroupKeep
    parseJSON Value
x = Options -> Value -> Parser ImportsGroup
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
7) Value
x

instance ToJSON SortImportsRule where
    toJSON :: SortImportsRule -> Value
toJSON SortImportsRule
NoImportSort = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
False
    toJSON SortImportsRule
SortImportsByPrefix = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True
    toJSON (SortImportsByGroups [ImportsGroup]
xs) = [ImportsGroup] -> Value
forall a. ToJSON a => a -> Value
toJSON [ImportsGroup]
xs

instance FromJSON SortImportsRule where
    parseJSON :: Value -> Parser SortImportsRule
parseJSON (JSON.Bool Bool
False) = SortImportsRule -> Parser SortImportsRule
forall (m :: * -> *) a. Monad m => a -> m a
return SortImportsRule
NoImportSort
    parseJSON (JSON.Bool Bool
True) = SortImportsRule -> Parser SortImportsRule
forall (m :: * -> *) a. Monad m => a -> m a
return SortImportsRule
SortImportsByPrefix
    parseJSON Value
v = [ImportsGroup] -> SortImportsRule
SortImportsByGroups ([ImportsGroup] -> SortImportsRule)
-> Parser [ImportsGroup] -> Parser SortImportsRule
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [ImportsGroup]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

instance ToJSON DeclarationConstruct where
    toJSON :: DeclarationConstruct -> Value
toJSON = Options -> DeclarationConstruct -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
enumOptions Int
4)

instance FromJSON DeclarationConstruct where
    parseJSON :: Value -> Parser DeclarationConstruct
parseJSON = Options -> Value -> Parser DeclarationConstruct
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
enumOptions Int
4)

instance ToJSON OptionConfig where
    toJSON :: OptionConfig -> Value
toJSON = Options -> OptionConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
9)

instance FromJSON OptionConfig where
    parseJSON :: Value -> Parser OptionConfig
parseJSON = Options -> Value -> Parser OptionConfig
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
9)

instance ToJSON Config where
    toJSON :: Config -> Value
toJSON = Options -> Config -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Int -> Options
recordOptions Int
3)

instance FromJSON Config where
    parseJSON :: Value -> Parser Config
parseJSON = Options -> Value -> Parser Config
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Int -> Options
recordOptions Int
3)