-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.LanguageExtensions.Type
-- Copyright   :  (c) The GHC Team
--
-- Maintainer  :  ghc-devs@haskell.org
-- Portability :  portable
--
-- A data type defining the language extensions supported by GHC.
--
{-# LANGUAGE DeriveGeneric, Safe #-}
module GHC.LanguageExtensions.Type ( Extension(..) ) where

import Prelude -- See note [Why do we import Prelude here?]
import GHC.Generics

-- | 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.
data Extension
-- See Note [Updating flag description in the User's Guide] in
-- GHC.Driver.Session
   = Cpp
   | OverlappingInstances
   | UndecidableInstances
   | IncoherentInstances
   | UndecidableSuperClasses
   | MonomorphismRestriction
   | MonoPatBinds
   | MonoLocalBinds
   | RelaxedPolyRec           -- Deprecated
   | ExtendedDefaultRules     -- Use GHC's extended rules for defaulting
   | ForeignFunctionInterface
   | UnliftedFFITypes
   | InterruptibleFFI
   | CApiFFI
   | GHCForeignImportPrim
   | JavaScriptFFI
   | ParallelArrays           -- Syntactic support for parallel arrays
   | Arrows                   -- Arrow-notation syntax
   | TemplateHaskell
   | TemplateHaskellQuotes    -- subset of TH supported by stage1, no splice
   | QuasiQuotes
   | ImplicitParams
   | ImplicitPrelude
   | ScopedTypeVariables
   | AllowAmbiguousTypes
   | UnboxedTuples
   | UnboxedSums
   | UnliftedNewtypes
   | BangPatterns
   | TypeFamilies
   | TypeFamilyDependencies
   | TypeInType
   | OverloadedStrings
   | OverloadedLists
   | NumDecimals
   | DisambiguateRecordFields
   | RecordWildCards
   | RecordPuns
   | ViewPatterns
   | GADTs
   | GADTSyntax
   | NPlusKPatterns
   | DoAndIfThenElse
   | BlockArguments
   | RebindableSyntax
   | ConstraintKinds
   | PolyKinds                -- Kind polymorphism
   | DataKinds                -- Datatype promotion
   | InstanceSigs
   | ApplicativeDo

   | StandaloneDeriving
   | DeriveDataTypeable
   | AutoDeriveTypeable       -- Automatic derivation of Typeable
   | DeriveFunctor
   | DeriveTraversable
   | DeriveFoldable
   | DeriveGeneric            -- Allow deriving Generic/1
   | DefaultSignatures        -- Allow extra signatures for defmeths
   | DeriveAnyClass           -- Allow deriving any class
   | DeriveLift               -- Allow deriving Lift
   | DerivingStrategies
   | DerivingVia              -- Derive through equal representation

   | 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
   | ImportQualifiedPost
   | CUSKs
   | StandaloneKindSignatures
   deriving (Extension -> Extension -> Bool
(Extension -> Extension -> Bool)
-> (Extension -> Extension -> Bool) -> Eq Extension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extension -> Extension -> Bool
$c/= :: Extension -> Extension -> Bool
== :: Extension -> Extension -> Bool
$c== :: Extension -> Extension -> Bool
Eq, Int -> Extension
Extension -> Int
Extension -> [Extension]
Extension -> Extension
Extension -> Extension -> [Extension]
Extension -> Extension -> Extension -> [Extension]
(Extension -> Extension)
-> (Extension -> Extension)
-> (Int -> Extension)
-> (Extension -> Int)
-> (Extension -> [Extension])
-> (Extension -> Extension -> [Extension])
-> (Extension -> Extension -> [Extension])
-> (Extension -> Extension -> Extension -> [Extension])
-> Enum Extension
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Extension -> Extension -> Extension -> [Extension]
$cenumFromThenTo :: Extension -> Extension -> Extension -> [Extension]
enumFromTo :: Extension -> Extension -> [Extension]
$cenumFromTo :: Extension -> Extension -> [Extension]
enumFromThen :: Extension -> Extension -> [Extension]
$cenumFromThen :: Extension -> Extension -> [Extension]
enumFrom :: Extension -> [Extension]
$cenumFrom :: Extension -> [Extension]
fromEnum :: Extension -> Int
$cfromEnum :: Extension -> Int
toEnum :: Int -> Extension
$ctoEnum :: Int -> Extension
pred :: Extension -> Extension
$cpred :: Extension -> Extension
succ :: Extension -> Extension
$csucc :: Extension -> Extension
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum, Int -> Extension -> ShowS
[Extension] -> ShowS
Extension -> String
(Int -> Extension -> ShowS)
-> (Extension -> String)
-> ([Extension] -> ShowS)
-> Show Extension
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Extension] -> ShowS
$cshowList :: [Extension] -> ShowS
show :: Extension -> String
$cshow :: Extension -> String
showsPrec :: Int -> Extension -> ShowS
$cshowsPrec :: Int -> Extension -> ShowS
Show, (forall x. Extension -> Rep Extension x)
-> (forall x. Rep Extension x -> Extension) -> Generic Extension
forall x. Rep Extension x -> Extension
forall x. Extension -> Rep Extension x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Extension x -> Extension
$cfrom :: forall x. Extension -> Rep Extension x
Generic, Extension
Extension -> Extension -> Bounded Extension
forall a. a -> a -> Bounded a
maxBound :: Extension
$cmaxBound :: Extension
minBound :: Extension
$cminBound :: Extension
Bounded)
-- 'Ord' and 'Bounded' are provided for GHC API users (see discussions
-- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and
-- https://gitlab.haskell.org/ghc/ghc/merge_requests/826).
instance Ord Extension where compare :: Extension -> Extension -> Ordering
compare Extension
a Extension
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare (Extension -> Int
forall a. Enum a => a -> Int
Instance of class: Enum of the constraint type Enum Extension
fromEnum Extension
a) (Extension -> Int
forall a. Enum a => a -> Int
Instance of class: Enum of the constraint type Enum Extension
fromEnum Extension
b)