Skip to content
Snippets Groups Projects
Commit 677c6fa2 authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Add some more extensions that GHC knows about

parent 2e4c13c5
No related branches found
No related tags found
No related merge requests found
......@@ -389,6 +389,47 @@ data KnownExtension =
-- paper \"Regular Expression Patterns\" by Niklas Broberg, Andreas Farre
-- and Josef Svenningsson, from ICFP '04.
| RegularPatterns
-- | Enables the use of tuple sections, e.g. @(, True)@ desugars into
-- @\x -> (x, True)@.
| TupleSections
-- | Allows GHC primops, written in C--, to be imported into a Haskell
-- file.
| GHCForeignImportPrim
-- | Support for patterns of the form @n + k@, where @k@ is an
-- integer literal.
| NPlusKPatterns
-- | Improve the layout rule when @if@ expressions are used in a @do@
-- block.
| DoAndIfThenElse
-- | Makes much of the Haskell sugar be desugared into calls to the
-- function with a particular name that is in scope.
| RebindableSyntax
-- | Make @forall@ a keyword in types, which can be used to give the
-- generalisation explicitly.
| ExplicitForAll
-- | Allow contexts to be put on datatypes, e.g. the @Eq a@ in
-- @data Eq a => Set a = NilSet | ConsSet a (Set a)@.
| DatatypeContexts
-- | Local (@let@ and @where@) bindings are monomorphic.
| MonoLocalBinds
-- | Enable @deriving@ for the @Data.Functor.Functor@ class.
| DeriveFunctor
-- | Enable @deriving@ for the @Data.Traversable.Traversable@ class.
| DeriveTraversable
-- | Enable @deriving@ for the @Data.Foldable.Foldable@ class.
| DeriveFoldable
deriving (Show, Read, Eq, Enum)
-- | Extensions that have been deprecated, possibly paired with another
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment