haskell-src-1.0.4.1: Support for manipulating Haskell source code
Copyright(c) The GHC Team 1997-2000
LicenseBSD-3-Clause
MaintainerAndreas Abel
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Syntax

Description

A suite of datatypes describing the abstract syntax of Haskell 98 plus a few extensions:

  • multi-parameter type classes
  • parameters of type class assertions are unrestricted

For GHC, we also derive Typeable and Data for all types.

Synopsis

Modules

data HsModule Source #

A Haskell source module.

Instances

Instances details
Data HsModule Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule -> c HsModule

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsModule

toConstr :: HsModule -> Constr

dataTypeOf :: HsModule -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsModule)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsModule)

gmapT :: (forall b. Data b => b -> b) -> HsModule -> HsModule

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule -> r

gmapQ :: (forall d. Data d => d -> u) -> HsModule -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule -> m HsModule

Show HsModule Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsModule -> ShowS

show :: HsModule -> String

showList :: [HsModule] -> ShowS

Eq HsModule Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsModule -> HsModule -> Bool

(/=) :: HsModule -> HsModule -> Bool

Pretty HsModule Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsModule -> Doc

prettyPrec :: Int -> HsModule -> Doc

data HsExportSpec Source #

Export specification.

Constructors

HsEVar HsQName

Variable.

HsEAbs HsQName

T: A class or datatype exported abstractly, or a type synonym.

HsEThingAll HsQName

T(..): A class exported with all of its methods, or a datatype exported with all of its constructors.

HsEThingWith HsQName [HsCName]

T(C_1,...,C_n): A class exported with some of its methods, or a datatype exported with some of its constructors.

HsEModuleContents Module

module M: Re-export a module.

Instances

Instances details
Data HsExportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExportSpec -> c HsExportSpec

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsExportSpec

toConstr :: HsExportSpec -> Constr

dataTypeOf :: HsExportSpec -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsExportSpec)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsExportSpec)

gmapT :: (forall b. Data b => b -> b) -> HsExportSpec -> HsExportSpec

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExportSpec -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExportSpec -> r

gmapQ :: (forall d. Data d => d -> u) -> HsExportSpec -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExportSpec -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExportSpec -> m HsExportSpec

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExportSpec -> m HsExportSpec

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExportSpec -> m HsExportSpec

Show HsExportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsExportSpec -> ShowS

show :: HsExportSpec -> String

showList :: [HsExportSpec] -> ShowS

Eq HsExportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsExportSpec -> HsExportSpec -> Bool

(/=) :: HsExportSpec -> HsExportSpec -> Bool

Pretty HsExportSpec Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsExportSpec -> Doc

prettyPrec :: Int -> HsExportSpec -> Doc

data HsImportDecl Source #

Import declaration.

Constructors

HsImportDecl 

Fields

Instances

Instances details
Data HsImportDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImportDecl -> c HsImportDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImportDecl

toConstr :: HsImportDecl -> Constr

dataTypeOf :: HsImportDecl -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImportDecl)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImportDecl)

gmapT :: (forall b. Data b => b -> b) -> HsImportDecl -> HsImportDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImportDecl -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImportDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> HsImportDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImportDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImportDecl -> m HsImportDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImportDecl -> m HsImportDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImportDecl -> m HsImportDecl

Show HsImportDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsImportDecl -> ShowS

show :: HsImportDecl -> String

showList :: [HsImportDecl] -> ShowS

Eq HsImportDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsImportDecl -> HsImportDecl -> Bool

(/=) :: HsImportDecl -> HsImportDecl -> Bool

Pretty HsImportDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsImportDecl -> Doc

prettyPrec :: Int -> HsImportDecl -> Doc

data HsImportSpec Source #

Import specification.

Constructors

HsIVar HsName

Variable.

HsIAbs HsName

T: The name of a class, datatype or type synonym.

HsIThingAll HsName

T(..): A class imported with all of its methods, or a datatype imported with all of its constructors.

HsIThingWith HsName [HsCName]

T(C_1,...,C_n): A class imported with some of its methods, or a datatype imported with some of its constructors.

Instances

Instances details
Data HsImportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImportSpec -> c HsImportSpec

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImportSpec

toConstr :: HsImportSpec -> Constr

dataTypeOf :: HsImportSpec -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImportSpec)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImportSpec)

gmapT :: (forall b. Data b => b -> b) -> HsImportSpec -> HsImportSpec

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImportSpec -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImportSpec -> r

gmapQ :: (forall d. Data d => d -> u) -> HsImportSpec -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImportSpec -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImportSpec -> m HsImportSpec

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImportSpec -> m HsImportSpec

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImportSpec -> m HsImportSpec

Show HsImportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsImportSpec -> ShowS

show :: HsImportSpec -> String

showList :: [HsImportSpec] -> ShowS

