Cabal-3.2.1.0: A framework for packaging Haskell software
Safe HaskellNone
LanguageHaskell2010

Distribution.Parsec.Newtypes

Description

This module provides newtype wrappers to be used with Distribution.FieldGrammar.

Synopsis

List

alaList :: sep -> [a] -> List sep (Identity a) a Source #

alaList and alaList' are simply List, with additional phantom arguments to constraint the resulting type

>>> :t alaList VCat
alaList VCat :: [a] -> List VCat (Identity a) a
>>> :t alaList' FSep Token
alaList' FSep Token :: [String] -> List FSep Token String

alaList' :: sep -> (a -> b) -> [a] -> List sep b a Source #

More general version of alaList.

Modifiers

data CommaVCat Source #

Vertical list with commas. Displayed with vcat

Constructors

CommaVCat 

Instances

Instances details
Sep CommaVCat # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy CommaVCat -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy CommaVCat -> m a -> m [a] Source #

data CommaFSep Source #

Paragraph fill list with commas. Displayed with fsep

Constructors

CommaFSep 

Instances

Instances details
Sep CommaFSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy CommaFSep -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy CommaFSep -> m a -> m [a] Source #

data VCat Source #

Vertical list with optional commas. Displayed with vcat.

Constructors

VCat 

Instances

Instances details
Sep VCat # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy VCat -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy VCat -> m a -> m [a] Source #

data FSep Source #

Paragraph fill list with optional commas. Displayed with fsep.

Constructors

FSep 

Instances

Instances details
Sep FSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy FSep -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy FSep -> m a -> m [a] Source #

data NoCommaFSep Source #

Paragraph fill list without commas. Displayed with fsep.

Constructors

NoCommaFSep 

Instances

Instances details
Sep NoCommaFSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

class Sep sep where Source #

Methods

prettySep :: Proxy sep -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy sep -> m a -> m [a] Source #

Instances

Instances details
Sep NoCommaFSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

Sep FSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy FSep -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy FSep -> m a -> m [a] Source #

Sep VCat # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy VCat -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy VCat -> m a -> m [a] Source #

Sep CommaFSep # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy CommaFSep -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy CommaFSep -> m a -> m [a] Source #

Sep CommaVCat # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

prettySep :: Proxy CommaVCat -> [Doc] -> Doc Source #

parseSep :: CabalParsing m => Proxy CommaVCat -> m a -> m [a] Source #

Type

data List sep b a Source #

List separated with optional commas. Displayed with sep, arguments of type a are parsed and pretty-printed as b.

Instances

Instances details
Newtype [a] (List sep wrapper a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

pack :: [a] -> List sep wrapper a Source #

unpack :: List sep wrapper a -> [a] Source #

(Newtype a b, Sep sep, Pretty b) => Pretty (List sep b a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

pretty :: List sep b a -> Doc Source #

prettyVersioned :: CabalSpecVersion -> List sep b a -> Doc Source #

(Newtype a b, Sep sep, Parsec b) => Parsec (List sep b a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

parsec :: CabalParsing m => m (List sep b a) Source #

Set

alaSet :: sep -> Set a -> Set' sep (Identity a) a Source #

alaSet and alaSet' are simply Set' constructor, with additional phantom arguments to constraint the resulting type

>>> :t alaSet VCat
alaSet VCat :: Set a -> Set' VCat (Identity a) a
>>> :t alaSet' FSep Token
alaSet' FSep Token :: Set String -> Set' FSep Token String
>>> unpack' (alaSet' FSep Token) <$> eitherParsec "foo bar foo"
Right (fromList ["bar","foo"])

Since: Cabal-3.2.0.0

alaSet' :: sep -> (a -> b) -> Set a -> Set' sep b a Source #

More general version of alaSet.

Since: Cabal-3.2.0.0

data Set' sep b a Source #

Like List, but for Set.

Since: Cabal-3.2.0.0

Instances

Instances details
Newtype (Set a) (Set' sep wrapper a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

pack :: Set a -> Set' sep wrapper a Source #

unpack :: Set' sep wrapper a -> Set a Source #

(Newtype a b, Sep sep, Pretty b) => Pretty (Set' sep b a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

pretty :: Set' sep b a -> Doc Source #

prettyVersioned :: CabalSpecVersion -> Set' sep b a -> Doc Source #

(Newtype a b, Ord a, Sep sep, Parsec b) => Parsec (Set' sep b a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

parsec :: CabalParsing m => m (Set' sep b a) Source #

Version & License

newtype SpecVersion Source #

Version range or just version, i.e. cabal-version field.

There are few things to consider:

newtype SpecLicense Source #

SPDX License expression or legacy license

Identifiers

newtype Token Source #

Haskell string or [^ ,]+

Constructors

Token 

Fields

Instances

Instances details
Pretty Token # 
Instance details

Defined in Distribution.Parsec.Newtypes

Parsec Token # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

parsec :: CabalParsing m => m Token Source #

Newtype String Token # 
Instance details

Defined in Distribution.Parsec.Newtypes

newtype Token' Source #

Haskell string or [^ ]+

Constructors

Token' 

Fields

Instances

Instances details
Pretty Token' # 
Instance details

Defined in Distribution.Parsec.Newtypes

Parsec Token' # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

parsec :: CabalParsing m => m Token' Source #

Newtype String Token' # 
Instance details

Defined in Distribution.Parsec.Newtypes

newtype MQuoted a Source #

Either "quoted" or un-quoted.

Constructors

MQuoted 

Fields

Instances

Instances details
Newtype a (MQuoted a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

pack :: a -> MQuoted a Source #

unpack :: MQuoted a -> a Source #

Pretty a => Pretty (MQuoted a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Parsec a => Parsec (MQuoted a) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Methods

parsec :: CabalParsing m => m (MQuoted a) Source #

newtype FilePathNT Source #

Filepath are parsed as Token.

Constructors

FilePathNT