Copyright | (c) The University of Glasgow 2015 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Language extensions known to GHC
Synopsis
- data Extension
- = Cpp
- | OverlappingInstances
- | UndecidableInstances
- | IncoherentInstances
- | UndecidableSuperClasses
- | MonomorphismRestriction
- | MonoPatBinds
- | MonoLocalBinds
- | RelaxedPolyRec
- | ExtendedDefaultRules
- | ForeignFunctionInterface
- | UnliftedFFITypes
- | InterruptibleFFI
- | CApiFFI
- | GHCForeignImportPrim
- | JavaScriptFFI
- | ParallelArrays
- | Arrows
- | TemplateHaskell
- | TemplateHaskellQuotes
- | QuasiQuotes
- | ImplicitParams
- | ImplicitPrelude
- | ScopedTypeVariables
- | AllowAmbiguousTypes
- | UnboxedTuples
- | UnboxedSums
- | BangPatterns
- | TypeFamilies
- | TypeFamilyDependencies
- | TypeInType
- | OverloadedStrings
- | OverloadedLists
- | NumDecimals
- | DisambiguateRecordFields
- | RecordWildCards
- | RecordPuns
- | ViewPatterns
- | GADTs
- | GADTSyntax
- | NPlusKPatterns
- | DoAndIfThenElse
- | BlockArguments
- | RebindableSyntax
- | ConstraintKinds
- | PolyKinds
- | DataKinds
- | InstanceSigs
- | ApplicativeDo
- | StandaloneDeriving
- | DeriveDataTypeable
- | AutoDeriveTypeable
- | DeriveFunctor
- | DeriveTraversable
- | DeriveFoldable
- | DeriveGeneric
- | DefaultSignatures
- | DeriveAnyClass
- | DeriveLift
- | DerivingStrategies
- | DerivingVia
- | TypeSynonymInstances
- | FlexibleContexts
- | FlexibleInstances
- | ConstrainedClassMethods
- | MultiParamTypeClasses
- | NullaryTypeClasses
- | FunctionalDependencies
- | UnicodeSyntax
- | ExistentialQuantification
- | MagicHash
- | EmptyDataDecls
- | KindSignatures
- | RoleAnnotations
- | ParallelListComp
- | TransformListComp
- | MonadComprehensions
- | GeneralizedNewtypeDeriving
- | RecursiveDo
- | PostfixOperators
- | TupleSections
- | PatternGuards
- | LiberalTypeSynonyms
- | RankNTypes
- | ImpredicativeTypes
- | TypeOperators
- | ExplicitNamespaces
- | PackageImports
- | ExplicitForAll
- | AlternativeLayoutRule
- | AlternativeLayoutRuleTransitional
- | DatatypeContexts
- | NondecreasingIndentation
- | RelaxedLayout
- | TraditionalRecordSyntax
- | LambdaCase
- | MultiWayIf
- | BinaryLiterals
- | NegativeLiterals
- | HexFloatLiterals
- | DuplicateRecordFields
- | OverloadedLabels
- | EmptyCase
- | PatternSynonyms
- | PartialTypeSignatures
- | NamedWildCards
- | StaticPointers
- | TypeApplications
- | Strict
- | StrictData
- | MonadFailDesugaring
- | EmptyDataDeriving
- | NumericUnderscores
- | QuantifiedConstraints
- | StarIsType
Documentation
The language extensions known to GHC.
Note that there is an orphan Binary
instance for this type supplied by
the GHC.LanguageExtensions module provided by ghc-boot
. We can't provide
here as this would require adding transitive dependencies to the
template-haskell
package, which must have a minimal dependency set.
Instances
Enum Extension | |
Defined in GHC.LanguageExtensions.Type succ :: Extension -> Extension Source # pred :: Extension -> Extension Source # toEnum :: Int -> Extension Source # fromEnum :: Extension -> Int Source # enumFrom :: Extension -> [Extension] Source # enumFromThen :: Extension -> Extension -> [Extension] Source # enumFromTo :: Extension -> Extension -> [Extension] Source # enumFromThenTo :: Extension -> Extension -> Extension -> [Extension] Source # | |
Eq Extension | |
Show Extension | |
Generic Extension | |
type Rep Extension | |
Defined in GHC.LanguageExtensions.Type type Rep Extension = D1 (MetaData "Extension" "GHC.LanguageExtensions.Type" "ghc-boot-th-8.6.3" False) ((((((C1 (MetaCons "Cpp" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OverlappingInstances" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UndecidableInstances" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "IncoherentInstances" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UndecidableSuperClasses" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MonomorphismRestriction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MonoPatBinds" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "MonoLocalBinds" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RelaxedPolyRec" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ExtendedDefaultRules" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ForeignFunctionInterface" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnliftedFFITypes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "InterruptibleFFI" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CApiFFI" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "GHCForeignImportPrim" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "JavaScriptFFI" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ParallelArrays" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Arrows" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TemplateHaskell" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TemplateHaskellQuotes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "QuasiQuotes" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ImplicitParams" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ImplicitPrelude" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ScopedTypeVariables" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "AllowAmbiguousTypes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnboxedTuples" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UnboxedSums" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BangPatterns" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "TypeFamilies" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TypeFamilyDependencies" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeInType" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "OverloadedStrings" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OverloadedLists" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NumDecimals" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DisambiguateRecordFields" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "RecordWildCards" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RecordPuns" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ViewPatterns" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "GADTs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GADTSyntax" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NPlusKPatterns" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoAndIfThenElse" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "BlockArguments" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RebindableSyntax" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ConstraintKinds" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "PolyKinds" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DataKinds" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "InstanceSigs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ApplicativeDo" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "StandaloneDeriving" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeriveDataTypeable" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AutoDeriveTypeable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeriveFunctor" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "DeriveTraversable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DeriveFoldable" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DeriveGeneric" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DefaultSignatures" PrefixI False) (U1 :: Type -> Type))))))) :+: (((((C1 (MetaCons "DeriveAnyClass" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DeriveLift" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DerivingStrategies" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "DerivingVia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeSynonymInstances" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FlexibleContexts" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FlexibleInstances" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ConstrainedClassMethods" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MultiParamTypeClasses" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NullaryTypeClasses" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "FunctionalDependencies" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnicodeSyntax" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ExistentialQuantification" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MagicHash" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "EmptyDataDecls" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "KindSignatures" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RoleAnnotations" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ParallelListComp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TransformListComp" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MonadComprehensions" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GeneralizedNewtypeDeriving" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "RecursiveDo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PostfixOperators" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TupleSections" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PatternGuards" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LiberalTypeSynonyms" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RankNTypes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ImpredicativeTypes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeOperators" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "ExplicitNamespaces" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PackageImports" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ExplicitForAll" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "AlternativeLayoutRule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlternativeLayoutRuleTransitional" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DatatypeContexts" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NondecreasingIndentation" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "RelaxedLayout" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TraditionalRecordSyntax" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LambdaCase" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "MultiWayIf" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BinaryLiterals" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NegativeLiterals" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HexFloatLiterals" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "DuplicateRecordFields" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OverloadedLabels" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EmptyCase" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "PatternSynonyms" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PartialTypeSignatures" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NamedWildCards" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StaticPointers" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "TypeApplications" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Strict" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StrictData" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MonadFailDesugaring" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "EmptyDataDeriving" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NumericUnderscores" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "QuantifiedConstraints" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StarIsType" PrefixI False) (U1 :: Type -> Type)))))))) |