Eq HsImportSpec Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsImportSpec -> HsImportSpec -> Bool

(/=) :: HsImportSpec -> HsImportSpec -> Bool

Pretty HsImportSpec Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsImportSpec -> Doc

prettyPrec :: Int -> HsImportSpec -> Doc

data HsAssoc Source #

Associativity of an operator.

Constructors

HsAssocNone

Non-associative operator (declared with infix).

HsAssocLeft

Left-associative operator (declared with infixl).

HsAssocRight

Right-associative operator (declared with infixr).

Instances

Instances details
Data HsAssoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsAssoc -> c HsAssoc

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsAssoc

toConstr :: HsAssoc -> Constr

dataTypeOf :: HsAssoc -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsAssoc)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsAssoc)

gmapT :: (forall b. Data b => b -> b) -> HsAssoc -> HsAssoc

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsAssoc -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsAssoc -> r

gmapQ :: (forall d. Data d => d -> u) -> HsAssoc -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsAssoc -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsAssoc -> m HsAssoc

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAssoc -> m HsAssoc

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAssoc -> m HsAssoc

Show HsAssoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsAssoc -> ShowS

show :: HsAssoc -> String

showList :: [HsAssoc] -> ShowS

Eq HsAssoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsAssoc -> HsAssoc -> Bool

(/=) :: HsAssoc -> HsAssoc -> Bool

Pretty HsAssoc Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsAssoc -> Doc

prettyPrec :: Int -> HsAssoc -> Doc

Declarations

data HsDecl Source #

Instances

Instances details
Data HsDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl -> c HsDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsDecl

toConstr :: HsDecl -> Constr

dataTypeOf :: HsDecl -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsDecl)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsDecl)

gmapT :: (forall b. Data b => b -> b) -> HsDecl -> HsDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> HsDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl -> m HsDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl -> m HsDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl -> m HsDecl

Show HsDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsDecl -> ShowS

show :: HsDecl -> String

showList :: [HsDecl] -> ShowS

Eq HsDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsDecl -> HsDecl -> Bool

(/=) :: HsDecl -> HsDecl -> Bool

Pretty HsDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsDecl -> Doc

prettyPrec :: Int -> HsDecl -> Doc

data HsConDecl Source #

Declaration of a data constructor.

Constructors

HsConDecl SrcLoc HsName [HsBangType]

Ordinary data constructor.

HsRecDecl SrcLoc HsName [([HsName], HsBangType)]

Record constructor.

Instances

Instances details
Data HsConDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDecl -> c HsConDecl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsConDecl

toConstr :: HsConDecl -> Constr

dataTypeOf :: HsConDecl -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsConDecl)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsConDecl)

gmapT :: (forall b. Data b => b -> b) -> HsConDecl -> HsConDecl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDecl -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDecl -> r

gmapQ :: (forall d. Data d => d -> u) -> HsConDecl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDecl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDecl -> m HsConDecl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDecl -> m HsConDecl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDecl -> m HsConDecl

Show HsConDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsConDecl -> ShowS

show :: HsConDecl -> String

showList :: [HsConDecl] -> ShowS

Eq HsConDecl Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsConDecl -> HsConDecl -> Bool

(/=) :: HsConDecl -> HsConDecl -> Bool

Pretty HsConDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsConDecl -> Doc

prettyPrec :: Int -> HsConDecl -> Doc

data HsBangType Source #

The type of a constructor argument or field, optionally including a strictness annotation.

Constructors

HsBangedTy HsType

Strict component, marked with "!".

HsUnBangedTy HsType

Non-strict component.

Instances

Instances details
Data HsBangType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBangType -> c HsBangType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsBangType

toConstr :: HsBangType -> Constr

dataTypeOf :: HsBangType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsBangType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsBangType)

gmapT :: (forall b. Data b => b -> b) -> HsBangType -> HsBangType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBangType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBangType -> r

gmapQ :: (forall d. Data d => d -> u) -> HsBangType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBangType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBangType -> m HsBangType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBangType -> m HsBangType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBangType -> m HsBangType

Show HsBangType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsBangType -> ShowS

show :: HsBangType -> String

showList :: [HsBangType] -> ShowS

Eq HsBangType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsBangType -> HsBangType -> Bool

(/=) :: HsBangType -> HsBangType -> Bool

Pretty HsBangType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsBangType -> Doc

prettyPrec :: Int -> HsBangType -> Doc

data HsMatch Source #

Clauses of a function binding.

Instances

Instances details
Data HsMatch Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatch -> c HsMatch

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsMatch

toConstr :: HsMatch -> Constr

dataTypeOf :: HsMatch -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsMatch)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsMatch)

gmapT :: (forall b. Data b => b -> b) -> HsMatch -> HsMatch

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatch -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatch -> r

gmapQ :: (forall d. Data d => d -> u) -> HsMatch -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatch -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatch -> m HsMatch

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatch -> m HsMatch

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatch -> m HsMatch

