Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Haskell.Extensions
Description
The module exports the set of recognized language extensions, mostly corresponding to GHC extensions
Synopsis
- data Extension
- = AllowAmbiguousTypes
- | AlternativeLayoutRule
- | AlternativeLayoutRuleTransitional
- | ApplicativeDo
- | Arrows
- | AutoDeriveTypeable
- | BangDataFields
- | BangPatterns
- | BinaryLiterals
- | BlockArguments
- | CApiFFI
- | CUSKs
- | ConstrainedClassMethods
- | ConstraintsAreTypes
- | ConstraintKinds
- | Cpp
- | DataKinds
- | DatatypeContexts
- | DeepSubsumption
- | DefaultSignatures
- | DeriveAnyClass
- | DeriveDataTypeable
- | DeriveFoldable
- | DeriveFunctor
- | DeriveGeneric
- | DeriveLift
- | DeriveTraversable
- | DerivingStrategies
- | DerivingVia
- | DisambiguateRecordFields
- | DoAndIfThenElse
- | DuplicateRecordFields
- | EmptyCase
- | EmptyDataDeclarations
- | EmptyDataDeriving
- | EqualityConstraints
- | ExistentialQuantification
- | ExplicitForAll
- | ExplicitNamespaces
- | ExtendedDefaultRules
- | ExtendedLiterals
- | FieldSelectors
- | FlexibleContexts
- | FlexibleInstances
- | ForeignFunctionInterface
- | FunctionalDependencies
- | GADTSyntax
- | GADTs
- | GHC2021
- | GHC2024
- | GHCForeignImportPrim
- | GeneralizedNewtypeDeriving
- | Haskell2010
- | Haskell98
- | HexFloatLiterals
- | IdentifierSyntax
- | ImplicitParameters
- | ImplicitPrelude
- | ImportQualifiedPost
- | ImpredicativeTypes
- | IncoherentInstances
- | InferredTypeVariables
- | InstanceSigs
- | InterruptibleFFI
- | JavaScriptFFI
- | KindSignatures
- | LambdaCase
- | LexicalNegation
- | LiberalTypeSynonyms
- | LinearTypes
- | ListTuplePuns
- | MagicHash
- | MonadComprehensions
- | MonadFailDesugaring
- | MonoLocalBinds
- | MonoPatBinds
- | MonomorphismRestriction
- | MultiParamTypeClasses
- | MultiParameterConstraints
- | MultiWayIf
- | NPlusKPatterns
- | NamedDefaults
- | NamedFieldPuns
- | NamedWildCards
- | NegativeLiterals
- | NondecreasingIndentation
- | NullaryTypeClasses
- | NumDecimals
- | NumericUnderscores
- | OverlappingInstances
- | OverloadedLabels
- | OverloadedLists
- | OverloadedRecordDot
- | OverloadedRecordUpdate
- | OverloadedStrings
- | PackageImports
- | ParallelArrays
- | ParallelListComp
- | ParallelListComprehensions
- | ParenthesizedTypeOperators
- | GratuitouslyParenthesizedTypes
- | PartialTypeSignatures
- | PatternGuards
- | PatternSynonyms
- | PolyKinds
- | PostfixOperators
- | QualifiedDo
- | QuantifiedConstraints
- | QuasiQuotes
- | RankNTypes
- | RebindableSyntax
- | RecordWildCards
- | RecursiveDo
- | RelaxedLayout
- | RelaxedPolyRec
- | RequiredTypeArguments
- | RoleAnnotations
- | Safe
- | SafeImports
- | ScopedTypeVariables
- | SpaceSensitiveOperators
- | StandaloneDeriving
- | StandaloneKindSignatures
- | StarIsType
- | StaticPointers
- | Strict
- | StrictData
- | TemplateHaskell
- | TemplateHaskellQuotes
- | TraditionalRecordSyntax
- | TransformListComp
- | Trustworthy
- | TupleSections
- | TypeAbstractions
- | TypeAbstractionsOrApplicationsInConstructorPatterns
- | TypeApplications
- | TypeData
- | TypeFamilies
- | TypeFamilyDependencies
- | TypeInType
- | TypeOperators
- | TypeSynonymInstances
- | TypeVariableConstraints
- | UnboxedSums
- | UnboxedTuples
- | UndecidableInstances
- | UndecidableSuperClasses
- | UnicodeSyntax
- | UnliftedDatatypes
- | UnliftedFFITypes
- | UnliftedNewtypes
- | Unsafe
- | ViewPatterns
- | VisibleDependedentQuantification
- newtype ExtensionSwitch = ExtensionSwitch (Extension, Bool)
- type On (e :: Extension) = 'ExtensionSwitch '(e, 'True)
- type Off (e :: Extension) = 'ExtensionSwitch '(e, 'False)
- on :: Extension -> ExtensionSwitch
- off :: Extension -> ExtensionSwitch
- allExtensions :: Set Extension
- byName :: (IsString t, Ord t) => Map t Extension
- includedByDefault :: Set Extension
- implications :: Map Extension (Map Extension Bool)
- inverseImplications :: Map Extension (Set Extension)
- languageVersions :: Set Extension
- partitionContradictory :: Set ExtensionSwitch -> (Set ExtensionSwitch, Map Extension Bool)
- switchesByName :: (IsString t, Ord t, Semigroup t) => Map t ExtensionSwitch
- withImplications :: Map Extension Bool -> Map Extension Bool
Documentation
The enumeration of all language extensions
Constructors
Instances
newtype ExtensionSwitch Source #
An extension together with an on/off boolean
Constructors
ExtensionSwitch (Extension, Bool) |
Instances
on :: Extension -> ExtensionSwitch Source #
The on-switch for an extension
off :: Extension -> ExtensionSwitch Source #
The off-switch for an extension
allExtensions :: Set Extension Source #
Set of all extensions
includedByDefault :: Set Extension Source #
Set of extensions that are on by default
implications :: Map Extension (Map Extension Bool) Source #
Map of all extension implications, including directImplications
but adding transitive implications
inverseImplications :: Map Extension (Set Extension) Source #
Inverse of the implications
map
languageVersions :: Set Extension Source #
Set of language version extensions, such as Haskell2010
switchesByName :: (IsString t, Ord t, Semigroup t) => Map t ExtensionSwitch Source #