| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Distribution.FieldGrammar.Newtypes
Description
This module provides newtype wrappers to be used with Distribution.FieldGrammar.
Synopsis
- alaList :: sep -> [a] -> List sep (Identity a) a
- alaList' :: sep -> (a -> b) -> [a] -> List sep b a
- data CommaVCat = CommaVCat
- data CommaFSep = CommaFSep
- data VCat = VCat
- data FSep = FSep
- data NoCommaFSep = NoCommaFSep
- class Sep sep where- prettySep :: Proxy sep -> [Doc] -> Doc
- parseSep :: CabalParsing m => Proxy sep -> m a -> m [a]
- parseSepNE :: CabalParsing m => Proxy sep -> m a -> m (NonEmpty a)
 
- data List sep b a
- alaSet :: sep -> Set a -> Set' sep (Identity a) a
- alaSet' :: sep -> (a -> b) -> Set a -> Set' sep b a
- data Set' sep b a
- alaNonEmpty :: sep -> NonEmpty a -> NonEmpty' sep (Identity a) a
- alaNonEmpty' :: sep -> (a -> b) -> NonEmpty a -> NonEmpty' sep b a
- data NonEmpty' sep b a
- newtype SpecVersion = SpecVersion {}
- newtype TestedWith = TestedWith {}
- newtype SpecLicense = SpecLicense {}
- newtype Token = Token {}
- newtype Token' = Token' {}
- newtype MQuoted a = MQuoted {- getMQuoted :: a
 
- newtype FilePathNT = FilePathNT {}
List
Modifiers
data NoCommaFSep Source #
Paragraph fill list without commas. Displayed with fsep.
Constructors
| NoCommaFSep | 
Instances
| Sep NoCommaFSep Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods prettySep :: Proxy NoCommaFSep -> [Doc] -> Doc Source # parseSep :: CabalParsing m => Proxy NoCommaFSep -> m a -> m [a] Source # parseSepNE :: CabalParsing m => Proxy NoCommaFSep -> m a -> m (NonEmpty a) Source # | |
Methods
prettySep :: Proxy sep -> [Doc] -> Doc Source #
parseSep :: CabalParsing m => Proxy sep -> m a -> m [a] Source #
parseSepNE :: CabalParsing m => Proxy sep -> m a -> m (NonEmpty a) Source #
Instances
| Sep CommaFSep Source # | |
| Sep CommaVCat Source # | |
| Sep FSep Source # | |
| Sep NoCommaFSep Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods prettySep :: Proxy NoCommaFSep -> [Doc] -> Doc Source # parseSep :: CabalParsing m => Proxy NoCommaFSep -> m a -> m [a] Source # parseSepNE :: CabalParsing m => Proxy NoCommaFSep -> m a -> m (NonEmpty a) Source # | |
| Sep VCat Source # | |
Type
List separated with optional commas. Displayed with sep, arguments of
 type a are parsed and pretty-printed as b.
Instances
| Newtype [a] (List sep wrapper a) Source # | |
| (Newtype a b, Sep sep, Parsec b) => Parsec (List sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m (List sep b a) Source # | |
| (Newtype a b, Sep sep, Pretty b) => Pretty (List sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
Set
alaSet :: sep -> Set a -> Set' sep (Identity a) a Source #
alaSet and alaSet' are simply Set' constructor, with additional phantom
 arguments to constrain the resulting type
>>>:t alaSet VCatalaSet VCat :: Set a -> Set' VCat (Identity a) a
>>>:t alaSet' FSep TokenalaSet' FSep Token :: Set String -> Set' FSep Token String
>>>unpack' (alaSet' FSep Token) <$> eitherParsec "foo bar foo"Right (fromList ["bar","foo"])
Since: 3.2.0.0
alaSet' :: sep -> (a -> b) -> Set a -> Set' sep b a Source #
More general version of alaSet.
Since: 3.2.0.0
Instances
| Newtype (Set a) (Set' sep wrapper a) Source # | |
| (Newtype a b, Ord a, Sep sep, Parsec b) => Parsec (Set' sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m (Set' sep b a) Source # | |
| (Newtype a b, Sep sep, Pretty b) => Pretty (Set' sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
NonEmpty
alaNonEmpty :: sep -> NonEmpty a -> NonEmpty' sep (Identity a) a Source #
alaNonEmpty and alaNonEmpty' are simply NonEmpty' constructor, with additional phantom
 arguments to constrain the resulting type
>>>:t alaNonEmpty VCatalaNonEmpty VCat :: NonEmpty a -> NonEmpty' VCat (Identity a) a
>>>unpack' (alaNonEmpty' FSep Token) <$> eitherParsec "foo bar foo"Right ("foo" :| ["bar","foo"])
Since: 3.2.0.0
alaNonEmpty' :: sep -> (a -> b) -> NonEmpty a -> NonEmpty' sep b a Source #
More general version of alaNonEmpty.
Since: 3.2.0.0
data NonEmpty' sep b a Source #
Instances
| Newtype (NonEmpty a) (NonEmpty' sep wrapper a) Source # | |
| (Newtype a b, Sep sep, Parsec b) => Parsec (NonEmpty' sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m (NonEmpty' sep b a) Source # | |
| (Newtype a b, Sep sep, Pretty b) => Pretty (NonEmpty' sep b a) Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
Version & License
newtype SpecVersion Source #
Version range or just version, i.e. cabal-version field.
There are few things to consider:
- Starting with 2.2 the cabal-version field should be the first field in the
   file and only exact version is accepted. Therefore if we get e.g.
   >= 2.2, we fail. See https://github.com/haskell/cabal/issues/4899
We have this newtype, as writing Parsec and Pretty instances for CabalSpecVersion would cause cycle in modules: Version -> CabalSpecVersion -> Parsec -> ...
Constructors
| SpecVersion | |
| Fields | |
Instances
| Parsec SpecVersion Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m SpecVersion Source # | |
| Pretty SpecVersion Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pretty :: SpecVersion -> Doc Source # prettyVersioned :: CabalSpecVersion -> SpecVersion -> Doc Source # | |
| Show SpecVersion Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods showsPrec :: Int -> SpecVersion -> ShowS # show :: SpecVersion -> String # showList :: [SpecVersion] -> ShowS # | |
| Eq SpecVersion Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
| Newtype CabalSpecVersion SpecVersion Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pack :: CabalSpecVersion -> SpecVersion Source # unpack :: SpecVersion -> CabalSpecVersion Source # | |
newtype TestedWith Source #
Version range or just version
Constructors
| TestedWith | |
| Fields | |
Instances
| Parsec TestedWith Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m TestedWith Source # | |
| Pretty TestedWith Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pretty :: TestedWith -> Doc Source # prettyVersioned :: CabalSpecVersion -> TestedWith -> Doc Source # | |
| Newtype (CompilerFlavor, VersionRange) TestedWith Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pack :: (CompilerFlavor, VersionRange) -> TestedWith Source # unpack :: TestedWith -> (CompilerFlavor, VersionRange) Source # | |
newtype SpecLicense Source #
SPDX License expression or legacy license
Constructors
| SpecLicense | |
| Fields | |
Instances
| Parsec SpecLicense Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m SpecLicense Source # | |
| Pretty SpecLicense Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pretty :: SpecLicense -> Doc Source # prettyVersioned :: CabalSpecVersion -> SpecLicense -> Doc Source # | |
| Show SpecLicense Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods showsPrec :: Int -> SpecLicense -> ShowS # show :: SpecLicense -> String # showList :: [SpecLicense] -> ShowS # | |
| Eq SpecLicense Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
| Newtype (Either License License) SpecLicense Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |
Identifiers
Haskell string or [^ ,]+
Haskell string or [^ ]+
Either "quoted" or un-quoted.
Constructors
| MQuoted | |
| Fields 
 | |
newtype FilePathNT Source #
Filepath are parsed as Token.
Constructors
| FilePathNT | |
| Fields | |
Instances
| Parsec FilePathNT Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods parsec :: CabalParsing m => m FilePathNT Source # | |
| Pretty FilePathNT Source # | |
| Defined in Distribution.FieldGrammar.Newtypes Methods pretty :: FilePathNT -> Doc Source # prettyVersioned :: CabalSpecVersion -> FilePathNT -> Doc Source # | |
| Newtype String FilePathNT Source # | |
| Defined in Distribution.FieldGrammar.Newtypes | |