Show HsMatch Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsMatch -> ShowS

show :: HsMatch -> String

showList :: [HsMatch] -> ShowS

Eq HsMatch Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsMatch -> HsMatch -> Bool

(/=) :: HsMatch -> HsMatch -> Bool

Pretty HsMatch Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsMatch -> Doc

prettyPrec :: Int -> HsMatch -> Doc

data HsRhs Source #

The right hand side of a function or pattern binding.

Constructors

HsUnGuardedRhs HsExp

Unguarded right hand side (exp).

HsGuardedRhss [HsGuardedRhs]

Guarded right hand side (gdrhs).

Instances

Instances details
Data HsRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRhs -> c HsRhs

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsRhs

toConstr :: HsRhs -> Constr

dataTypeOf :: HsRhs -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsRhs)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsRhs)

gmapT :: (forall b. Data b => b -> b) -> HsRhs -> HsRhs

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRhs -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRhs -> r

gmapQ :: (forall d. Data d => d -> u) -> HsRhs -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRhs -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRhs -> m HsRhs

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRhs -> m HsRhs

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRhs -> m HsRhs

Show HsRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsRhs -> ShowS

show :: HsRhs -> String

showList :: [HsRhs] -> ShowS

Eq HsRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsRhs -> HsRhs -> Bool

(/=) :: HsRhs -> HsRhs -> Bool

Pretty HsRhs Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsRhs -> Doc

prettyPrec :: Int -> HsRhs -> Doc

data HsGuardedRhs Source #

A guarded right hand side | exp = exp. The first expression will be Boolean-valued.

Instances

Instances details
Data HsGuardedRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGuardedRhs -> c HsGuardedRhs

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsGuardedRhs

toConstr :: HsGuardedRhs -> Constr

dataTypeOf :: HsGuardedRhs -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsGuardedRhs)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsGuardedRhs)

gmapT :: (forall b. Data b => b -> b) -> HsGuardedRhs -> HsGuardedRhs

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedRhs -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedRhs -> r

gmapQ :: (forall d. Data d => d -> u) -> HsGuardedRhs -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGuardedRhs -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGuardedRhs -> m HsGuardedRhs

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedRhs -> m HsGuardedRhs

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedRhs -> m HsGuardedRhs

Show HsGuardedRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsGuardedRhs -> ShowS

show :: HsGuardedRhs -> String

showList :: [HsGuardedRhs] -> ShowS

Eq HsGuardedRhs Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsGuardedRhs -> HsGuardedRhs -> Bool

(/=) :: HsGuardedRhs -> HsGuardedRhs -> Bool

Pretty HsGuardedRhs Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedRhs -> Doc

prettyPrec :: Int -> HsGuardedRhs -> Doc

data HsSafety Source #

Safety level for invoking a foreign entity.

Constructors

HsSafe

Call may generate callbacks.

HsUnsafe

Call will not generate callbacks.

Instances

Instances details
Data HsSafety Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSafety -> c HsSafety

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSafety

toConstr :: HsSafety -> Constr

dataTypeOf :: HsSafety -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSafety)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSafety)

gmapT :: (forall b. Data b => b -> b) -> HsSafety -> HsSafety

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSafety -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSafety -> r

gmapQ :: (forall d. Data d => d -> u) -> HsSafety -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSafety -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSafety -> m HsSafety

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSafety -> m HsSafety

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSafety -> m HsSafety

Show HsSafety Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsSafety -> ShowS

show :: HsSafety -> String

showList :: [HsSafety] -> ShowS

Eq HsSafety Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsSafety -> HsSafety -> Bool

(/=) :: HsSafety -> HsSafety -> Bool

Ord HsSafety Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsSafety -> HsSafety -> Ordering

(<) :: HsSafety -> HsSafety -> Bool

(<=) :: HsSafety -> HsSafety -> Bool

(>) :: HsSafety -> HsSafety -> Bool

(>=) :: HsSafety -> HsSafety -> Bool

max :: HsSafety -> HsSafety -> HsSafety

min :: HsSafety -> HsSafety -> HsSafety

Pretty HsSafety Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsSafety -> Doc

prettyPrec :: Int -> HsSafety -> Doc

Class Assertions and Contexts

data HsQualType Source #

A type qualified with a context. An unqualified type has an empty context.

Instances

Instances details
Data HsQualType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQualType -> c HsQualType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsQualType

toConstr :: HsQualType -> Constr

dataTypeOf :: HsQualType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsQualType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsQualType)

gmapT :: (forall b. Data b => b -> b) -> HsQualType -> HsQualType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQualType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQualType -> r

gmapQ :: (forall d. Data d => d -> u) -> HsQualType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQualType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQualType -> m HsQualType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQualType -> m HsQualType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQualType -> m HsQualType

Show HsQualType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsQualType -> ShowS

show :: HsQualType -> String

