These extensions simply enhance Haskell’s core syntax without providing any actually new semantic features.
PostfixOperators
Available in: All recent GHC versions
The PostfixOperators
extension allows you some slight extra leeway with Haskell’s operator section syntax. Normally, when you write, for example:
(4 !)
it expands into:
\x -> 4 ! x
or, equivalently:
\x -> (!) 4 x
PostfixOperators
instead expands this left section into:
(!) 4
which may look the same to you initially, and it behaves the same way where they both compile, but the new form allows GHC to be somewhat more lenient about the type of (!)
.
For example, (!)
can now be the factorial function and have the type:
(!) :: Integer -> Integer
Unfortunately, PostfixOperators
does not allow you to define operators in postfix fashion, it just allows you to use them that way.
Try it out!
{-# LANGUAGE PostfixOperators #-}
(!) :: Integer -> Integer
(!) n | n == 0 = 1
| n > 0 = n * ((n - 1) !)
| otherwise = error "factorial of a negative number"
main = print (4 !)
TupleSections
Available in: GHC 6.12 and later
The TupleSections
extension allows you to omit values from the tuple syntax, unifying the standard tuple sugar with the tuple constructor syntax to form one generalized syntax for tuples.
Normally, tuples are constructed with the standard tuple sugar, which looks like this:
(1, "hello", 6.5, Just (), [5, 5, 6, 7])
This could be considered shorthand for the following explicit tuple constructor use:
(,,,,) 1 "hello" 6.5 (Just ()) [5, 5, 6, 7]
However, the explicit tuple constructor (,,,,)
could just as easily be considered section sugar for tuples, expanding to:
\v w x y z -> (v, w, x, y, z)
Looking at it this way allows us to ask, “Why can’t we partially section a tuple? After all, (+)
is valid, (,)
is valid, and (1 +)
is valid, but (1,)
is not valid. The TupleSections
extension fixes this oversight.
With TupleSections
you can now write, for example:
(1, "hello",, Just (),)
and have it mean the same as
\x y -> (1, "hello", x, Just (), y)
Try it out!
{-# LANGUAGE TupleSections #-}
main = print $ map (1, "hello", 6.5,, [5, 5, 6, 7]) [Just (), Nothing]
PackageImports
Available in: All recent GHC versions
Let’s say you want to import module Data.Module.X
from package package-one
, but package-two
is also installed and also contains a module named Data.Module.X
. You could try to mess with package hiding, either manually or through cabal, but sometimes you might want some other module from package-two
, so hiding it is not an option.
Enter the PackageImports
extension. Rather than writing:
import Data.Module.X
and hoping that GHC gets the one from the right package, PackageImports
lets you write:
import "package-one" Data.Module.X
and explicitly specify the package you want to import that module from. You can even import from a specific package version:
import "package-one-0.1.0.1" Data.Module.X
You can use PackageImports
in combination with any other variant of the import
syntax, and you can use both package-qualified imports and regular imports in the same file.
Try it out!
{-# LANGUAGE PackageImports #-}
import Data.Monoid (Sum(..))
import "base" Data.Foldable (foldMap)
import qualified "containers" Data.Map as Map
main = print . getSum . foldMap Sum $ Map.fromList [(1, 2), (3, 4)]
OverloadedStrings
Available in: All recent GHC versions
By default, Haskell’s numeric literals are polymorphic over Num
(in the case of integer literals) or Fractional
(in the case of decimal literals). That is, you can write:
a :: Int
a = 1
b :: Double
b = 1
c :: Float
c = 3.5
d :: Rational
d = 3.5
and it just works as expected.
String literals, on the other hand, are always of type String
, and are not polymorphic at all. The OverloadedStrings
extension corrects this, making string literals polymorphic over the IsString
type class, which is found in the Data.String
module in the base
package. That is, you can write:
a :: String
a = "hello"
b :: Text
b = "hello"
OverloadedStrings
also adds IsString
to the list of defaultable type classes, so you can use types like String
, Text
, and Bytestring
in a default
declaration.
Try it out!
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text.IO as T
main = do putStrLn "Hello as String!"
T.putStrLn "Hello as Text!"
UnicodeSyntax
Available in: All recent GHC versions
With the UnicodeSyntax
extension (along with the base-unicode-symbols
and containers-unicode-symbols
packages), you can use Unicode alternatives to many of the standard operators. The UnicodeSyntax
extension itself handles just the operators and symbols that are built into the Haskell language, whereas the base-unicode-symbols
package handles the operators and functions provided by the base
package and the containers-unicode-symbols
package handles the operators and functions provided by the containers
package.
For the package-based Unicode symbols, you need to import the appropriate syntax module. For example, if you wanted to use Unicode symbols when working with Data.Map
, you would import Data.Map.Unicode
.
The various aliased ASCII syntax pieces, values, and types, along with their UnicodeSyntax
equivalents, are as follows:
- From the
UnicodeSyntax
extension::
=∷
=>
=⇒
forall
=∀
->
=→
<-
=←
-<
=⤙
>-
=⤚
-<<
=⤛
>>-
=⤜
*
=★
- From the
base-unicode-symbols
package- From the
Prelude.Unicode
module - From the
Control.Applicative.Unicode
module - From the
Control.Arrow.Unicode
module - From the
Control.Category.Unicode
module - From the
Control.Monad.Unicode
module - From the
Data.Bool.Unicode
module - From the
Data.Eq.Unicode
module - From the
Data.Foldable.Unicode
module - From the
Data.Function.Unicode
module - From the
Data.List.Unicode
module - From the
Data.Monoid.Unicode
module - From the
Data.Ord.Unicode
module
- From the
- From the
containers-unicode-symbols
package- From the
Data.Sequence.Unicode
module - From the
Data.Set.Unicode
modulemember
=(∈)
flip
member
=(∋)
notMember
=(∉)
flip
notMember
=(∌)
empty
=(∅)
union
=(∪)
difference
=(∖)
\x y ->
union
(
difference
x y) (
difference
y x)
=(∆)
intersection
=(∩)
isSubsetOf
=(⊆)
flip
isSubsetOf
=(⊇)
\x y -> (x
/=
y)
&&
not
(
isProperSubsetOf
x y)
=(⊈)
\x y -> (x
/=
y)
&&
not
(
isProperSubsetOf
y x)
=(⊉)
isProperSubsetOf
=(⊂)
flip
isProperSubsetOf
=(⊃)
\x y ->
not
(
isProperSubsetOf
x y)
=(⊄)
\x y ->
not
(
isProperSubsetOf
y x)
=(⊅)
- From the
Data.Map.Lazy.Unicode
module (reexported by theData.Map.Unicode
module) - From the
Data.Map.Strict.Unicode
module - From the
Data.IntSet.Unicode
modulemember
=(∈)
flip
member
=(∋)
notMember
=(∉)
flip
notMember
=(∌)
empty
=(∅)
union
=(∪)
difference
=(∖)
\x y ->
union
(
difference
x y) (
difference
y x)
=(∆)
intersection
=(∩)
isSubsetOf
=(⊆)
flip
isSubsetOf
=(⊇)
\x y -> (x
/=
y)
&&
not
(
isProperSubsetOf
x y)
=(⊈)
\x y -> (x
/=
y)
&&
not
(
isProperSubsetOf
y x)
=(⊉)
isProperSubsetOf
=(⊂)
flip
isProperSubsetOf
=(⊃)
\x y ->
not
(
isProperSubsetOf
x y)
=(⊄)
\x y ->
not
(
isProperSubsetOf
y x)
=(⊅)
- From the
Data.IntMap.Lazy.Unicode
module (reexported by theData.IntMap.Unicode
module) - From the
Data.IntMap.Strict.Unicode
module
- From the
Try it out!
{-# LANGUAGE UnicodeSyntax #-}
import Data.List.Unicode ((∪))
import qualified Data.Map as M
import Data.Map.Unicode ((∆))
main ∷ IO ()
main = do print $ [1, 2, 3] ∪ [1, 3, 5]
print $ M.fromList [(1, 2), (3, 4)] ∆ M.fromList [(3, 4), (5, 6)]
RecursiveDo
and DoRec
Available in: All recent GHC versions
The RecursiveDo
extension (as well as its deprecated synonym DoRec
) enables syntactic sugar for value recursion in a monadic context. “What on Earth does that mean?” you might ask. To explain, let’s take a look at how let
behaves in Haskell.
let
in Haskell allows lazy recursion; that is, you can write:
main = print $
-- show
let x = fst y
y = (3, x)
in snd y
-- /show
However, do
in Haskell does not allow lazy recursion; in fact, it doesn’t allow recursion at all. If you try to write a recursive binding in do notation, it will fail; for example, the following code will cause an error that complains about y
not being in scope:
{-# LANGUAGE StandaloneDeriving #-}
import Control.Monad.Identity
deriving instance (Show a) => Show (Identity a)
main = print ((
-- show
do x <- return $ fst y
y <- return (3, x)
return $ snd y
-- /show
) :: Identity Integer)
However, sometimes we want to be able to use value recursion but still need to be within a monad. The MonadFix
type class, from the Control.Monad.Fix
module in the base
package, provides an mfix
function that helps us do exactly that, but the results, while they work, are not very pretty:
{-# LANGUAGE StandaloneDeriving #-}
import Control.Monad.Identity
deriving instance (Show a) => Show (Identity a)
main = print ((
-- show
do y <- mfix $ \y0 -> do x <- return $ fst y0
y1 <- return (3, x)
return y1
return $ snd y
-- /show
) :: Identity Integer)
The RecursiveDo
extension provides sugar for using mfix
this way, so that the previous example can be equivalently rewritten as:
{-# LANGUAGE RecursiveDo, StandaloneDeriving #-}
import Control.Monad.Identity
main = print ((
-- show
mdo x <- return $ fst y
y <- return (3, x)
return $ snd y
-- /show
) :: Identity Integer)
RecursiveDo
also provides a second type of syntactic sugar for mfix
that uses the rec
keyword instead of the mdo
keyword. The rec
-based sugar is somewhat more direct and “low-level” than the mdo
-based sugar. In terms of the rec
sugar, our running example is expressed as:
{-# LANGUAGE RecursiveDo, StandaloneDeriving #-}
import Control.Monad.Identity
main = print ((
-- show
do rec x <- return $ fst y
y <- return (3, x)
return $ snd y
-- /show
) :: Identity Integer)
The two types of sugar are subtly different in meaning, and the difference has to do with something called segmentation.
When GHC encounters a let
binding, rather than naïvely binding all of the variables at once, it will divide (or segment) them into minimal mutually-dependent groups. For example, take this expression:
let x = 1
y = (x, z)
z = fst y
v = snd w
w = (v, y)
in (snd y, fst w)
Instead of just binding everything in a single group, GHC improves the code’s efficiency somewhat by treating it as though you’d actually written something like:
let x = 1
in let y = (x, z)
z = fst y
in let v = snd w
w = (v, y)
in (snd y, fst w)
In a pure let
binding, the only way this might matter is performance; the semantics of the code is guaranteed to not change. However, segmenting monadic code might produce unexpected results, because mfix
has to deal with the monadic context somehow during the value recursion, and segmenting a set of bindings into minimal groups could potentially change the meaning of the code.
Only mdo
segments its bindings. rec
does no segmentation at all, instead translating to calls to mfix
exactly where you put rec
s in the original code. This means that, in the following example, the first two of the following three expressions are equivalent to each other, but the third one is not equivalent to either of the first two:
-- | expression 1 (equivalent to expression 2)
mdo x <- return 1
y <- return $ (x, z)
z <- return $ fst y
v <- return $ snd w
w <- return (v, y)
return (snd y, fst w)
-- | expression 2 (equivalent to expression 1)
do x <- return 1
rec y <- return $ (x, z)
z <- return $ fst y
rec v <- return $ snd w
w <- return (v, y)
return (snd y, fst w)
-- | expression 3 (not equivalent to expression 1 or expression 2)
do rec x <- return 1
y <- return $ (x, z)
z <- return $ fst y
v <- return $ snd w
w <- return (v, y)
return (snd y, fst w)
Both expression 1 and expression 2 translate roughly to:
do x <- return 1
(y, z) <- mfix $ \(y0, z0) -> do y1 <- return $ (x, z0)
z1 <- return $ fst y0
return (y1, z1)
(v, w) <- mfix $ \(v0, w0) -> do v1 <- return $ snd w0
w1 <- return (v0, y)
return (v1, w1)
return (snd y, fst w)
On the other hand, expression 3 translates roughly to:
do (x, y, z, v, w) <- mfix $ \(x0, y0, z0, v0, w0) -> do x1 <- return 1
y1 <- return $ (x0, z0)
z1 <- return $ fst y0
v1 <- return $ snd w0
w1 <- return (v0, y0)
return (x1, y1, z1, v1, w1)
return (snd y, fst w)
Try it out!
{-# LANGUAGE RecursiveDo #-}
import Control.Monad.State.Lazy
comp = do x0 <- get
modify (+1)
x1 <- get
rec y <- return $ (x0, fst z)
z <- return $ (x1, fst y)
put 3
return (y, z)
main = print $ runState comp 1
WARNING: In GHC versions before 7.6, there was a lot of churn in the meanings of the RecursiveDo
and DoRec
extensions and their relationship to each other. For such older GHC versions, the above discussion may be partially or wholly inaccurate; consult your GHC version’s User’s Guide for more detailed information.
LambdaCase
Available in: GHC 7.6 and later
The LambdaCase
extension is very simple. Any time you would otherwise have written:
\x -> case x of ...
you can instead simply write
\case ...
which is both shorter and doesn’t bind x
as a name. The Layout Rule works as usual with LambdaCase
, so, for example:
[Just 1, Just 2, Nothing, Just 3] `forM_` \x -> case x of
Just v -> putStrLn ("just a single" ++ show v)
Nothing -> putStrLn "no numbers at all"
can be shortened to:
[Just 1, Just 2, Nothing, Just 3] `forM_` \case
Just v -> putStrLn ("just a single" ++ show v)
Nothing -> putStrLn "no numbers at all"
Try it out!
{-# LANGUAGE LambdaCase #-}
import Control.Monad (forM_)
-- | should print:
-- @["just a single 1","just a single 2","no numbers at all","just a single 3"]@
main = [Just 1, Just 2, Nothing, Just 3] `forM_` \case
Just v -> putStrLn ("just a single " ++ show v)
Nothing -> putStrLn "no numbers at all"
EmptyCase
Available in: GHC 7.8 and later
The EmptyCase
extension allows you to write a case
statement that has no clauses; the syntax is case
e
of {}
(where e
is any expression). If you also have LambdaCase
enabled, you can abbreviate \x -> case x of {}
to \case {}
This is most useful when you have a type that you know for sure has no values, but Haskell‘s syntax and type system force you to do something with a hypothetical such value anyway. Without EmptyCase
, you could just use error
or undefined
, or otherwise diverge, and such an action is still possible; however, using an empty case
statement for such things is more indicative of intent, and holds some promise of being better supported by the exhaustivity checker in the future.
MultiWayIf
Available in: GHC 7.6 and later
The MultiWayIf
extension allows you to use the full power of Haskell’s guard syntax in an if
expression. For example, this code:
if x == 1
then "a"
else if y < 2
then "b"
else "c"
can be rewritten as:
if | x == 1 -> "a"
| y < 2 -> "b"
| otherwise -> "d"
which is much nicer.
Try it out!
{-# LANGUAGE MultiWayIf #-}
fn :: Int -> Int -> String
fn x y = if | x == 1 -> "a"
| y < 2 -> "b"
| otherwise -> "c"
-- | should print:
-- @c@
main = putStrLn $ fn 3 4
WARNING: In GHC 7.6, the use of MultiWayIf
doesn’t affect layout, instead allowing the previous layout (prior to the if
keyword) to remain unchanged. This was changed shortly afterwards; in GHC 7.8 and later, MultiWayIf
affects layout, just like ordinary function guards do.
BinaryLiterals
Available in: GHC 7.10 and later
Standard Haskell allows you to write integer literals in decimal (without any prefix), hexadecimal (preceded by 0x
or 0X
), and octal (preceded by 0o
or 0O
). The BinaryLiterals
extension adds binary (preceded by 0b
or 0B
) to the list of acceptable integer literal styles.
Try it out!
{-# LANGUAGE BinaryLiterals #-}
-- | should print:
-- @(1458,1458,1458,1458)@
main = print (1458, 0x5B2, 0o2662, 0b10110110010)
NegativeLiterals
Available in: GHC 7.8 and later
Standard Haskell desugars negative numeric literals (of either integer or fractional form) by applying the negate
function from the Num
type class to the corresponding positive numeric literal (which is then expanded again using either fromInteger
or fromRational
, as appropriate). That is, the standard full desugaring of the literal -1458
is negate (fromInteger 1458)
. The NegativeLiterals
extension changes this, making negative numeric literals instead desugar as fromInteger
or fromRational
applied directly to a negative Integer
or Rational
value; that is, -1458
is desugared as fromInteger (-1458)
. In a sense, NegativeLiterals
swaps the positions of negation and conversion in the desugaring of numeric literals.
This doesn’t make a difference for the common cases, but certain edge cases can behave differently (and usually better) under NegativeLiterals
than otherwise. The example that the GHC User’s guide gives is 8-bit signed arithmetic, in which 128
is not representable but -128
is representable. The naïve desugaring of -128
to negate (fromInteger 128)
results in an overflow from 128
to -128
followed by a negation to 128
followed by another overflow back to -128
; meanwhile, the NegativeLiterals
desugaring to fromInteger (-128)
doesn’t waste cycles (or risk trapping on some architectures), but instead produces the appropriate value from the start. Other examples might actually change behavior rather than simply be less efficient; you should make sure that you understand a piece of numeric Haskell code fairly well before enabling or disabling NegativeLiterals
for it.
Try it out!
{-# LANGUAGE NegativeLiterals #-}
main = do print (-1 :: ExplicitNegation Integer)
print (negate 1 :: ExplicitNegation Integer)
print (-1.5 :: ExplicitNegation Rational)
print (negate 1 :: ExplicitNegation Rational)
-- /show
-- this type exists solely to explicitly mark where negation happens
data ExplicitNegation n = Value n | Negate (ExplicitNegation n) deriving Show
collapseNegation :: Num n => ExplicitNegation n -> n
collapseNegation (Value x) = x
collapseNegation (Negate v) = negate $ collapseNegation v
instance (Eq n, Num n) => Eq (ExplicitNegation n) where
v == w = collapseNegation v == collapseNegation w
instance (Ord n, Num n) => Ord (ExplicitNegation n) where
v `compare` w = collapseNegation v `compare` collapseNegation w
instance Num n => Num (ExplicitNegation n) where
v + w = Value $ collapseNegation v + collapseNegation w
v * w = Value $ collapseNegation v * collapseNegation w
negate = Negate
abs = Value . abs . collapseNegation
signum = Value . signum . collapseNegation
fromInteger = Value . fromInteger
instance Fractional n => Fractional (ExplicitNegation n) where
recip = Value . recip . collapseNegation
fromRational = Value . fromRational
NumDecimals
Available in: GHC 7.8 and later
Standard Haskell gives the polymorphic type (Fractional a) => a
to otherwise-unconstrained fractional numeric literals; however, some such literals are guaranteed to actually be integers, because they have an exponent (whether implicit or explicit) that is larger than the distance from the decimal point at which their last non-zero digit occurs (for example, 4.65690e4
is “the same number” as 46569
, which is clearly an integer). The NumDecimals
extension exploits this fact by giving fractional literals which are “really just integers” the more general type (Num a) => a
instead.
Try it out!
{-# LANGUAGE NumDecimals #-}
-- notice that this code will not compile if
-- '1.6e1' isn't allowed to be an 'Integer'
main = print (1.6e1 `div` 5 :: Integer)
DoAndIfThenElse
Available in: GHC 7.0 and later
TODO
NondecreasingIndentation
Available in: GHC 7.2 and later
TODO