Portability | portable |
---|---|
Stability | transient |
Maintainer | Niklas Broberg, niklas.broberg@chalmers.se |
Safe Haskell | Safe-Inferred |
This module defines the list of recognized modular features of Haskell, most often (sloppily) referred to as extensions.
Closely mimicking the Language.Haskell.Extension module from the Cabal library, this package also includes functionality for computing languages as sets of features. Also, we make no promise not to add extensions not yet recognized by Cabal.
- data Language
- knownLanguages :: [Language]
- classifyLanguage :: String -> Language
- prettyLanguage :: Language -> String
- data Extension
- data KnownExtension
- = OverlappingInstances
- | UndecidableInstances
- | IncoherentInstances
- | RecursiveDo
- | ParallelListComp
- | MultiParamTypeClasses
- | MonomorphismRestriction
- | FunctionalDependencies
- | Rank2Types
- | RankNTypes
- | PolymorphicComponents
- | ExistentialQuantification
- | ScopedTypeVariables
- | PatternSignatures
- | ImplicitParams
- | FlexibleContexts
- | FlexibleInstances
- | EmptyDataDecls
- | CPP
- | KindSignatures
- | BangPatterns
- | TypeSynonymInstances
- | TemplateHaskell
- | ForeignFunctionInterface
- | Arrows
- | Generics
- | ImplicitPrelude
- | NamedFieldPuns
- | PatternGuards
- | GeneralizedNewtypeDeriving
- | ExtensibleRecords
- | RestrictedTypeSynonyms
- | HereDocuments
- | MagicHash
- | TypeFamilies
- | StandaloneDeriving
- | UnicodeSyntax
- | UnliftedFFITypes
- | LiberalTypeSynonyms
- | TypeOperators
- | RecordWildCards
- | RecordPuns
- | DisambiguateRecordFields
- | OverloadedStrings
- | GADTs
- | MonoPatBinds
- | RelaxedPolyRec
- | ExtendedDefaultRules
- | UnboxedTuples
- | DeriveDataTypeable
- | ConstrainedClassMethods
- | PackageImports
- | LambdaCase
- | ImpredicativeTypes
- | NewQualifiedOperators
- | PostfixOperators
- | QuasiQuotes
- | TransformListComp
- | ViewPatterns
- | XmlSyntax
- | RegularPatterns
- | TupleSections
- | GHCForeignImportPrim
- | NPlusKPatterns
- | DoAndIfThenElse
- | RebindableSyntax
- | ExplicitForAll
- | DatatypeContexts
- | MonoLocalBinds
- | DeriveFunctor
- | DeriveTraversable
- | DeriveFoldable
- | NondecreasingIndentation
- | InterruptibleFFI
- | CApiFFI
- | DataKinds
- | PolyKinds
- | MultiWayIf
- classifyExtension :: String -> Extension
- parseExtension :: String -> Extension
- prettyExtension :: Extension -> String
- ghcDefault :: [Extension]
- glasgowExts :: [Extension]
- knownExtensions :: [Extension]
- deprecatedExtensions :: [(Extension, Maybe Extension)]
- impliesExts :: [KnownExtension] -> [KnownExtension]
- toExtensionList :: Language -> [Extension] -> [KnownExtension]
Language definitions
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 |
HaskellAllDisabled | The minimal language resulting from disabling all recognized extensions - including ones that are part of all known language definitions e.g. MonomorphismRestriction. |
UnknownLanguage String | An unknown language, identified by its name. |
Extensions
This represents language extensions beyond a base Language
definition
(such as Haskell98
) that are supported by some implementations, usually
in some special mode.
EnableExtension KnownExtension | Enable a known extension |
DisableExtension KnownExtension | Disable a known extension |
UnknownExtension String | An unknown extension, identified by the name of its |
data KnownExtension Source
OverlappingInstances |
|
UndecidableInstances |
|
IncoherentInstances |
|
RecursiveDo |
|
ParallelListComp |
|
MultiParamTypeClasses |
|
MonomorphismRestriction |
|
FunctionalDependencies |
|
Rank2Types |
|
RankNTypes |
|
PolymorphicComponents |
|
ExistentialQuantification |
|
ScopedTypeVariables |
|
PatternSignatures | Deprecated, use |
ImplicitParams |
|
FlexibleContexts |
|
FlexibleInstances |
|
EmptyDataDecls |
|
CPP |
|
KindSignatures |
|
BangPatterns |
|
TypeSynonymInstances |
|
TemplateHaskell |
|
ForeignFunctionInterface |
|
Arrows |
|
Generics |
|
ImplicitPrelude |
|
NamedFieldPuns |
|
PatternGuards |
|
GeneralizedNewtypeDeriving |
|
ExtensibleRecords |
|
RestrictedTypeSynonyms |
|
HereDocuments |
|
MagicHash |
|
TypeFamilies |
|
StandaloneDeriving |
|
UnicodeSyntax |
|
UnliftedFFITypes |
|
LiberalTypeSynonyms |
|
TypeOperators |
|
RecordWildCards |
|
RecordPuns | Deprecated, use |
DisambiguateRecordFields |
|
OverloadedStrings |
|
GADTs |
|
MonoPatBinds |
|
RelaxedPolyRec |
|
ExtendedDefaultRules |
|
UnboxedTuples |
|
DeriveDataTypeable |
|
ConstrainedClassMethods |
|
PackageImports |
import "network" Network.Socket |
LambdaCase | |
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 |
NondecreasingIndentation | Enable non-decreasing indentation for 'do' blocks. |
InterruptibleFFI |
|
CApiFFI |
|
DataKinds | |
PolyKinds | |
MultiWayIf |
|
classifyExtension :: String -> ExtensionSource
A clever version of read that returns an UnknownExtension
if the string is not recognised.
parseExtension :: String -> ExtensionSource
Parse an enabled or disabled extension; returns
UnknownExtension
if the parse fails.
prettyExtension :: Extension -> StringSource
Pretty print an extension. Disabled extensions are prefixed with 'No'.
Extension groups
glasgowExts :: [Extension]Source
The list of extensions enabled by GHC's portmanteau -fglasgow-exts flag.
knownExtensions :: [Extension]Source
List of all known extensions, both "yes" and "no" versions.
deprecatedExtensions :: [(Extension, Maybe Extension)]Source
Extensions that have been deprecated, possibly paired with another extension that replaces it.
Semantics of extensions applied to languages
impliesExts :: [KnownExtension] -> [KnownExtension]Source
Certain extensions imply other extensions, and this function makes the implication explicit. This also handles deprecated extensions, which imply their replacements. The returned value is the transitive closure of implied extensions.
toExtensionList :: Language -> [Extension] -> [KnownExtension]Source