showList :: [HsQualType] -> ShowS

Eq HsQualType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsQualType -> HsQualType -> Bool

(/=) :: HsQualType -> HsQualType -> Bool

Pretty HsQualType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQualType -> Doc

prettyPrec :: Int -> HsQualType -> Doc

type HsAsst = (HsQName, [HsType]) Source #

Class assertions. In Haskell 98, the argument would be a tyvar, but this definition allows multiple parameters, and allows them to be types.

Types

data HsType Source #

Haskell types and type constructors.

Constructors

HsTyFun HsType HsType

Function type.

HsTyTuple [HsType]

Tuple type.

HsTyApp HsType HsType

Application of a type constructor.

HsTyVar HsName

Type variable.

HsTyCon HsQName

Named type or type constructor.

Instances

Instances details
Data HsType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType -> c HsType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsType

toConstr :: HsType -> Constr

dataTypeOf :: HsType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsType)

gmapT :: (forall b. Data b => b -> b) -> HsType -> HsType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType -> r

gmapQ :: (forall d. Data d => d -> u) -> HsType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType -> m HsType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType -> m HsType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType -> m HsType

Show HsType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsType -> ShowS

show :: HsType -> String

showList :: [HsType] -> ShowS

Eq HsType Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsType -> HsType -> Bool

(/=) :: HsType -> HsType -> Bool

Pretty HsType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsType -> Doc

prettyPrec :: Int -> HsType -> Doc

Expressions

data HsExp Source #

Haskell expressions.

Notes:

  • Because it is difficult for parsers to distinguish patterns from expressions, they typically parse them in the same way and then check that they have the appropriate form. Hence the expression type includes some forms that are found only in patterns. After these checks, these constructors should not be used.
  • The parser does not take precedence and associativity into account, so it will leave HsInfixApps associated to the left.
  • The Pretty instance for HsExp does not add parentheses in printing.

Constructors

HsVar HsQName

Variable.

HsCon HsQName

Data constructor.

HsLit HsLiteral

Literal constant.

HsInfixApp HsExp HsQOp HsExp

Infix application.

HsApp HsExp HsExp

Ordinary application.

HsNegApp HsExp

Negation expression - exp.

HsLambda SrcLoc [HsPat] HsExp

Lambda expression.

HsLet [HsDecl] HsExp

Local declarations with let.

HsIf HsExp HsExp HsExp

If exp then exp else exp.

HsCase HsExp [HsAlt]

Case exp of alts.

HsDo [HsStmt]

Do-expression: The last statement in the list should be an expression.

HsTuple [HsExp]

Tuple expression.

HsList [HsExp]

List expression.

HsParen HsExp

Parenthesized expression.

HsLeftSection HsExp HsQOp

Left section (exp qop).

HsRightSection HsQOp HsExp

Right section (qop exp).

HsRecConstr HsQName [HsFieldUpdate]

Record construction expression.

HsRecUpdate HsExp [HsFieldUpdate]

Record update expression.

HsEnumFrom HsExp

Unbounded arithmetic sequence, incrementing by 1.

HsEnumFromTo HsExp HsExp

Bounded arithmetic sequence, incrementing by 1.

HsEnumFromThen HsExp HsExp

Unbounded arithmetic sequence, with first two elements given.

HsEnumFromThenTo HsExp HsExp HsExp

Bounded arithmetic sequence, with first two elements given.

HsListComp HsExp [HsStmt]

List comprehension.

HsExpTypeSig SrcLoc HsExp HsQualType

Expression type signature.

HsAsPat HsName HsExp

(patterns only)

HsWildCard

(patterns only)

HsIrrPat HsExp

(patterns only)

Instances

Instances details
Data HsExp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExp -> c HsExp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsExp

toConstr :: HsExp -> Constr

dataTypeOf :: HsExp -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsExp)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsExp)

gmapT :: (forall b. Data b => b -> b) -> HsExp -> HsExp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExp -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExp -> r

gmapQ :: (forall d. Data d => d -> u) -> HsExp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExp -> m HsExp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExp -> m HsExp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExp -> m HsExp

Show HsExp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsExp -> ShowS

show :: HsExp -> String

showList :: [HsExp] -> ShowS

Eq HsExp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsExp -> HsExp -> Bool

(/=) :: HsExp -> HsExp -> Bool

Pretty HsExp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsExp -> Doc

prettyPrec :: Int -> HsExp -> Doc

data HsStmt Source #

This type represents both stmt in a do-expression, and qual in a list comprehension.

Constructors

HsGenerator SrcLoc HsPat HsExp

A generator pat <- exp.

HsQualifier HsExp

An exp by itself: in a do-expression, an action whose result is discarded; in a list comprehension, a guard expression.

HsLetStmt [HsDecl]

Local bindings.

Instances

Instances details
Data HsStmt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmt -> c HsStmt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsStmt

