Cabal-2.2.0.1: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Parsec.Newtypes

Contents

Description

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

Synopsis

List

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

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 #

More general version of alaList.

Modifiers

data CommaVCat #

Vertical list with commas. Displayed with vcat

Constructors

CommaVCat 

data CommaFSep #

Paragraph fill list with commas. Displayed with fsep

Constructors

CommaFSep 

data VCat #

Vertical list with optional commas. Displayed with vcat.

Constructors

VCat 

data FSep #

Paragraph fill list with optional commas. Displayed with fsep.

Constructors

FSep 

data NoCommaFSep #

Paragraph fill list without commas. Displayed with fsep.

Constructors

NoCommaFSep 

Type

data List sep b a #

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

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

Methods

pretty :: List sep b a -> Doc #

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

Methods

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

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

Methods

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

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

Version & License

newtype SpecVersion #

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

There are few things to consider:

newtype TestedWith #

Version range or just version

Instances
Pretty TestedWith # 
Instance details

Methods

pretty :: TestedWith -> Doc #

Parsec TestedWith # 
Instance details

Methods

parsec :: CabalParsing m => m TestedWith #

Newtype TestedWith (CompilerFlavor, VersionRange) # 
Instance details

newtype SpecLicense #

SPDX License expression or legacy license

Instances
Pretty SpecLicense # 
Instance details

Methods

pretty :: SpecLicense -> Doc #

Parsec SpecLicense # 
Instance details

Methods

parsec :: CabalParsing m => m SpecLicense #

Newtype SpecLicense (Either License License) # 
Instance details

Identifiers

newtype Token #

Haskell string or [^ ,]+

Constructors

Token 

Fields

Instances
Pretty Token # 
Instance details

Methods

pretty :: Token -> Doc #

Parsec Token # 
Instance details

Methods

parsec :: CabalParsing m => m Token #

Newtype Token String # 
Instance details

Methods

pack :: String -> Token #

unpack :: Token -> String #

newtype Token' #

Haskell string or [^ ]+

Constructors

Token' 

Fields

Instances
Pretty Token' # 
Instance details

Methods

pretty :: Token' -> Doc #

Parsec Token' # 
Instance details

Methods

parsec :: CabalParsing m => m Token' #

Newtype Token' String # 
Instance details

Methods

pack :: String -> Token' #

unpack :: Token' -> String #

newtype MQuoted a #

Either "quoted" or un-quoted.

Constructors

MQuoted 

Fields

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

Methods

pretty :: MQuoted a -> Doc #

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

Methods

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

Newtype (MQuoted a) a # 
Instance details

Methods

pack :: a -> MQuoted a #

unpack :: MQuoted a -> a #

newtype FreeText #

This is almost many anyChar, but it

  • trims whitespace from ends of the lines,
  • converts lines with only single dot into empty line.

Constructors

FreeText 

Fields

Instances
Pretty FreeText # 
Instance details

Methods

pretty :: FreeText -> Doc #

Parsec FreeText # 
Instance details

Methods

parsec :: CabalParsing m => m FreeText #

Newtype FreeText String # 
Instance details

newtype FilePathNT #

Filepath are parsed as Token.

Constructors

FilePathNT 
Instances
Pretty FilePathNT # 
Instance details

Methods

pretty :: FilePathNT -> Doc #

Parsec FilePathNT # 
Instance details

Methods

parsec :: CabalParsing m => m FilePathNT #

Newtype FilePathNT String # 
Instance details