Cabal-2.2.0.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Parsec.Common

Contents

Description

Module containing small types

Synopsis

Diagnostics

data PError #

Parser error.

Constructors

PError Position String 

Instances

Show PError # 
Generic PError # 

Associated Types

type Rep PError :: * -> * #

Methods

from :: PError -> Rep PError x #

to :: Rep PError x -> PError #

Binary PError # 

Methods

put :: PError -> Put #

get :: Get PError #

putList :: [PError] -> Put #

NFData PError # 

Methods

rnf :: PError -> () #

type Rep PError # 
type Rep PError = D1 * (MetaData "PError" "Distribution.Parsec.Common" "Cabal-2.2.0.0-KtVb5LuYqFjKrhxFyS8D9H" False) (C1 * (MetaCons "PError" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Position)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

data PWarning #

Parser warning.

data PWarnType #

Type of parser warning. We do classify warnings.

Different application may decide not to show some, or have fatal behaviour on others

Constructors

PWTOther

Unclassified warning

PWTUTF

Invalid UTF encoding

PWTBoolCase

true or false, not True or False

PWTVersionTag

there are version with tags

PWTNewSyntax

New syntax used, but no cabal-version: >= 1.2 specified

PWTOldSyntax

Old syntax used, and cabal-version >= 1.2 specified

PWTDeprecatedField 
PWTInvalidSubsection 
PWTUnknownField 
PWTUnknownSection 
PWTTrailingFields 
PWTExtraMainIs

extra main-is field

PWTExtraTestModule

extra test-module field

PWTExtraBenchmarkModule

extra benchmark-module field

PWTLexNBSP 
PWTLexBOM 
PWTLexTab 
PWTQuirkyCabalFile

legacy cabal file that we know how to patch

PWTDoubleDash

Double dash token, most likely it's a mistake - it's not a comment

PWTMultipleSingularField

e.g. name or version should be specified only once.

PWTBuildTypeDefault

Workaround for derive-package having build-type: Default. See https://github.com/haskell/cabal/issues/5020.

PWTVersionLeadingZeros

See https://github.com/haskell-infra/hackage-trustees/issues/128

Instances

Bounded PWarnType # 
Enum PWarnType # 
Eq PWarnType # 
Ord PWarnType # 
Show PWarnType # 
Generic PWarnType # 

Associated Types

type Rep PWarnType :: * -> * #

Binary PWarnType # 
NFData PWarnType # 

Methods

rnf :: PWarnType -> () #

type Rep PWarnType # 
type Rep PWarnType = D1 * (MetaData "PWarnType" "Distribution.Parsec.Common" "Cabal-2.2.0.0-KtVb5LuYqFjKrhxFyS8D9H" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PWTOther" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTUTF" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PWTBoolCase" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTVersionTag" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTNewSyntax" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PWTOldSyntax" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTDeprecatedField" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTInvalidSubsection" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "PWTUnknownField" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTUnknownSection" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTTrailingFields" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PWTExtraMainIs" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTExtraTestModule" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PWTExtraBenchmarkModule" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTLexNBSP" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTLexBOM" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PWTLexTab" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTQuirkyCabalFile" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTDoubleDash" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "PWTMultipleSingularField" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PWTBuildTypeDefault" PrefixI False) (U1 *)) (C1 * (MetaCons "PWTVersionLeadingZeros" PrefixI False) (U1 *)))))))

Position

data Position #

1-indexed row and column positions in a file.

Constructors

Position !Int !Int 

Instances

Eq Position # 
Ord Position # 
Show Position # 
Generic Position # 

Associated Types

type Rep Position :: * -> * #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

Binary Position # 

Methods

put :: Position -> Put #

get :: Get Position #

putList :: [Position] -> Put #

NFData Position # 

Methods

rnf :: Position -> () #

type Rep Position # 
type Rep Position = D1 * (MetaData "Position" "Distribution.Parsec.Common" "Cabal-2.2.0.0-KtVb5LuYqFjKrhxFyS8D9H" False) (C1 * (MetaCons "Position" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int))))

incPos :: Int -> Position -> Position #

Shift position by n columns to the right.

retPos :: Position -> Position #

Shift position to beginning of next row.