toConstr :: HsStmt -> Constr

dataTypeOf :: HsStmt -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsStmt)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsStmt)

gmapT :: (forall b. Data b => b -> b) -> HsStmt -> HsStmt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmt -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmt -> r

gmapQ :: (forall d. Data d => d -> u) -> HsStmt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmt -> m HsStmt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmt -> m HsStmt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmt -> m HsStmt

Show HsStmt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsStmt -> ShowS

show :: HsStmt -> String

showList :: [HsStmt] -> ShowS

Eq HsStmt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsStmt -> HsStmt -> Bool

(/=) :: HsStmt -> HsStmt -> Bool

Pretty HsStmt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsStmt -> Doc

prettyPrec :: Int -> HsStmt -> Doc

data HsFieldUpdate Source #

An fbind in a labeled record construction or update expression.

Instances

Instances details
Data HsFieldUpdate Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsFieldUpdate -> c HsFieldUpdate

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsFieldUpdate

toConstr :: HsFieldUpdate -> Constr

dataTypeOf :: HsFieldUpdate -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsFieldUpdate)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsFieldUpdate)

gmapT :: (forall b. Data b => b -> b) -> HsFieldUpdate -> HsFieldUpdate

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldUpdate -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldUpdate -> r

gmapQ :: (forall d. Data d => d -> u) -> HsFieldUpdate -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldUpdate -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldUpdate -> m HsFieldUpdate

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldUpdate -> m HsFieldUpdate

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldUpdate -> m HsFieldUpdate

Show HsFieldUpdate Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsFieldUpdate -> ShowS

show :: HsFieldUpdate -> String

showList :: [HsFieldUpdate] -> ShowS

Eq HsFieldUpdate Source # 
Instance details

Defined in Language.Haskell.Syntax

Pretty HsFieldUpdate Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsFieldUpdate -> Doc

prettyPrec :: Int -> HsFieldUpdate -> Doc

data HsAlt Source #

An alt in a case expression.

Instances

Instances details
Data HsAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsAlt -> c HsAlt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsAlt

toConstr :: HsAlt -> Constr

dataTypeOf :: HsAlt -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsAlt)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsAlt)

gmapT :: (forall b. Data b => b -> b) -> HsAlt -> HsAlt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsAlt -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsAlt -> r

gmapQ :: (forall d. Data d => d -> u) -> HsAlt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsAlt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsAlt -> m HsAlt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAlt -> m HsAlt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAlt -> m HsAlt

Show HsAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsAlt -> ShowS

show :: HsAlt -> String

showList :: [HsAlt] -> ShowS

Eq HsAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsAlt -> HsAlt -> Bool

(/=) :: HsAlt -> HsAlt -> Bool

Pretty HsAlt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsAlt -> Doc

prettyPrec :: Int -> HsAlt -> Doc

data HsGuardedAlts Source #

Instances

Instances details
Data HsGuardedAlts Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGuardedAlts -> c HsGuardedAlts

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsGuardedAlts

toConstr :: HsGuardedAlts -> Constr

dataTypeOf :: HsGuardedAlts -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsGuardedAlts)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsGuardedAlts)

gmapT :: (forall b. Data b => b -> b) -> HsGuardedAlts -> HsGuardedAlts

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedAlts -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedAlts -> r

gmapQ :: (forall d. Data d => d -> u) -> HsGuardedAlts -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGuardedAlts -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGuardedAlts -> m HsGuardedAlts

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedAlts -> m HsGuardedAlts

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedAlts -> m HsGuardedAlts

Show HsGuardedAlts Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsGuardedAlts -> ShowS

show :: HsGuardedAlts -> String

showList :: [HsGuardedAlts] -> ShowS

Eq HsGuardedAlts Source # 
Instance details

Defined in Language.Haskell.Syntax

Pretty HsGuardedAlts Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedAlts -> Doc

prettyPrec :: Int -> HsGuardedAlts -> Doc

data HsGuardedAlt Source #

A guarded alternative | exp -> exp. The first expression will be Boolean-valued.

Instances

Instances details
Data HsGuardedAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGuardedAlt -> c HsGuardedAlt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsGuardedAlt

toConstr :: HsGuardedAlt -> Constr

dataTypeOf :: HsGuardedAlt -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsGuardedAlt)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsGuardedAlt)

gmapT :: (forall b. Data b => b -> b) -> HsGuardedAlt -> HsGuardedAlt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedAlt -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGuardedAlt -> r

gmapQ :: (forall d. Data d => d -> u) -> HsGuardedAlt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGuardedAlt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGuardedAlt -> m HsGuardedAlt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedAlt -> m HsGuardedAlt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGuardedAlt -> m HsGuardedAlt

Show HsGuardedAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsGuardedAlt -> ShowS

show :: HsGuardedAlt -> String

showList :: [HsGuardedAlt] -> ShowS

