Type operators

In standard Haskell, operator symbols may only be used at the value level. The only exception to this is the function arrow, (->), which is a built-in type operator. GHC expands the role of operators with the TypeOperators extension, which makes it possible to use an operator as the name of a type.

The TypeOperators extension has been available since GHC 6.8.1 and implies the ExplicitNamespaces extension.GHC User Manual documentation for TypeOperators.

Defining type operators

By default, if you try to define a type whose name isn’t composed of letters, compilation fails and GHC suggests that you enable the TypeOperators extension. This happens regardless of whether you place the name in infix or prefix position.

An example of failing with infix notation:

λ> data a & b = Tuple a b

error:
    Illegal declaration of a type or class operator ‘&’
      Use TypeOperators to declare operators in type and declarations

An example of failing with prefix notation:

λ> data (&) a b = Tuple a b

error:
    Illegal declaration of a type or class operator ‘&’
      Use TypeOperators to declare operators in type and declarations

With the extension enabled, either of these declarations is permitted.

λ> :set -XTypeOperators

λ> data a & b = Tuple a b

Using type operators

You can use a type operator, in prefix notation, without any extensions enabled.

λ> x = Tuple 2 'c' :: (&) Int Char

However, you cannot use it in infix notation.

λ> x = Tuple 2 'c' :: Int & Char

error:
    Illegal operator ‘&’ in type ‘Int & Char’
      Use TypeOperators to allow operators in types

Using a type operator in infix notation requires enabling the TypeOperators extension.

λ> :set -XTypeOperators

λ> x = Tuple 2 'c' :: Int & Char

Example: Compose

In Functortown, we discuss the following example using the Compose type:

{-# LANGUAGE DerivingVia #-}

import Data.Functor.Compose

newtype ReaderIO env a = ReaderIO (env -> IO a)
    deriving (Functor, Applicative) via (Compose ((->) env) IO)

We emphasize that since type constructors are functions (at the type level), functor composition bears a great deal of similarity to function composition.Function composition: (.) Function composition is often written using the infix operator (.). If we wanted our code to emphasize the similarity as well, we might want to define (.) at the type level as an alias for the Compose type constructor.

{-# LANGUAGE DerivingVia, TypeOperators #-}

import Data.Functor.Compose

type (.) = Compose

newtype ReaderIO env a = ReaderIO (env -> IO a)
    deriving (Functor, Applicative) via ((->) env . IO)

Example: Generics

GHC genericsGHC.Generics defines types named (:+:) and (:*:).

-- | Sums: encode choice between constructors
infixr 5 :+:
data (:+:) (f :: k -> *) (g :: k -> *) (p :: k) =
    L1 (f p) | R1 (g p)
-- | Products: encode multiple arguments to constructors
infixr 6 :*:
data (:*:) (f :: k -> *) (g :: k -> *) (p :: k) =
    f p :*: g p

Join Type Classes for courses and projects to get you started and make you an expert in FP with Haskell.