{-# LANGUAGE TypeApplications #-}
module CabalGild.Unstable.Action.FormatFields where
import qualified CabalGild.Unstable.Extra.FieldLine as FieldLine
import qualified CabalGild.Unstable.Extra.Name as Name
import qualified CabalGild.Unstable.Extra.SectionArg as SectionArg
import qualified CabalGild.Unstable.Extra.String as String
import qualified CabalGild.Unstable.Type.Condition as Condition
import qualified CabalGild.Unstable.Type.Dependency as Dependency
import qualified CabalGild.Unstable.Type.ExeDependency as ExeDependency
import qualified CabalGild.Unstable.Type.Extension as Extension
import qualified CabalGild.Unstable.Type.ForeignLibOption as ForeignLibOption
import qualified CabalGild.Unstable.Type.Language as Language
import qualified CabalGild.Unstable.Type.LegacyExeDependency as LegacyExeDependency
import qualified CabalGild.Unstable.Type.Mixin as Mixin
import qualified CabalGild.Unstable.Type.ModuleReexport as ModuleReexport
import qualified CabalGild.Unstable.Type.PkgconfigDependency as PkgconfigDependency
import qualified CabalGild.Unstable.Type.SomeParsecParser as SPP
import qualified CabalGild.Unstable.Type.TestedWith as TestedWith
import qualified CabalGild.Unstable.Type.Variable as Variable
import qualified Data.ByteString as ByteString
import qualified Data.Functor.Identity as Identity
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import qualified Distribution.CabalSpecVersion as CabalSpecVersion
import qualified Distribution.FieldGrammar.Newtypes as Newtypes
import qualified Distribution.Fields as Fields
import qualified Distribution.ModuleName as ModuleName
import qualified Distribution.Parsec as Parsec
import qualified Distribution.Parsec.FieldLineStream as FieldLineStream
import qualified Text.PrettyPrint as PrettyPrint
run ::
(Applicative m) =>
CabalSpecVersion.CabalSpecVersion ->
([Fields.Field (p, [c])], [c]) ->
m ([Fields.Field (p, [c])], [c])
run :: forall (m :: * -> *) p c.
Applicative m =>
CabalSpecVersion
-> ([Field (p, [c])], [c]) -> m ([Field (p, [c])], [c])
run CabalSpecVersion
csv ([Field (p, [c])]
fs, [c]
cs) = ([Field (p, [c])], [c]) -> m ([Field (p, [c])], [c])
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Field (p, [c]) -> Field (p, [c]))
-> [Field (p, [c])] -> [Field (p, [c])]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CabalSpecVersion -> Field (p, [c]) -> Field (p, [c])
forall p c. CabalSpecVersion -> Field (p, [c]) -> Field (p, [c])
field CabalSpecVersion
csv) [Field (p, [c])]
fs, [c]
cs)
field ::
CabalSpecVersion.CabalSpecVersion ->
Fields.Field (p, [c]) ->
Fields.Field (p, [c])
field :: forall p c. CabalSpecVersion -> Field (p, [c]) -> Field (p, [c])
field CabalSpecVersion
csv Field (p, [c])
f = case Field (p, [c])
f of
Fields.Field Name (p, [c])
n [FieldLine (p, [c])]
fls ->
let position :: p
position =
p -> (FieldLine (p, [c]) -> p) -> Maybe (FieldLine (p, [c])) -> p
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ((p, [c]) -> p
forall a b. (a, b) -> a
fst ((p, [c]) -> p) -> (p, [c]) -> p
forall a b. (a -> b) -> a -> b
$ Name (p, [c]) -> (p, [c])
forall a. Name a -> a
Name.annotation Name (p, [c])
n) ((p, [c]) -> p
forall a b. (a, b) -> a
fst ((p, [c]) -> p)
-> (FieldLine (p, [c]) -> (p, [c])) -> FieldLine (p, [c]) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLine (p, [c]) -> (p, [c])
forall a. FieldLine a -> a
FieldLine.annotation) (Maybe (FieldLine (p, [c])) -> p)
-> Maybe (FieldLine (p, [c])) -> p
forall a b. (a -> b) -> a -> b
$
[FieldLine (p, [c])] -> Maybe (FieldLine (p, [c]))
forall a. [a] -> Maybe a
Maybe.listToMaybe [FieldLine (p, [c])]
fls
in Name (p, [c]) -> [FieldLine (p, [c])] -> Field (p, [c])
forall ann. Name ann -> [FieldLine ann] -> Field ann
Fields.Field Name (p, [c])
n ([FieldLine (p, [c])] -> Field (p, [c]))
-> [FieldLine (p, [c])] -> Field (p, [c])
forall a b. (a -> b) -> a -> b
$ case FieldName
-> Map FieldName SomeParsecParser -> Maybe SomeParsecParser
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Name (p, [c]) -> FieldName
forall a. Name a -> FieldName
Name.value Name (p, [c])
n) Map FieldName SomeParsecParser
parsers of
Maybe SomeParsecParser
Nothing -> p -> [FieldLine (p, [c])] -> [FieldLine (p, [c])]
forall p c. p -> [FieldLine (p, [c])] -> [FieldLine (p, [c])]
floatComments p
position [FieldLine (p, [c])]
fls
Just SomeParsecParser
spp -> CabalSpecVersion
-> p
-> [FieldLine (p, [c])]
-> SomeParsecParser
-> [FieldLine (p, [c])]
forall p c.
CabalSpecVersion
-> p
-> [FieldLine (p, [c])]
-> SomeParsecParser
-> [FieldLine (p, [c])]
fieldLines CabalSpecVersion
csv p
position [FieldLine (p, [c])]
fls SomeParsecParser
spp
Fields.Section Name (p, [c])
n [SectionArg (p, [c])]
sas [Field (p, [c])]
fs ->
let result :: Either ParseError (Condition Variable)
result =
CabalSpecVersion
-> ParsecParser (Condition Variable)
-> String
-> FieldLineStream
-> Either ParseError (Condition Variable)
forall a.
CabalSpecVersion
-> ParsecParser a
-> String
-> FieldLineStream
-> Either ParseError a
Parsec.runParsecParser' CabalSpecVersion
csv (ParsecParser Variable -> ParsecParser (Condition Variable)
forall a. ParsecParser a -> ParsecParser (Condition a)
Condition.parseCondition ParsecParser Variable
forall (m :: * -> *). CabalParsing m => m Variable
Variable.parseVariable) String
"<conditional>"
(FieldLineStream -> Either ParseError (Condition Variable))
-> ([FieldName] -> FieldLineStream)
-> [FieldName]
-> Either ParseError (Condition Variable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> FieldLineStream
FieldLineStream.fieldLineStreamFromBS
(FieldName -> FieldLineStream)
-> ([FieldName] -> FieldName) -> [FieldName] -> FieldLineStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> [FieldName] -> FieldName
ByteString.intercalate (Word8 -> FieldName
ByteString.singleton Word8
0x20)
([FieldName] -> Either ParseError (Condition Variable))
-> [FieldName] -> Either ParseError (Condition Variable)
forall a b. (a -> b) -> a -> b
$ (SectionArg (p, [c]) -> FieldName)
-> [SectionArg (p, [c])] -> [FieldName]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SectionArg (p, [c]) -> FieldName
forall a. SectionArg a -> FieldName
SectionArg.value [SectionArg (p, [c])]
sas
position :: p
position =
(p, [c]) -> p
forall a b. (a, b) -> a
fst
((p, [c]) -> p)
-> (Maybe (SectionArg (p, [c])) -> (p, [c]))
-> Maybe (SectionArg (p, [c]))
-> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (p, [c])
-> (SectionArg (p, [c]) -> (p, [c]))
-> Maybe (SectionArg (p, [c]))
-> (p, [c])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Name (p, [c]) -> (p, [c])
forall a. Name a -> a
Name.annotation Name (p, [c])
n) SectionArg (p, [c]) -> (p, [c])
forall a. SectionArg a -> a
SectionArg.annotation
(Maybe (SectionArg (p, [c])) -> p)
-> Maybe (SectionArg (p, [c])) -> p
forall a b. (a -> b) -> a -> b
$ [SectionArg (p, [c])] -> Maybe (SectionArg (p, [c]))
forall a. [a] -> Maybe a
Maybe.listToMaybe [SectionArg (p, [c])]
sas
newSas :: [SectionArg (p, [c])]
newSas =
if CabalSpecVersion -> Name (p, [c]) -> Bool
forall p. CabalSpecVersion -> Name p -> Bool
isConditional CabalSpecVersion
csv Name (p, [c])
n
then case Either ParseError (Condition Variable)
result of
Left ParseError
_ -> [SectionArg (p, [c])]
sas
Right Condition Variable
c ->
SectionArg (p, [c]) -> [SectionArg (p, [c])]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(SectionArg (p, [c]) -> [SectionArg (p, [c])])
-> (Doc -> SectionArg (p, [c])) -> Doc -> [SectionArg (p, [c])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (p, [c]) -> FieldName -> SectionArg (p, [c])
forall ann. ann -> FieldName -> SectionArg ann
Fields.SecArgName (p
position, [])
(FieldName -> SectionArg (p, [c]))
-> (Doc -> FieldName) -> Doc -> SectionArg (p, [c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FieldName
String.toUtf8
(String -> FieldName) -> (Doc -> String) -> Doc -> FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Style -> Doc -> String
PrettyPrint.renderStyle Style
style
(Doc -> [SectionArg (p, [c])]) -> Doc -> [SectionArg (p, [c])]
forall a b. (a -> b) -> a -> b
$ (Variable -> Doc) -> Condition Variable -> Doc
forall a. (a -> Doc) -> Condition a -> Doc
Condition.prettyCondition Variable -> Doc
Variable.prettyVariable Condition Variable
c
else [SectionArg (p, [c])]
sas
in Name (p, [c])
-> [SectionArg (p, [c])] -> [Field (p, [c])] -> Field (p, [c])
forall ann.
Name ann -> [SectionArg ann] -> [Field ann] -> Field ann
Fields.Section Name (p, [c])
n [SectionArg (p, [c])]
newSas ([Field (p, [c])] -> Field (p, [c]))
-> [Field (p, [c])] -> Field (p, [c])
forall a b. (a -> b) -> a -> b
$ (Field (p, [c]) -> Field (p, [c]))
-> [Field (p, [c])] -> [Field (p, [c])]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CabalSpecVersion -> Field (p, [c]) -> Field (p, [c])
forall p c. CabalSpecVersion -> Field (p, [c]) -> Field (p, [c])
field CabalSpecVersion
csv) [Field (p, [c])]
fs
isConditional :: CabalSpecVersion.CabalSpecVersion -> Fields.Name p -> Bool
isConditional :: forall p. CabalSpecVersion -> Name p -> Bool
isConditional CabalSpecVersion
csv Name p
n =
Name p -> Bool
forall a. Name a -> Bool
Name.isIf Name p
n
Bool -> Bool -> Bool
|| CabalSpecVersion -> Name p -> Bool
forall p. CabalSpecVersion -> Name p -> Bool
Name.isElif CabalSpecVersion
csv Name p
n
fieldLines ::
CabalSpecVersion.CabalSpecVersion ->
p ->
[Fields.FieldLine (p, [c])] ->
SPP.SomeParsecParser ->
[Fields.FieldLine (p, [c])]
fieldLines :: forall p c.
CabalSpecVersion
-> p
-> [FieldLine (p, [c])]
-> SomeParsecParser
-> [FieldLine (p, [c])]
fieldLines CabalSpecVersion
csv p
position [FieldLine (p, [c])]
fls SPP.SomeParsecParser {parsec :: ()
SPP.parsec = ParsecParser a
parsec, pretty :: ()
SPP.pretty = CabalSpecVersion -> a -> Doc
pretty} =
case CabalSpecVersion
-> ParsecParser a
-> String
-> FieldLineStream
-> Either ParseError a
forall a.
CabalSpecVersion
-> ParsecParser a
-> String
-> FieldLineStream
-> Either ParseError a
Parsec.runParsecParser' CabalSpecVersion
csv ParsecParser a
parsec String
"" (FieldLineStream -> Either ParseError a)
-> FieldLineStream -> Either ParseError a
forall a b. (a -> b) -> a -> b
$ [FieldLine (p, [c])] -> FieldLineStream
forall a. [FieldLine a] -> FieldLineStream
FieldLine.toFieldLineStream [FieldLine (p, [c])]
fls of
Left ParseError
_ -> p -> [FieldLine (p, [c])] -> [FieldLine (p, [c])]
forall p c. p -> [FieldLine (p, [c])] -> [FieldLine (p, [c])]
floatComments p
position [FieldLine (p, [c])]
fls
Right a
r ->
(Bool -> String -> FieldLine (p, [c]))
-> [Bool] -> [String] -> [FieldLine (p, [c])]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(\Bool
b String
l -> (p, [c]) -> FieldName -> FieldLine (p, [c])
forall ann. ann -> FieldName -> FieldLine ann
Fields.FieldLine (p
position, if Bool
b then [FieldLine (p, [c])] -> [c]
forall p c. [FieldLine (p, [c])] -> [c]
collectComments [FieldLine (p, [c])]
fls else []) (FieldName -> FieldLine (p, [c]))
-> FieldName -> FieldLine (p, [c])
forall a b. (a -> b) -> a -> b
$ String -> FieldName
String.toUtf8 String
l)
(Bool
True Bool -> [Bool] -> [Bool]
forall a. a -> [a] -> [a]
: Bool -> [Bool]
forall a. a -> [a]
repeat Bool
False)
([String] -> [FieldLine (p, [c])])
-> (Doc -> [String]) -> Doc -> [FieldLine (p, [c])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
(String -> [String]) -> (Doc -> String) -> Doc -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Style -> Doc -> String
PrettyPrint.renderStyle Style
style
(Doc -> [FieldLine (p, [c])]) -> Doc -> [FieldLine (p, [c])]
forall a b. (a -> b) -> a -> b
$ CabalSpecVersion -> a -> Doc
pretty CabalSpecVersion
csv a
r
floatComments ::
p ->
[Fields.FieldLine (p, [c])] ->
[Fields.FieldLine (p, [c])]
p
p [FieldLine (p, [c])]
fls =
(Bool -> FieldLine (p, [c]) -> FieldLine (p, [c]))
-> [Bool] -> [FieldLine (p, [c])] -> [FieldLine (p, [c])]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(\Bool
b -> (p, [c]) -> FieldName -> FieldLine (p, [c])
forall ann. ann -> FieldName -> FieldLine ann
Fields.FieldLine (p
p, if Bool
b then [FieldLine (p, [c])] -> [c]
forall p c. [FieldLine (p, [c])] -> [c]
collectComments [FieldLine (p, [c])]
fls else []) (FieldName -> FieldLine (p, [c]))
-> (FieldLine (p, [c]) -> FieldName)
-> FieldLine (p, [c])
-> FieldLine (p, [c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLine (p, [c]) -> FieldName
forall a. FieldLine a -> FieldName
FieldLine.value)
(Bool
True Bool -> [Bool] -> [Bool]
forall a. a -> [a] -> [a]
: Bool -> [Bool]
forall a. a -> [a]
repeat Bool
False)
[FieldLine (p, [c])]
fls
collectComments :: [Fields.FieldLine (p, [c])] -> [c]
= (FieldLine (p, [c]) -> [c]) -> [FieldLine (p, [c])] -> [c]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((p, [c]) -> [c]
forall a b. (a, b) -> b
snd ((p, [c]) -> [c])
-> (FieldLine (p, [c]) -> (p, [c])) -> FieldLine (p, [c]) -> [c]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLine (p, [c]) -> (p, [c])
forall a. FieldLine a -> a
FieldLine.annotation)
style :: PrettyPrint.Style
style :: Style
style =
PrettyPrint.Style
{ mode :: Mode
PrettyPrint.mode = Mode
PrettyPrint.PageMode,
lineLength :: Int
PrettyPrint.lineLength = Int
0,
ribbonsPerLine :: Float
PrettyPrint.ribbonsPerLine = Float
1
}
parsers :: Map.Map Fields.FieldName SPP.SomeParsecParser
parsers :: Map FieldName SomeParsecParser
parsers =
let (=:) :: String -> SPP.SomeParsecParser -> (Fields.FieldName, SPP.SomeParsecParser)
=: :: String -> SomeParsecParser -> (FieldName, SomeParsecParser)
(=:) = (,) (FieldName -> SomeParsecParser -> (FieldName, SomeParsecParser))
-> (String -> FieldName)
-> String
-> SomeParsecParser
-> (FieldName, SomeParsecParser)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FieldName
String.toUtf8
in [(FieldName, SomeParsecParser)] -> Map FieldName SomeParsecParser
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ String
"asm-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"asm-sources" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"autogen-includes" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"autogen-modules" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @(Newtypes.MQuoted ModuleName.ModuleName),
String
"build-depends" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaVCat @(Identity.Identity Dependency.Dependency),
String
"build-tool-depends" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaFSep @(Identity.Identity ExeDependency.ExeDependency),
String
"build-tools" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaFSep @(Identity.Identity LegacyExeDependency.LegacyExeDependency),
String
"c-sources" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"cc-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"cmm-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"cmm-sources" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"code-generators" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.CommaFSep @Newtypes.Token,
String
"cpp-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"cxx-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"cxx-sources" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"data-files" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"default-extensions" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Newtypes.MQuoted Extension.Extension),
String
"exposed-modules" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @(Newtypes.MQuoted ModuleName.ModuleName),
String
"extensions" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Newtypes.MQuoted Extension.Extension),
String
"extra-bundled-libraries" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-doc-files" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"extra-dynamic-library-flavours" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-framework-dirs" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"extra-ghci-libraries" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-lib-dirs-static" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"extra-lib-dirs" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"extra-libraries-static" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-libraries" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-library-flavours" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.Token,
String
"extra-source-files" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"extra-tmp-files" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"frameworks" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.Token,
String
"ghc-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"ghc-prof-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"ghc-shared-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"ghcjs-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"ghcjs-prof-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"ghcjs-shared-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"hs-source-dirs" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.FSep @Newtypes.FilePathNT,
String
"hsc2hs-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"include-dirs" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"includes" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"install-includes" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"js-sources" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @Newtypes.FilePathNT,
String
"ld-options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (List s b a), Pretty (List s b a)) =>
SomeParsecParser
SPP.list @Newtypes.NoCommaFSep @Newtypes.Token',
String
"license-files" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @Newtypes.FilePathNT,
String
"mixins" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaVCat @(Identity.Identity Mixin.Mixin),
String
"options" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Identity.Identity ForeignLibOption.ForeignLibOption),
String
"other-extensions" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Newtypes.MQuoted Extension.Extension),
String
"other-languages" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Newtypes.MQuoted Language.Language),
String
"other-modules" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @(Newtypes.MQuoted ModuleName.ModuleName),
String
"pkgconfig-depends" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaFSep @(Identity.Identity PkgconfigDependency.PkgconfigDependency),
String
"reexported-modules" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaVCat @(Identity.Identity ModuleReexport.ModuleReexport),
String
"setup-depends" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.CommaVCat @(Identity.Identity Dependency.Dependency),
String
"signatures" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @(Newtypes.MQuoted ModuleName.ModuleName),
String
"tested-with" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.FSep @(Identity.Identity TestedWith.TestedWith),
String
"virtual-modules" String -> SomeParsecParser -> (FieldName, SomeParsecParser)
=: forall s b a.
(Parsec (Set s b a), Pretty (Set s b a)) =>
SomeParsecParser
SPP.set @Newtypes.VCat @(Newtypes.MQuoted ModuleName.ModuleName)
]