Eq HsGuardedAlt Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsGuardedAlt -> HsGuardedAlt -> Bool

(/=) :: HsGuardedAlt -> HsGuardedAlt -> Bool

Pretty HsGuardedAlt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedAlt -> Doc

prettyPrec :: Int -> HsGuardedAlt -> Doc

Patterns

data HsPat Source #

A pattern, to be matched against a value.

Constructors

HsPVar HsName

Variable.

HsPLit HsLiteral

Literal constant.

HsPNeg HsPat

Negated pattern.

HsPInfixApp HsPat HsQName HsPat

Pattern with infix data constructor.

HsPApp HsQName [HsPat]

Data constructor and argument patterns.

HsPTuple [HsPat]

Tuple pattern.

HsPList [HsPat]

List pattern.

HsPParen HsPat

Parenthesized pattern.

HsPRec HsQName [HsPatField]

Labelled pattern.

HsPAsPat HsName HsPat

@-Pattern.

HsPWildCard

Wildcard pattern (_).

HsPIrrPat HsPat

Irrefutable pattern (~).

Instances

Instances details
Data HsPat Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPat -> c HsPat

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsPat

toConstr :: HsPat -> Constr

dataTypeOf :: HsPat -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsPat)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsPat)

gmapT :: (forall b. Data b => b -> b) -> HsPat -> HsPat

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPat -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPat -> r

gmapQ :: (forall d. Data d => d -> u) -> HsPat -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPat -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPat -> m HsPat

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPat -> m HsPat

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPat -> m HsPat

Show HsPat Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsPat -> ShowS

show :: HsPat -> String

showList :: [HsPat] -> ShowS

Eq HsPat Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsPat -> HsPat -> Bool

(/=) :: HsPat -> HsPat -> Bool

Pretty HsPat Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsPat -> Doc

prettyPrec :: Int -> HsPat -> Doc

data HsPatField Source #

An fpat in a labeled record pattern.

Constructors

HsPFieldPat HsQName HsPat 

Instances

Instances details
Data HsPatField Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatField -> c HsPatField

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsPatField

toConstr :: HsPatField -> Constr

dataTypeOf :: HsPatField -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsPatField)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsPatField)

gmapT :: (forall b. Data b => b -> b) -> HsPatField -> HsPatField

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatField -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatField -> r

gmapQ :: (forall d. Data d => d -> u) -> HsPatField -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatField -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatField -> m HsPatField

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatField -> m HsPatField

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatField -> m HsPatField

Show HsPatField Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsPatField -> ShowS

show :: HsPatField -> String

showList :: [HsPatField] -> ShowS

Eq HsPatField Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsPatField -> HsPatField -> Bool

(/=) :: HsPatField -> HsPatField -> Bool

Pretty HsPatField Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsPatField -> Doc

prettyPrec :: Int -> HsPatField -> Doc

Literals

data HsLiteral Source #

literal. Values of this type hold the abstract value of the literal, not the precise string representation used. For example, 10, 0o12 and 0xa have the same representation.

Constructors

HsChar Char

Character literal.

HsString String

String literal.

HsInt Integer

Integer literal.

HsFrac Rational

Floating point literal.

HsCharPrim Char

GHC unboxed character literal.

HsStringPrim String

GHC unboxed string literal.

HsIntPrim Integer

GHC unboxed integer literal.

HsFloatPrim Rational

GHC unboxed float literal.

HsDoublePrim Rational

GHC unboxed double literal.

Instances

Instances details
Data HsLiteral Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLiteral -> c HsLiteral

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsLiteral

toConstr :: HsLiteral -> Constr

dataTypeOf :: HsLiteral -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsLiteral)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsLiteral)

gmapT :: (forall b. Data b => b -> b) -> HsLiteral -> HsLiteral

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLiteral -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLiteral -> r

gmapQ :: (forall d. Data d => d -> u) -> HsLiteral -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLiteral -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLiteral -> m HsLiteral

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLiteral -> m HsLiteral

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLiteral -> m HsLiteral

Show HsLiteral Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsLiteral -> ShowS

show :: HsLiteral -> String

showList :: [HsLiteral] -> ShowS

Eq HsLiteral Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsLiteral -> HsLiteral -> Bool

(/=) :: HsLiteral -> HsLiteral -> Bool

Pretty HsLiteral Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsLiteral -> Doc

prettyPrec :: Int -> HsLiteral -> Doc

Variables, Constructors and Operators

newtype Module Source #

The name of a Haskell module.

Constructors

Module String 

Instances

Instances details
Data Module Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module

toConstr :: Module -> Constr

dataTypeOf :: Module -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)

gmapT :: (forall b. Data b => b -> b) -> Module -> Module

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

Show Module Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> Module -> ShowS

show :: Module -> String

showList :: [Module] -> ShowS

Eq Module Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: Module -> Module -> Bool

(/=) :: Module -> Module -> Bool

Ord Module Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: Module -> Module -> Ordering

(<) :: Module -> Module -> Bool

(<=) :: Module -> Module -> Bool

(>) :: Module -> Module -> Bool

(>=) :: Module -> Module -> Bool

max :: Module -> Module -> Module

min :: Module -> Module -> Module

Pretty Module Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: Module -> Doc

prettyPrec :: Int -> Module -> Doc

data HsQName Source #

This type is used to represent qualified variables, and also qualified constructors.

Constructors

Qual Module HsName

Name qualified with a module name.

UnQual HsName

Unqualified name.

Special HsSpecialCon

Built-in constructor with special syntax.

Instances

Instances details
Data HsQName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQName -> c HsQName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsQName

toConstr :: HsQName -> Constr

dataTypeOf :: HsQName -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsQName)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsQName)

gmapT :: (forall b. Data b => b -> b) -> HsQName -> HsQName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQName -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQName -> r

gmapQ :: (forall d. Data d => d -> u) -> HsQName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQName -> m HsQName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQName -> m HsQName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQName -> m HsQName

Show HsQName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsQName -> ShowS

show :: HsQName -> String

showList :: [HsQName] -> ShowS

Eq HsQName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsQName -> HsQName -> Bool

(/=) :: HsQName -> HsQName -> Bool

Ord HsQName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsQName -> HsQName -> Ordering

(<) :: HsQName -> HsQName -> Bool

(<=) :: HsQName -> HsQName -> Bool

(>) :: HsQName -> HsQName -> Bool

(>=) :: HsQName -> HsQName -> Bool

max :: HsQName -> HsQName -> HsQName

min :: HsQName -> HsQName -> HsQName

Pretty HsQName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQName -> Doc

prettyPrec :: Int -> HsQName -> Doc

data HsName Source #

This type is used to represent variables, and also constructors.

Constructors

HsIdent String

varid or conid.

HsSymbol String

varsym or consym.

Instances

Instances details
Data HsName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsName -> c HsName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsName

toConstr :: HsName -> Constr

dataTypeOf :: HsName -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsName)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsName)

gmapT :: (forall b. Data b => b -> b) -> HsName -> HsName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsName -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsName -> r

gmapQ :: (forall d. Data d => d -> u) -> HsName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsName -> m HsName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsName -> m HsName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsName -> m HsName

Show HsName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsName -> ShowS

show :: HsName -> String

showList :: [HsName] -> ShowS

Eq HsName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsName -> HsName -> Bool

(/=) :: HsName -> HsName -> Bool

Ord HsName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsName -> HsName -> Ordering

(<) :: HsName -> HsName -> Bool

(<=) :: HsName -> HsName -> Bool

(>) :: HsName -> HsName -> Bool

(>=) :: HsName -> HsName -> Bool

max :: HsName -> HsName -> HsName

min :: HsName -> HsName -> HsName

Pretty HsName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsName -> Doc

prettyPrec :: Int -> HsName -> Doc

data HsQOp Source #

Possibly qualified infix operators (qop), appearing in expressions.

Constructors

HsQVarOp HsQName

Variable operator (qvarop).

HsQConOp HsQName

Constructor operator (qconop).

Instances

Instances details
Data HsQOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQOp -> c HsQOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsQOp

toConstr :: HsQOp -> Constr

dataTypeOf :: HsQOp -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsQOp)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsQOp)

gmapT :: (forall b. Data b => b -> b) -> HsQOp -> HsQOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQOp -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQOp -> r

gmapQ :: (forall d. Data d => d -> u) -> HsQOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQOp -> m HsQOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQOp -> m HsQOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQOp -> m HsQOp

Show HsQOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsQOp -> ShowS

show :: HsQOp -> String

showList :: [HsQOp] -> ShowS

Eq HsQOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsQOp -> HsQOp -> Bool

(/=) :: HsQOp -> HsQOp -> Bool

Ord HsQOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsQOp -> HsQOp -> Ordering

(<) :: HsQOp -> HsQOp -> Bool

(<=) :: HsQOp -> HsQOp -> Bool

(>) :: HsQOp -> HsQOp -> Bool

(>=) :: HsQOp -> HsQOp -> Bool

max :: HsQOp -> HsQOp -> HsQOp

min :: HsQOp -> HsQOp -> HsQOp

Pretty HsQOp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQOp -> Doc

prettyPrec :: Int -> HsQOp -> Doc

data HsOp Source #

Operators, appearing in infix declarations.

Constructors

HsVarOp HsName

Variable operator (varop).

HsConOp HsName

Constructor operator (conop).

Instances

Instances details
Data HsOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOp -> c HsOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsOp

toConstr :: HsOp -> Constr

dataTypeOf :: HsOp -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsOp)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsOp)

gmapT :: (forall b. Data b => b -> b) -> HsOp -> HsOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOp -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOp -> r

gmapQ :: (forall d. Data d => d -> u) -> HsOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOp -> m HsOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOp -> m HsOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOp -> m HsOp

