Haskell’s expressive type system means that type signatures can carry
a lot of information. Haskell’s polymorphism means that you sometimes
write functions that work across an enormous range of types, and are
left wondering “what do I actually call my variables?”. It is often the
case that there’s nothing to say beyond “this variable is a Functor
”,
or “this variable is a monadic action”, and so a single-letter variable
name is appropriate. An unofficial and largely undocumented convention
has emerged around these variable names, and so I wanted to write them
all down in one place.
It should go without saying that single-letter variable names are not always the answer. Like point-free style, it sometimes obscures more than it helps and people get carried away with it. But when you have a highly polymorphic function and no good words to use, choosing the right letter can convey a surprising amount of meaning.
This dictionary is not and cannot be exhaustive. Variable naming often relies on context to convey information, and shorter variable names should only be used when they make sense in context. That context could be:
(...) =>
context to reference
“nearby” concepts, as in Monoid
and
Monad
;(k, v)
to
reference the key and value of a Map
entry; orposition a u t = u * t + (a * t * t) / 2
is reasonable if
the reader knows you’re talking classical mechanics.With the warnings out of the way, the dictionary is after the jump. The bulk of the dictionary documents type variables, where overly long variable names can blow out complicated type signatures. Important value-level variable names are also documented, and are explicitly labelled as such.
a
Arrow
,
but because of the common usage of a
as “arbitrary ground
type (type of kind Type
)”, this is often confusing. I
recommend arr
or infix k
instead.a
, b
, c
,
d
a
in a
Foldable t => t a
. Almost never used for higher-kinded
types, unless they’re kind-polymorphic (like
data Proxy (a :: k) = Proxy
).b
ByteString
. I personally am not
a fan of using b
or bs
for this: there is
often a short contextual word that describes what it actually is, and if
it truly is an arbitrary collection of bytes, then bytes
is
only five characters.c
A constraint (type variable of kind Constraint
).
(Sometimes) type variable of class Category
,
but that clashes with c
if you’re writing out a composition
operator. Consider cat
or infix k
as
alternatives.
-- From package `constraints`. Given evidence `e`,
-- produce a dictionary for constraint `c`:
class HasDict c e | e -> c
evidence :: e -> Dict c
-- From package `constraints-extras`:
class Has c f where
has :: forall a r. f a -> (c a => r) -> r
e
(As type or value) An “error” or exception type, though I
personally prefer ex
for true exceptions. Using
e
in a type like Either e a
indicates that
Either
is being used for its Monad
instance,
where Left
is considered an exceptional/early/error return,
and not as an unbiased choice between two types.
-- From packages `mtl`, `generic-lens`:
trySomething ::
MonadError e m, AsType SomeSpecificError e) =>
(SomeArgument ->
SomeResponse m
f
, g
, h
A Functor
or “Functor
-like” type,
including Applicative
,
Alternative
,
and their contravariant versions Contravariant
,
Divisible
,
and Decidable
.
(As value) An arbitrary function.
h
h
ead of a sequence, but the
x:xs
notation is more common.i
, j
An index: a type that identifies an element in a structure (a key
in a key-value map; an Int
for a list, vector, or sequence;
etc).
-- From package `indexed-traversable`:
class Functor f => FunctorWithIndex i f | f -> i where
imap :: (i -> a -> b) -> f a -> f b
instance FunctorWithIndex Int List
instance FunctorWithIndex k (Map k)
(As value) An integral value.
(As value, uncommon) An index into a data structure.
idx
is more common.
k
(As type or value) k
ey type of a key-value map, or
the key
of a K-V entry within such a map.
-- From package `containers`:
mapWithKey ::
-> a -> b) ->
(k Map k a ->
Map k b
(Sometimes) the arrows of a category, often written infix.
-- From package `categories`:
class Category k => HasTerminalObject k where
type Terminal k :: Type
terminate :: a `k` Terminal k
(As value) A continuation parameter. (Mnemonic:
k
ontinuation)
-- From package `transformers`:
runCont :: Cont r a -> (a -> r) -> r
= runIdentity (runContT m (Identity . k))
runCont m k -- ^-- The continuation parameter.
The “k
ind variable” for a type variables of
polymorphic kind.
data Proxy (a :: k) = Proxy
-- ^-- The variable `a` has polymorphic kind.
m
A Monoid
,
subclass of Monoid
, or a monoidal value.
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
A Monad
,
subclass of Monad
, or (as value) a monadic action.
(>>=) :: Monad m => m a -> (a -> m b) -> m b
(As value) a map (such as a Data.Map.Map k v
), but
with no contextual meaning.
For Monad
s and Monoid
s, n
is
sometimes also used when a second variable is needed, but is hard to
visually distinguish from m
. Consider m'
,
m1
and m2
, or (if using Monad
s as
Functor
s) f
and g
instead.
n
A type-level natural number.
(As value) A numeric (often Natural
or at least Integral)
quantity. Often used for the (single) numeric induction variable in a
recursive function.
p
(As value) A p
roposition — a Bool
with
no contextual meaning that we can see. All we care about is whether it
is True
or False
.
when :: Applicative f => Bool -> f () -> f ()
= if p then s else pure () when p s
(As value, rare) A “predicate”.
A predicate is almost always represented by a function
a -> Bool
and often named pred_
(pred
without the underscore clashes with a method from
class Enum
), or with the standard variable name
f
.
p
, q
Mnemonically, a Profunctor
,
or a profunctor value.
-- From package `profunctors`:
class Profunctor p where
dimap :: (a -> b) -> (c -> d) -> p b c -> p a d
lmap :: (a -> b) -> p b c -> p a c
rmap :: (b -> c) -> p a b -> p a c
A Bifunctor
,
or a bifunctor value. (The obvious first choice — b
— would
clash with the use of
a
/b
/c
/d
for
arbitrary types.)
class (forall a. Functor (p a)) => Bifunctor p where
bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
first :: (a -> b) -> p a c -> p b c
second :: (b -> c) -> p a b -> p a c
r
A “reader” or “environment” type, like the kind carried around in
a ReaderT
.
-- Constraints from packages 'mtl' and 'generic-lens':
doSomething ::
MonadReader r m, HasField' "apiKey" r ApiKey) =>
(AnArg ->
AResult m
A “return” or “result” type. Often used as the result type for streams and the like, as well as in type signatures for functions written in continuation-passing style:
-- From package `streaming`:
data Stream f m r
-- ^-- Result type of the stream.
-- From package `constraints-extras`:
class Has c f where
has :: forall a r. f a -> (c a => r) -> r
-- ^ ^
-- Continuation-passing style: the return type
-- of the function argument is the return type
-- of the whole function.
(As value) A result of some sort. (I personally prefer
res
.)
s
A “state type”, like the ones plumbed around by StateT
.
-- From package `mtl`.
modify :: MonadState s m => (s -> s) -> m ()
(As value, sometimes) An arbitrary String
or
Text
. str
is usually more common, or
c:cs
or ch:chs
if recursing over individual
Char
s (the s
suffix denotes plural “chars”;
this is also discussed in the section on x
, y
,
z
).
s
, t
, a
,
b
These four type variables often appear together in lenses or
other optics. The simplest complete example is a
Lens s t a b
: it can extract an a
from an
s
and overwrite it with a b
. Doing so would
produce a value of type t
.
-- A lens into the second part of a 2-tuple.
-- Inspired by package `lens`, but less polymorphic to make the point clear.
_2 :: Lens (x, c) (x, d) c d
-- ^ ^ ^ ^-- `b`: Type of the new value to put back in.
-- | | '---- `a`: Type of the value extracted from the tuple.
-- | '--------- `t`: Type of the tuple with a new value written back.
-- '---------------- `s`: Type of the initial tuple that is focused upon.
t
A Traversable
or Foldable
structure. The mnemonic for Traversable
is obvious, but
Foldable
is a superclass of Traversable
and so
is often called t
as well:
class Foldable t where
foldMap :: Monoid m => (a -> m) -> t a -> m
(As value) An arbitrary Text
value.
(As value, sometimes) A time value. I personally avoid using
t
for times, as times often have some contextual meaning
and can be given better names like now
or
createdAt
.
(As value, rare) The t
ail of a sequence, but the
x:xs
notation is more common.
v
v
alue type of a key-value map, or
the value of a K-V entry within such a map.w
Comonad
.
(Mnemonic: a comonad is dual to a monad, and w
is an
upside-down m
.)x
A type that is ignored, irrelevant, or inaccessible.
-- From package `streaming`:
maps ::
Monad m, Functor f) =>
(forall x. f x -> g x) ->
(-- ^-- The function passed in here cannot know anything
-- interesting about `x`, so it is "inaccessible".
Stream f m r ->
Stream g m r
-- From package `streaming`:
for ::
Monad m, Functor f) =>
(Stream (Of a) m r ->
-> Stream f m x) ->
(a -- ^-- This x is not referenced elsewhere; `for`
-- discards the result of the substreams.
Stream f m r
x
, y
, z
(As values) Arbitrary values about which nothing is known. Often
seen with a suffix s
to pluralise the variable and denote a
collection of arbitrary values. Read xs
, ys
,
zs
as “eckses”, “wyes”, and “zeds” (though American readers
may disagree on the final one).
map :: (a -> b) -> [a] -> [b]
map f list = case list of
-> []
[]
-- `x` binds one value from the list head;
-- `xs` binds many values from the list tail.
:xs -> f x : map f xs x
_
(Underscore)Thanks to Fraser Tweedale for suggesting that I include type
variables {s
, t
, a
,
b
}; type variable k
as a polymorphic kind
variable; term variables h
and t
for head and
tail; term variables k
and v
for key-value
entries; and _
as blank pattern.
Thanks to /u/gasche
on Reddit for reminding me that
p
is often used for p
redicates and
p
ropositions.
Thanks to /u/maxigit
on discourse.haskell.org for
suggesting e
rror, n
atural number,
s
tate, and t
ime.
Thanks to /u/enobayram
on Reddit for also suggesting
n
.
Thanks to /u/rhendric
on discourse.haskell.org for
suggesing w
as the type variable for Comonad
s,
and that c
is used for categories.
Thanks to /u/danidiaz
for reminding me that
c
is used for constraint variables.
Thanks to /u/taejo
on Reddit for suggesting an
example from classical mechanics that brings in its own single-character
variables.
Thanks to Tikhon Jelvis, who suggested expanding some important context.
Thanks to jonathrg
on HN, who reminded me about
r
as r
eader.