Haskell98 and Haskell2010 are standards.
But GHC provides many extensions.
Extensions can be enabled with:
:set -XBinaryLiterals
(in ghci){-# LANGUAGE BinaryLiterals #-}
(in code)EmptyCase
Allow to pattern match with case
on a type without constructors.
Eg:
data Void = Void
f :: Void -> Int
= case x of { } f x
DeriveLift
Lift
class for types via deriving
clauseExplicitForAll
Implied by: ScopedTypeVariables, LiberalTypeSynonyms, RankNTypes, ExistentialQuantification
Even without this extension, there is a forall
by default.
For example, foo :: a -> a
really means foo :: forall a. (a -> a)
(but the latter makes scoped type variables via ScopedTypeVariables
possible).
ExplicitForAll
can give more control over this implicit quantification.
ScopedTypeVariables
let
.
—
Allows free variables (introduced with a forall
) occuring in the type to be 're-used' in type annotations in the body of a definition ??
Example from Haskell wiki:
{-# LANGUAGE ScopedTypeVariables #-}
f :: forall a. [a] -> [a]
= ys ++ ys
f xs where
ys :: [a] -- This `a` is same the one in type of `f'
= reverse xs ys
See: https://wiki.haskell.org/Scoped_type_variables
Apparently can help avoid monomorphism restriction.
UnicodeSyntax
Allows using unicode symbols in place of certain character sequences.
Like:
∀
instead of forall
→
instead of ->
StandaloneDeriving
Allow a shorter form of instance definition of a type class for an type that has already been defined.
data Foo a = Bar a | Baz String
deriving instance Eq a => Eq (Foo a)
For types for which haskell can make the derivation by itself. Otherwise we would have to write the instance definition ourselves.
Standalone deriving is similar to having a deriving
clause made as part of a type's definition, but not exactly same?
deriving
clause, standalone deriving needn't be in same module as type definition.MagicHash
Allow definition (and use?) of identifiers with a #
at its end.
Like: Word#
Variables with #
in end are usually used by internals.
For example, types with #
at its end are unboxed types by convention (not a requirement though).
BinaryLiterals
Allows use of binary notation to represent integers.
$ ghci
GHCi, version 9.4.8: https://www.haskell.org/ghc/ :? for help
λ> {-# LANGUAGE BinaryLiterals #-}
λ> 0b101
5
λ> 0b1001010101011
4779
λ> 0b2031
<interactive>:4:2: error: Variable not in scope: b2031
(Couldn't get this working in ghci v8.8.4 for some reason. Though docs say it is available since v7.10.1)
Note that octal and hexadecimal notations are supported without any extensions:
λ> 0x2e
46
λ> 0o70
56
Also see: link
MultiWayIf
Use guards syntax of pattern matching in if
statements.
TypeFamilies
Kind of like functions at type level.
DataKinds
DataKinds
makes a type and kind.
Kind is a type of types.
data Nat = Zero | Succ
makes the following:
Nat
: a typeNat
: a kindZero
: Constructor of the type NatSucc
: Constructor of the type Nat'Zero
: Type constructor of the kind Nat'Succ
: Type constructor of the kind Nat–
'Zero
, 'Succ
Nat
are types.We can skip the apostrophe for type constructors if it can be inferred as being of the kind level at compile time.
LinearTypes
Linear function: Every argument is used exactly once.
a %1 -> b
: a linear function from a to b
a ⊸ b
: Same thing with UnicodeSyntax
ghc extension enabledPartialTypeSignatures
Allows us to leave holes in type signature.
{-# LANGUAGE PartialTypeSignatures #-}
v :: Either _ Bool
= Left 3
v
{-
Hi.hs:3:13: warning: [-Wpartial-type-signatures] …
• Found type wildcard ‘_’ standing for ‘Integer’
• In the first argument of ‘Either’, namely ‘_’
In the type ‘Either _ Bool’
In the type signature: v :: Either _ Bool
|
-}
Another example with a 3rd party library (clash):
import Clash.Prelude
v1 :: Vec _ Bool
=
v1 :>) True ((:>) False ((:>) True Nil)) (
NoImplicitPrelude
GHC implicitly imports Prelude
by default. This can be disabled with this extension.
GADTs
Allows to define generalized algebraic data types.
GADTSyntax
and MonoLocalBinds
.{-# LANGUAGE GADTs #-}
data Literal a where
NumLit :: Int -> Literal Int
BoolLit :: Bool -> Literal Bool
CPP
Find macros already defined:
# Some foo.hs file is needed, but it isn't used...
$ touch foo.hs
$ ghc -E -optP-dM -cpp foo.hs
LambdaCase
case
but differentAllows to say
\case { p1 -> e1; ...; pN -> eN }
instead of
\freshName -> case freshName of {
p1 -> e1
...
pN -> eN
}
—
Casing on multiple args (scrutinees) also possible with cases
(from GHC 9.4.1):
\cases { p11 ... pM1 -> e1; ...; p1N ... pMN -> eN }
would be same as a function f
like:
f p11 ... pM1 -> e1
f p12 ... pM2 -> e2
...
f p1N ... pMN -> eN
\case { p1 -> e1; ...; pN -> eN }
is same as
\freshName -> case freshName of
p1 -> e1
...
pN -> eN
Example:
λ> :set -XLambdaCase
λ> f = \case {0 -> "zero"; 1 -> "one"; otherwise -> "other"}
λ> f 0
"zero"
λ> f 1
"one"
λ> f 2
"other"
Reference: https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/lambda_case.html
Arrows
Control.Arrow
ExistentialQuantification
https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/existential_quantification.html
Allows us to use forall
in the type of data constructors, where it plays the role of an existential quantification.
Example:
data Stream a = ∃s. Stream (s -> Maybe (s, a))
is written as
{-# LANGUAGE ExistentialQuantification #-}
data Stream a = forall s. Stream (s -> Maybe (s, a))
forall
is used for ∃
..forall
is also used to mean universal quantification.forall
assumes different meanings.
By default, a forall
for universal quantification is implicit in Haskell types.
Type | Same as |
---|---|
foo :: a -> b | foo :: forall a b. a -> b |
But forall
is not a haskell keyword and it can't be used without extensions.
ExplicitForall
extension can be used to write the forall
for universal quantification explicitly.
RankNTypes
allows us to 'use forall
nested in type signatures, so that it does not apply to the whole type signature but just the part of it'ʳ.
https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/rewrite_rules.html#rewrite-rules
Read: A history of haskell 2007: https://dl.acm.org/doi/pdf/10.1145/1238844.1238856