Show HsOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsOp -> ShowS

show :: HsOp -> String

showList :: [HsOp] -> ShowS

Eq HsOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsOp -> HsOp -> Bool

(/=) :: HsOp -> HsOp -> Bool

Ord HsOp Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsOp -> HsOp -> Ordering

(<) :: HsOp -> HsOp -> Bool

(<=) :: HsOp -> HsOp -> Bool

(>) :: HsOp -> HsOp -> Bool

(>=) :: HsOp -> HsOp -> Bool

max :: HsOp -> HsOp -> HsOp

min :: HsOp -> HsOp -> HsOp

Pretty HsOp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsOp -> Doc

prettyPrec :: Int -> HsOp -> Doc

data HsSpecialCon Source #

Constructors with special syntax. These names are never qualified, and always refer to builtin type or data constructors.

Constructors

HsUnitCon

Unit type and data constructor ().

HsListCon

List type constructor [].

HsFunCon

Function type constructor ->.

HsTupleCon Int

n-ary tuple type and data constructors (,) etc.

HsCons

List data constructor (:).

Instances

Instances details
Data HsSpecialCon Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSpecialCon -> c HsSpecialCon

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSpecialCon

toConstr :: HsSpecialCon -> Constr

dataTypeOf :: HsSpecialCon -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSpecialCon)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSpecialCon)

gmapT :: (forall b. Data b => b -> b) -> HsSpecialCon -> HsSpecialCon

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSpecialCon -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSpecialCon -> r

gmapQ :: (forall d. Data d => d -> u) -> HsSpecialCon -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSpecialCon -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSpecialCon -> m HsSpecialCon

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSpecialCon -> m HsSpecialCon

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSpecialCon -> m HsSpecialCon

Show HsSpecialCon Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsSpecialCon -> ShowS

show :: HsSpecialCon -> String

showList :: [HsSpecialCon] -> ShowS

Eq HsSpecialCon Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsSpecialCon -> HsSpecialCon -> Bool

(/=) :: HsSpecialCon -> HsSpecialCon -> Bool

Ord HsSpecialCon Source # 
Instance details

Defined in Language.Haskell.Syntax

data HsCName Source #

A name (cname) of a component of a class or data type in an import or export specification.

Constructors

HsVarName HsName

Name of a method or field.

HsConName HsName

Name of a data constructor.

Instances

Instances details
Data HsCName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCName -> c HsCName

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsCName

toConstr :: HsCName -> Constr

dataTypeOf :: HsCName -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsCName)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsCName)

gmapT :: (forall b. Data b => b -> b) -> HsCName -> HsCName

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCName -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCName -> r

gmapQ :: (forall d. Data d => d -> u) -> HsCName -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCName -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCName -> m HsCName

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCName -> m HsCName

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCName -> m HsCName

Show HsCName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> HsCName -> ShowS

show :: HsCName -> String

showList :: [HsCName] -> ShowS

Eq HsCName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: HsCName -> HsCName -> Bool

(/=) :: HsCName -> HsCName -> Bool

Ord HsCName Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: HsCName -> HsCName -> Ordering

(<) :: HsCName -> HsCName -> Bool

(<=) :: HsCName -> HsCName -> Bool

(>) :: HsCName -> HsCName -> Bool

(>=) :: HsCName -> HsCName -> Bool

max :: HsCName -> HsCName -> HsCName

min :: HsCName -> HsCName -> HsCName

Pretty HsCName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsCName -> Doc

prettyPrec :: Int -> HsCName -> Doc

Builtin names

Modules

Main function of a program

Constructors

Type constructors

Source coordinates

data SrcLoc Source #

A position in the source.

Constructors

SrcLoc 

Fields

Instances

Instances details
Data SrcLoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcLoc -> c SrcLoc

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcLoc

toConstr :: SrcLoc -> Constr

dataTypeOf :: SrcLoc -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcLoc)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc)

gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r

gmapQ :: (forall d. Data d => d -> u) -> SrcLoc -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcLoc -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc

Show SrcLoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

showsPrec :: Int -> SrcLoc -> ShowS

show :: SrcLoc -> String

showList :: [SrcLoc] -> ShowS

Eq SrcLoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

(==) :: SrcLoc -> SrcLoc -> Bool

(/=) :: SrcLoc -> SrcLoc -> Bool

Ord SrcLoc Source # 
Instance details

Defined in Language.Haskell.Syntax

Methods

compare :: SrcLoc -> SrcLoc -> Ordering

(<) :: SrcLoc -> SrcLoc -> Bool

(<=) :: SrcLoc -> SrcLoc -> Bool

(>) :: SrcLoc -> SrcLoc -> Bool

(>=) :: SrcLoc -> SrcLoc -> Bool

max :: SrcLoc -> SrcLoc -> SrcLoc

min :: SrcLoc -> SrcLoc -> SrcLoc