Portability | portable |
---|---|
Maintainer | libraries@haskell.org |
Haskell language dialects and extensions
- data Language
- knownLanguages :: [Language]
- data Extension
- = OverlappingInstances
- | UndecidableInstances
- | IncoherentInstances
- | DoRec
- | RecursiveDo
- | ParallelListComp
- | MultiParamTypeClasses
- | NoMonomorphismRestriction
- | FunctionalDependencies
- | Rank2Types
- | RankNTypes
- | PolymorphicComponents
- | ExistentialQuantification
- | ScopedTypeVariables
- | PatternSignatures
- | ImplicitParams
- | FlexibleContexts
- | FlexibleInstances
- | EmptyDataDecls
- | CPP
- | KindSignatures
- | BangPatterns
- | TypeSynonymInstances
- | TemplateHaskell
- | ForeignFunctionInterface
- | Arrows
- | Generics
- | NoImplicitPrelude
- | NamedFieldPuns
- | PatternGuards
- | GeneralizedNewtypeDeriving
- | ExtensibleRecords
- | RestrictedTypeSynonyms
- | HereDocuments
- | MagicHash
- | TypeFamilies
- | StandaloneDeriving
- | UnicodeSyntax
- | UnliftedFFITypes
- | LiberalTypeSynonyms
- | TypeOperators
- | RecordWildCards
- | RecordPuns
- | DisambiguateRecordFields
- | OverloadedStrings
- | GADTs
- | NoMonoPatBinds
- | RelaxedPolyRec
- | ExtendedDefaultRules
- | UnboxedTuples
- | DeriveDataTypeable
- | ConstrainedClassMethods
- | PackageImports
- | ImpredicativeTypes
- | NewQualifiedOperators
- | PostfixOperators
- | QuasiQuotes
- | TransformListComp
- | ViewPatterns
- | XmlSyntax
- | RegularPatterns
- | TupleSections
- | GHCForeignImportPrim
- | NPlusKPatterns
- | DoAndIfThenElse
- | RebindableSyntax
- | ExplicitForAll
- | DatatypeContexts
- | MonoLocalBinds
- | DeriveFunctor
- | DeriveTraversable
- | DeriveFoldable
- | UnknownExtension String
- knownExtensions :: [Extension]
- deprecatedExtensions :: [(Extension, Maybe Extension)]
Documentation
This represents a Haskell language dialect.
Language Extension
s are interpreted relative to one of these base
languages.
Haskell98 | The Haskell 98 language as defined by the Haskell 98 report. http://haskell.org/onlinereport/ |
Haskell2010 | The Haskell 2010 language as defined by the Haskell 2010 report. http://www.haskell.org/onlinereport/haskell2010 |
UnknownLanguage String | An unknown language, identified by its name. |
This represents language extensions beyond a base Language
definition
(such as Haskell98
) that are supported by some implementations, usually
in some special mode.
Where applicable, references are given to an implementation's official documentation, e.g. "GHC § 7.2.1" for an extension documented in section 7.2.1 of the GHC User's Guide.
OverlappingInstances |
|
UndecidableInstances |
|
IncoherentInstances |
|
DoRec |
|
RecursiveDo |
|
ParallelListComp |
|
MultiParamTypeClasses |
|
NoMonomorphismRestriction |
|
FunctionalDependencies |
|
Rank2Types |
|
RankNTypes |
|
PolymorphicComponents |
|
ExistentialQuantification |
|
ScopedTypeVariables |
|
PatternSignatures | Deprecated, use |
ImplicitParams |
|
FlexibleContexts |
|
FlexibleInstances |
|
EmptyDataDecls |
|
CPP |
|
KindSignatures |
|
BangPatterns |
|
TypeSynonymInstances |
|
TemplateHaskell |
|
ForeignFunctionInterface |
|
Arrows |
|
Generics |
|
NoImplicitPrelude |
|
NamedFieldPuns |
|
PatternGuards |
|
GeneralizedNewtypeDeriving |
|
ExtensibleRecords |
|
RestrictedTypeSynonyms |
|
HereDocuments |
|
MagicHash |
|
TypeFamilies |
|
StandaloneDeriving |
|
UnicodeSyntax |
|
UnliftedFFITypes |
|
LiberalTypeSynonyms |
|
TypeOperators |
|
RecordWildCards |
|
RecordPuns | Deprecated, use |
DisambiguateRecordFields |
|
OverloadedStrings |
|
GADTs |
|
NoMonoPatBinds |
|
RelaxedPolyRec |
|
ExtendedDefaultRules |
|
UnboxedTuples |
|
DeriveDataTypeable |
|
ConstrainedClassMethods |
|
PackageImports |
import "network" Network.Socket |
ImpredicativeTypes |
|
NewQualifiedOperators |
|
PostfixOperators |
|
QuasiQuotes |
|
TransformListComp |
|
ViewPatterns |
|
XmlSyntax | Allow concrete XML syntax to be used in expressions and patterns, as per the Haskell Server Pages extension language: http://www.haskell.org/haskellwiki/HSP. The ideas behind it are discussed in the paper "Haskell Server Pages through Dynamic Loading" by Niklas Broberg, from Haskell Workshop '05. |
RegularPatterns | Allow regular pattern matching over lists, as discussed in the paper "Regular Expression Patterns" by Niklas Broberg, Andreas Farre and Josef Svenningsson, from ICFP '04. |
TupleSections | Enables the use of tuple sections, e.g. |
GHCForeignImportPrim | Allows GHC primops, written in C--, to be imported into a Haskell file. |
NPlusKPatterns | Support for patterns of the form |
DoAndIfThenElse | Improve the layout rule when |
RebindableSyntax | Makes much of the Haskell sugar be desugared into calls to the function with a particular name that is in scope. |
ExplicitForAll | Make |
DatatypeContexts | Allow contexts to be put on datatypes, e.g. the |
MonoLocalBinds | Local ( |
DeriveFunctor | Enable |
DeriveTraversable | Enable |
DeriveFoldable | Enable |
UnknownExtension String | An unknown extension, identified by the name of its |
deprecatedExtensions :: [(Extension, Maybe Extension)]Source
Extensions that have been deprecated, possibly paired with another extension that replaces it.