Any, All, and the Hidden Power of lolnogenerics

This is going to sound really odd, especially if you have have some passing familiarly with Idris, but Idris doesn't actually have generics. Sure, it has something that looks like generics, and can do everything generics can do, but it isn't actually generics, at least not in terms of the usual conceptual framework programmers have for generics. What Idris actually has is something more fundamental, in a sense simpler than generics, yet infinitely more flexible.

But These Really Look Like Generics

Lets consider an example, map, the function that applies another function to each element in some arbitrary collection. For our purposes, lets say it has the following type signature:

map1 : Functor t => (f : a -> b) -> (xs : t a) -> t b

And if you are thinking this sure looks like it has generics, you would be right. This function certainly appears to be generic over the types a and b, as well as any type t that implements Functor, and by extension the type of the function f. But do not let "looks like" fool you. The layers of sugar present in Idris create an illusion, and things are not quite what they seem.

Note

In the following few sections, I will be ignoring multiplicities/linear types for the sake of simplification, as they aren't materially relevant to immediate topic.

The => syntax, usually used to bound a type such that it implements an interface, is actually just syntactic sugar, decomposing into an auto-implicit argument. We can rewrite map as follows without changing it's meaning:

map2 : {auto functor_impl : Functor t} -> (f : a -> b) -> (xs : t a) -> t b

The implicit binding that happens when an unbound lowercase argument appears, such as the a, b, and t in this function's signature, is yet more sugar. They all get lifted into their own implicit arguments1. Let's rewrite map again to take this into account:

Tip

t : Type -> Type is implied by Functor t

map3 : {a : Type} -> {b : Type} -> {t : Type -> Type} -> {auto functor_impl : Functor t}
  -> (f : a -> b) -> (xs : t a) -> t b

auto-implicits are another fiction, getting filled in during elaboration. Reducing them out, we get:

map4 : {a : Type} -> {b : Type} -> {t : Type -> Type} -> {functor_impl : Functor t}
  -> (f : a -> b) -> (xs : t a) -> t b

We can check that we are on the right track by inspecting the standard library's map function at the REPL:

Tip

The :ti REPL command shows the full type signature of the provided value, including implicits.

λΠ〉 :ti map
Prelude.map : {0 b : Type} -> {0 a : Type} -> {0 f : Type -> Type} -> Functor f =>
(a -> b) -> f a -> f b

Implicits themselves are yet another sweet fantasy, the barest core of Idris does not have them, they get converted into explicit arguments during the lowering process, before type checking completes. In the lowest level core language, map looks more like this:

map5 : (a : Type) -> (b : Type) -> (t : Type -> Type) -> (functor_impl : Functor t)
  -> (f : a -> b) -> (xs : t a) -> t b

To try and gain a sense of perspective, lets translate our fully lowered map into a Rust function signature. To allow us to ignore Rust's lack of higher kinded types2, and make it a bit less of a mouthful, we'll ignore the polymorphism over Functor, and manually monomorphize it over List. Otherwise, we'll do a direct translation without regard for the limitations of Rust's type system, and clean it up in the next step:

fn map(A: Type, B: Type, f: Fn(A) -> B, xs: List<A>) -> List<B> { ... }

Wait, uh, huh... Ignoring for a second that this would never work as written, because types aren't values in Rust and Rust evaluates function signatures "all at once" so to speak, not allowing for dependency between arguments, this function signature... doesn't have any generics, at least not in the sense of Rust's generics.

We are going to have to perform some modifications to the Rust version for it to actually work in Rust's type system. We'll ignore the whole "family of function interfaces" situation, since it's not salient to the point of this article. After extracting our type arguments into generics we are left with:

fn map<A, B>(f : Fn(A) -> B, xs: List<A>) -> List<B> {...}

If you squint a bit, its almost like the type arguments are still regular arguments, just lifted into ~special~ ones that don't quite play by the same rules. As with any time you insert an object that's almost like one of the fundamental objects, but ~special~, into a system, this comes with the addition of all sorts of arbitrary restrictions. Rust's generics are heavily restricted compared to normal arguments, and extremely heavily restricted compared to the dependently typed version.

Approaching from the dependently typed direction, slowly reducing the Idris version of map into its Rust equivalent, it becomes clear that it's appropriate to think of the-thing-Idris-has as the more fundamental concept, and Rust's generics as a restricted subset. On the dependently typed side, instead of "generics" existing as their own first class construct in the type system, they show up as a specific invocation of a more general aspect of the system, just another case of types depending on values. Only, in this instance, the values being depended on are themselves types.

This deeper integration into the overall type system often simplifies the logical burden of dealing with complex structures, and comes with numerous other benefits, placing many useful magic tricks at our disposal.

Note

It is still entirely appropriate to refer to the-thing-that-Idris-has as "generics" in context. It is a fundamentally different type of object than what rust has, and doesn't really exist as an independent concept within the type system, but it is still most often used as if it was generics.

I am sticking to my terminology guns to make the main point of this article more clear, but people will still understand what you are talking about if you speak of generics in the context of a dependently typed language.

We've gotten a pretty good idea of how the-thing-that-Idris-has compares to Rust's generics, but we are still missing some insights about it from the Idris side. Lets jump to the least complicated function we can find and consider the identity function:

id : a -> a
id x = x

If we query it's debugging information at the REPL:

λΠ〉 :di DependentNuggets.AnyAllLolnogenerics.id
DependentNuggets.AnyAllLolnogenerics.id
Arguments [{arg:0}, {arg:1}]
Compile time tree: {arg:1}
Erasable args: [0]
Inferrable args: [0]
Compiled: \ {arg:1} => {arg:1}
Flags: inline, total

It tells us that our id function has two arguments, the first of which is both erasable, meaning it doesn't have to exist at runtime, and inferable, meaning it can be forced to take on a particular value by type checking alone. This is a bit odd, we only wrote id with one argument.

Let's try applying a round of our desugaring rules from above to see if we can figure out what's going on:

Note

We are now going to consider linearity. The arguments generated by the compiler for unbound lowercase implicits are given multiplicity 0, meaning they must be consumed exactly 0 times at runtime, forcing their erasure.

id' : {0 a : Type} -> a -> a
id' x = x

Running :di on this again, we can see we are on the right track:

λΠ〉 :di id'
DependentNuggets.AnyAllLolnogenerics.id'
Arguments [{arg:0}, {arg:1}]
Compile time tree: {arg:1}
Erasable args: [0]
Inferrable args: [0]
Compiled: \ {arg:1} => {arg:1}
Flags: inline, total

So we now know that {0 a : Type} -> a -> a is the actual type signature of id. While one could look at this as a function that's generic over types, there is a much more interesting interpretation: id is a function from a type a to the monomorphic/non-generic identity function for values of a.

Things get even more interesting if we un-erase the type argument, we can then pattern match over the type, and make practical use of this "function from a type to another function" concept in a way that Rust programmers might recognize as similar to specialization:

Tip

Using Typecase like this does require that the type argument is un-erased, and will often result in the types actually existing at runtime in the compiled code. This, however, isn't really idiomatic, un-erased types are very rare to find in typical Idris code, and you can always tell whether or not a type is allowed to exist at runtime by inspecting the type signatures involved.

reallyFunnyId : {a : Type} -> a -> a
reallyFunnyId {a = String} = const "This is most likely not the string given as input"
reallyFunnyId {a = Nat} = (+ 1)
reallyFunnyId {a} = \x => x

Before addressing some of the more advanced type-level programming concepts in this article, it will be helpful to develop an understanding of how interfaces work in Idris. At first glance, interfaces in Idris are quite similar to traits in Rust, with a few notable differences. Importantly, you can implement the same Idris interface for the same type multiple times, and implementations can be given individual names allowing the programmer to disambiguate when needed, eliminating the need for an equivalent to the orphan rule3. And yes, this does mean that package A can implement package B's interfaces for types in package C without issue in Idris.

When we implement a function that's polymorphic over an interface in Idris, we generally default to using the => syntax. Consider this example function:

greet : Show t => (x : t) -> String
greet x = "Hello \{show x}"

As previously discussed, the => argument desugars into an auto-implicit, like so:

greet' : {auto _ : Show t} -> (x : t) -> String
greet' x = "Hello \{show x}"

So our greet function, which is polymorphic over any type t implementing the Show interface, is actually a function that accepts a value of Show t and returns a function from a value of type t to a String. That's all well and good, but what is this Show t type, and what do values of type Show t look like?

For any given interface I, a value of type I t serves as a witness that the type t implements the interface I. This isn't some highly abstract forgetful witness though, it's a constructive witness, proving the implementation by providing the implementing functions for each of the interface methods.

This is quite similar to the concept of a vtable, or a trait object in Rust4. If we take a look at the type of a bare interface method, such as show from Show:

λΠ〉 :type show
Prelude.show : Show ty => ty -> String

We see that the interface method itself accepts the implementation witness as an auto-implicit, and it uses that witness to dispatch to the corresponding method from the provided implementation.

Since interfaces in Idris are passed into functions as normal arguments, the language has no issues with the same interface being implemented for the same type multiple times, as only one can ever be passed in through single argument at a time. Idris allows us to give names to specific implementations, in square brackets ([]) before the implementation, allowing the programmer to disambiguate when needed, like so:

[funnyShow]
Show String where
  show _ = "Ha Ha, stole your string!"

This name, funnyShow, is a normal first class value. Since this is an implementation of Show for String, we might expect that this value has type Show String, inspecting the type at the REPL, we see that is the case:

λΠ〉 :type funnyShow
DependentNuggets.AnyAllLolnogenerics.funnyShow : Show String

Idris will default to the unnamed implementation when there is only one unnamed implementation in scope, regardless of the presence of named implementations. We can see that simply defining a named implementation of Show for String doesn't affect normal use of our greet function from earlier:

λΠ〉 :exec putStrLn $ greet "Tim"
Hello "Tim"

We can, however, explicitly instruct Idris to use our named implementation, and get the expected result:

Tip

Even though the implicit arguments created through => syntax don't have names, we can still explicitly specify values for them using @{} syntax. In the following example, @{funnyShow} reads as "Set the value of the next implicit argument to funnyShow".

λΠ〉 :exec putStrLn $ greet @{funnyShow} "Tim"
Hello Ha Ha, stole your string!

From time to time, it becomes necessary to have values of multiple different types in a collection. In languages with less expressive type systems, this might require implementing a sum type/enum with a variant for each type we wish to contain, such as the following Rust example:

enum Heterogeneous {
    TString(String),
    Tu64(u64),
    ...
}

fn doThingsHeterogenously(xs: Vec<Heterogeneous>) -> ... {
    for x in xs {
       match x {
           TString(string) => ...,
           Tu64(number) => ...,
       } 
    }
}

This solution incurs a fair amount of boilerplate, and also has some other drawbacks. For instance, our Vec<Heterogeneous> type can't contain any values of any type that isn't explicitly addressed in the Heterogeneous enum, if we want our Vec to contain any other type, we have to go back and add it to the enum. If the Heterogeneous enum is exposed in the public api, then there are also semver concerns with adding new variants, and simply marking the enum #[non_exhaustive] may not be suitable in every case.

If we want to work with an open universe of types instead of a closed universe, to use the dependent typing parlance, Rust does provide another option: trait objects. We could instead write something like:

fn displayThingsHeterogenously(xs: Vec<Box<dyn Display>>) -> ... {
    for x in xs {
        let formatted = format!("{x}");
        ...
    }
}

This lets us, at least nominally, put any value of any type that implements Display in our Vec, but trait objects come with plenty of drawbacks of their own. Trait objects don't have a fixed size, so in general we can only talk about pointers to them, adding boilerplate. Additionally, not every trait is dyn-compatible(also known as object safe)5. Many of the more expressive features of the type system become off-limits for use in our trait if we want it to be dyn-compatible. For instance, methods in dyn-compatible traits aren't allowed to have any type parameters at all!

Idris has many more comprehensive solutions for us to employ, allowing us to get the best of both worlds, relative to the above Rust solutions, keeping our types fully concrete without forgetful upcasting, but still allowing us to keep our universes open and not arbitrarily restricted to a specifically enumerated list of types.

One of the simplest heterogeneous collection types in Idris is HList, a list like structure parameterized over a list of types where each type in the list describes the type contained in the corresponding position of the HList. HList can be defined like so:

Note

This definition is made with a ' appended to its name and left un-exported in its own namespace to avoid name collision with the standard library HList, which we will be using for the remainder of this article.

namespace HListDefinition
  data HList' : List Type -> Type where
    Nil : HList' []
    (::) : (x : t) -> (xs : HList' ts) -> HList' (t :: ts)

In addition to collecting the types of the contained values into a list at the type level, this structure has a few other interesting properties:

HLists are most useful when combined with other dependently typed constructs, serving as a foundational concept for type level programming, but they still have many uses on their own. As we have seen in Row Polymorphic Programming, they can be used to build ad-hoc struct-like entities with convenient syntax for the caller, to provide a simple example:

numberStringBool : HList [Nat, String, Bool] -> String
numberStringBool [number, string, bool] = "The number \{number} is \{string}: \{show bool}"
λΠ〉 numberStringBool [3, "even", False]
"The number 3 is even: False"

This simple usage isn't too much different from just using a tuple. Lets try to show off the type level programming capability a bit better by expressing a little bit of a non-trivial contract in the type. Say we want to be able to show a list of objects with separators between them, and we want those separators to be arbitrary strings that can be different in each position. For a list of n things, we can build a list of types to describe this collection by replicating the type n times and interspersing String into it:

showNThingsWithSeparators : Show t => 
  (n : Nat) -> (xs : HList (intersperse String (replicate n t))) -> String
showNThingsWithSeparators 0 [] = ""
showNThingsWithSeparators (S 0) [x] = show x
showNThingsWithSeparators (S (S k)) (x :: (y :: xs)) = 
  show x ++ y ++ showNThingsWithSeparators (S k) xs

We can then call this with a manually specified HList, and see that the compiler accepts it and it works as expected:

λΠ〉 showNThingsWithSeparators 9 [1, "", 2, "", 3, ",", 4, "", 5, "", 6, ".", 0, "", 0, "", 0]
"123,456.000"

Now, if we get a bit lazy, and we want to call this function, but we don't actually want distinct separators in different positions, we can write a function to generate an appropriate HList from a List t and a constant separator:

intersperseH : Show t => 
  (xs : List t) -> (sep : String) -> HList (intersperse String (replicate (length xs) t))
intersperseH [] sep = []
intersperseH [x] sep = [x]
intersperseH (x :: (y :: xs)) sep = 
  x :: sep :: intersperseH (y :: xs) sep

And we can see it also works as expected:

λΠ〉 showNThingsWithSeparators 3 (intersperseH ['a', 'b', 'c'] ",")
"'a','b','c'"

Thinking back to our Rust example, where we had to lift the type arguments into ~special~ arguments, we can see that the List Type argument to the HList type constructor isn't ~special~ at all. Its just a normal list, that we can do normal list things to. And the types contained in that list behave just like regular values7 without the arbitrary restrictions that come with Rust's type arguments.

Think back to our id example above, where we showed that id is actually a function from a type to a monomorphic identity function. Consider this identity function over HLists:

hListId : HList ts -> HList ts
hListId [] = []
hListId (x :: xs) = x :: hListId xs

Applying our desugaring rules to its type signature, we get:

hListId' : {0 ts : List Type} -> HList ts -> HList ts

Instead of a function from a type to a monomorphic implementation, the structure of HList has given us a function from a list of types to a monomorphic implementation.

HList on its own is already pretty useful, but also somewhat limited. In the examples we've worked through so far, there are still all sorts of restrictions on the included types, such as the "either String or t" requirement in showNThingsWithSeperators. We haven't yet looked at anything equivalent to the Rust example of heterogeneous collections yet. To do that, we need a way to make general statements about all of the types in the list. This is where All comes in.

All "augments" a list with a witness that each value in the list satisfies a given "predicate". In this context, a predicate is a type of kind8 a -> Type, where a given value x : a satisfies a predicate Pred : a -> Type if a value of the type Pred x exists. Predicates are a quite general concept, interfaces can be thought of as predicates, and we will consider other examples as we continue through the article.

Note

As above, we are using a namespace to avoid conflicting with the standard library implementation

namespace AllDefinition
  data All : (p : a -> Type) -> (ts : List a) -> Type where
    Nil : All p []
    (::) : {0 x : a} -> (a : p x) -> (ps : AllDefinition.All p xs) 
      -> All p (x :: xs)

Notice how the types themselves still don't show up in the runtime representation, only the witnesses of the provided predicate. The types themselves need not exist at runtime, and in some situations, we can even get away with erasing the All entirely.

Notably, All can be considered a more fundamental concept than HList, since HList can be implemented in terms of All. The Idris standard library implements HList as simply an alias for All id9. As a predicate, id can be understood as a proof that an arbitrary type is inhabited, by way of presenting a value of that type, with no further restriction.

Think back to our examples of heterogeneous collections in Rust, with All in our toolkit, we can finally express the Idris equivalent:

Tip

imapProperty is a function provided by the standard library specifically for mapping an interface method over an HList, or another shape of All, when you have proof that every element of the list implements the interface.

displayH : All Show ts => HList ts -> String
displayH xs = 
  let shown : All (const String) _ = imapProperty Show show xs
      -- Our list has become homogenous, so we can forget that it was originally
      -- a heterogenous collection
      strings : List String = forget shown
  in "[\{joinBy ", " strings}]"

We can see that this works as expected:

λΠ〉 :exec putStrLn $ displayH [the Double 2.0, the Bool False, the Nat 11, the String "Hello!"]
[2.0, False, 11, "Hello!"]

Note that this does not have the drawback of the first Rust version, the "universe" of types it operates on is completely open, since Show can be implemented for any type anywhere. It also doesn't have the drawback of the second, there's no forgetful upcasting, or even casting at all! The types are still in their full, concrete forms, with no reference to them at runtime, we just don't have to reference the types directly as the All Show ts constraint ensures that each element in the HList is matched up with an appropriate Show implementation for its type.

To explore that concept more, lets manually implement the operation being performed by the imapProperty operation above:

showAll : All Show ts => HList ts -> List String
showAll {ts = []} @{[]} [] = []
showAll {ts = (t :: ts)} @{(show_x :: show_xs)} (x :: xs) = ?showAll_rhs

I've deliberately left it not fully implemented so we can inspect the hole and see what's going on with the types:

λΠ〉 :t showAll_rhs
 0 t : Type
 0 ts : List Type
   show_x : Show t
   show_xs : All Show ts
   x : t
   xs : All id ts
------------------------------
showAll_rhs : List String

As you can see, the type of x, t, is erased10, as such it doesn't exist at runtime, and the evaluation of our function can't depend on what t is. Even though we are forbidden from inspecting the value of t, we don't have to, we can still tell that show_x constitutes a valid Show implementation for t, enabling us to call show x, just from the type signatures alone.

Let's complete the implementation and show that it works as expected:

showAll' : All Show ts => HList ts -> List String
showAll' @{[]} [] = []
showAll' @{_ :: _} (x :: xs) = 
  show x :: showAll' xs 
λΠ〉 showAll' [the Nat 1, the Double 2.0, the Bool True]
["1", "2.0", "True"]

In the Rust example, in order to achieve this type of "open universe" polymorphism, we had to upcast into a trait object, which is a ~special~ type of value that glues together a particular value and the trait implementation over it, but doesn't fully behave like the normal values of the system.

In contrast, interface implementations in Idris aren't ~special~, they are normal first class values with no special behavior. We also don't have to do this "gluing together" of the value and the associated implementation into a single value, by keeping the implementation and the associated value separate while keeping them paired through the type signatures, we are free to forget the type of the value at runtime, while still being able to statically enforce that a given implementation will only ever be invoked against a value with the correct type.

If we inspect the full type signature of showAll':

λΠ〉 :ti showAll'
DependentNuggets.AnyAllLolnogenerics.showAll' : {0 ts : List Type} ->
All {a = Type} Show ts => HList ts -> List String

We can see that it is a function from a list of types to a function that accepts implementations of the Show interface for all of the types of the list, returning a monomorphic implementation of the underlying logic.

Sometimes, the behavior of the first Rust implementation, restricting the set of allowed types in the collection, is desirable. Idris provides us a few different ways to do so. Since we've mentioned predicates before, we'll start with those.

As previously mentioned a predicate is a type of kind Pred : a -> Type, that is considered satisfied for a given value x : a when a value of the type Pred x exists. We have already looked at interfaces, which are a type of predicate over types, but we can also straightforwardly define a "closed" type predicate as a sum type:

data Allowed : Type -> Type where
  StringAllowed : Allowed String
  NatAllowed : Allowed Nat
  BoolAllowed : Allowed Bool

This particular predicate is satisfied for String, Nat, and Bool, with the individual constructors serving as proof that the respective type is allowed. We can see that proof search is able to find instances of Allowed for the allowed types:

λΠ〉 the (Allowed Bool) %search
BoolAllowed

We can also see that a compiler allows us to create a well formed HList of Allowed types:

acceptsAllowed : All Allowed ts => HList ts -> ()
acceptsAllowed _ = ()

thisAllowedIsValid : ()
thisAllowedIsValid = acceptsAllowed [the Bool True, the Nat 1, the String "Hello"]

And that it rejects attempts to include types that aren't allowed:

failing
  thisAllowedIsNotValid : ()
  thisAllowedIsNotValid = acceptsAllowed [the Double 1.0]

This approach gives us a few paths to implement our running example of displaying a heterogeneous list of things. As one approach, we can implement a conversion function from our Allowed witness to a Show implementation:

allowedToShow : Allowed t -> Show t
allowedToShow StringAllowed = %search
allowedToShow NatAllowed = %search
allowedToShow BoolAllowed = %search

We can then use this function to convert a value of All Allowed ts into a value of All Show ts and use our previously defined displayH function:

displayAllowed : All Allowed ts => HList ts -> String
displayAllowed @{allAllowed} xs = 
  let allShow : All Show ts = mapProperty allowedToShow allAllowed
  in displayH xs
λΠ〉 :exec putStrLn $ displayAllowed [the Bool False, the Nat 42, the String "frog" ]
[False, 42, "frog"]

If we wanted to, we could also directly pattern match on the witnesses ourselves, which gives us a little bit more flexibility at the cost of some verbosity. For example, we could choose to output strings verbatim, only using show for the other types:

displayAllowed' : All Allowed ts => HList ts -> String
displayAllowed' xs = 
  let strings : List String = allowedsToStrings xs
  in "[\{joinBy ", " strings}]"
  where
    allowedsToStrings : All Allowed ts' => HList ts' -> List String
    allowedsToStrings @{[]} [] = []
    allowedsToStrings @{(StringAllowed :: _)} (y :: ys) = 
      y :: allowedsToStrings ys
    allowedsToStrings @{(NatAllowed :: _)} (y :: ys) = 
      show y :: allowedsToStrings ys
    allowedsToStrings @{(BoolAllowed :: _)} (y :: ys) =
      show y :: allowedsToStrings ys
λΠ〉 :exec putStrLn $ displayAllowed' [the Bool False, the Nat 42, the String "frog" ]
[False, 42, frog]

Instead of specifying our sum type as a predicate, we could, instead, build a normal enum-style sum type, and define a function from it to the corresponding type:

data Universe = TString | TNat | TBool

universeType : Universe -> Type
universeType TString = String
universeType TNat = Nat
universeType TBool = Bool

We'll also want a function to convert a list of Universe to a list of types, to avoid running into issues with the standard library's implementation of map:

universeTypes : List Universe -> List Type
universeTypes [] = []
universeTypes (x :: xs) = universeType x :: universeTypes xs

We can also implement a proof that every type in a list of types generated from a List Universe has a Show implementation:

universalShow : {us : List Universe} -> All Show (universeTypes us)
universalShow {us = []} = []
universalShow {us = (TString :: us)} = %search :: universalShow 
universalShow {us = (TNat :: us)} = %search :: universalShow
universalShow {us = (TBool :: us)} = %search :: universalShow

We can use our universeTypes function to define the list-of-types type argument to an HList in terms of a list of Universe values, and then invoke our universalShow proof to allow us to call displayH on that HList:

displayU : (us : List Universe) -> HList (universeTypes us) -> String
displayU us xs = displayH @{universalShow} xs
λΠ〉 :exec putStrLn $ displayU [TString, TNat, TBool] ["cat", 5, False]
["cat", 5, False]

This approach can often be a little bit more verbose, but comes with advantages of its own. For instance, this approach enables relatively ergonomic building of types from runtime inputs, which will be covered in a future article.

All is also useful outside the context of HLists, as it can apply any predicate over any list. Just as an example, you can use All with the IsSucc11 predicate, which is satisfied for Nats which are non-zero, to specify a list of non-zero numbers:

Tip

Since the All is constraining an explicit argument to this function, it has to come after that explicit argument in the argument list.

sumNonZeros : (xs : List Nat) -> All IsSucc xs => Nat
sumNonZeros xs = sum xs

We can see this function works when called on a list of non-zero numbers:

λΠ〉 sumNonZeros [1, 2, 3, 4, 5]
15

And we can also see that a call to sumNonZeros fails to compile if we try to include a 0 in the list:

failing
  oopsAZero : Nat
  oopsAZero = sumNonZeros [0, 1, 2, 3, 4, 5]

Sometimes, making a blanket statement about all the types in a list is too strong of a statement. Lets dial it back a bit and just make a statement about one arbitrary element in a list, through the Any type.

A value of type Any p xs proves that at least one element of xs satisfies the predicate p by encoding the position of that element in the xs:

namespace AnyDefinition
  data Any' : (p : a -> Type) -> (xs : List a) -> Type where
    Here : {0 x : a} -> p x -> Any' p (x :: xs)
    There : Any' p xs -> Any' p (x :: xs)

Any is a bit more niche, so we'll be exploring a more contrived use-case for it. Imagine we are working with some row types, which must have at least one identifying column, but it doesn't matter where that identifying column is in the row. We want to display such row types with the identifier in front of the the row.

First, we must describe what types are allowed to be an identifier, to keep things simple, we'll define a predicate that only accepts Nat:

data Identifier : Type -> Type where
  INat : Identifier Nat

Now we can write our special display function and try it out:

Tip

Proof search in Idris always tries the constructors to a type in order, as a result, Anys constructed by proof search will always point to the first item in the list that proof search can demonstrate satisfies the predicate. While this behavior is quite reliable, keep in mind that the caller can potentially manually construct a value of Any that points to a different location in the list. It may also be the case that proof search fails to demonstrate the predicate for the actual first value, but succeeds for some later value in the list, but I have personally not yet encountered this in practice.

displayWithIdent : Any Identifier ts => All Show ts => 
  HList ts -> String
displayWithIdent @{ident} xs = 
  let id = extractIdent ident xs
  in "\{id}: \{displayH xs}"
  where
    extractIdent : Any Identifier ts' -> HList ts' -> String
    extractIdent (Here INat) (z :: zs) = show z
    extractIdent (There x) (z :: zs) = extractIdent x zs
λΠ〉 :exec putStrLn $ displayWithIdent [the String "Cat", the String "meows", the Bool True, the Nat 0]
0: ["Cat", "meows", True, 0]

Concrete use cases for Any tend to be a bit more informed by the overall structure of the larger system, which makes it harder to give a brief survey with code examples, but other potential uses of any include:

There are plenty of other heterogeneous collections to consider in Idris with all sorts of varied use cases.

Data.List.Alternating provides a sort of restricted HList that alternates back and forth between two specific types, our showNThingsWithSeparators example from earlier can be thought of as using an ad-hoc implementation of Odd, the type of alternating list that starts and ends with the same type. Let's write an equivalent using Odd and try it out:

Tip

The functions in the where block are mutually recursive, and as Idris is a strictly declare-before-use language due to concerns related to dependent typing, we declare both the type signatures before implementing either body.

showAlternating : Show t => Odd t String -> String
showAlternating xs = 
  let strings = oddToStrings xs
  in joinBy "" strings
  where
    oddToStrings : Odd t String -> List String
    evenToStrings : Even String t -> List String
    oddToStrings (x :: xs) = show x :: evenToStrings xs
    evenToStrings [] = []
    evenToStrings (x :: xs) = x :: oddToStrings xs
λΠ〉 :exec putStrLn $ showAlternating [1, ",", 2, "", 3, "", 4, ".", 5, "", 6]
1,234.56

Row types are a form of augmented HList that provide all sorts of extra type-level programming tools.

Dependent lists and dependent maps are both heterogeneous collections that derive typing information from some aspect of the contained data. We will be giving both of these structures the proper treatment they deserve in future articles.


  1. In haskell parlance, this is an implicit forall↩︎

  2. While this is an important way in which Rust's type system is "weaker" then Idris's, its also not essential to understand the topic under discussion.↩︎

  3. See https://doc.rust-lang.org/reference/items/implementations.html#trait-implementation-coherence↩︎

  4. Though, notably, without all the arbitrary restrictions that trait objects have in Rust. To apply Rust parlance, all interfaces in Idris are intrinsically object safe with no exceptions or restrictions on the kinds of type signatures that interface methods can have.↩︎

  5. See https://doc.rust-lang.org/reference/items/traits.html#r-items.traits.dyn-compatible↩︎

  6. I personally like to think of tuples as the shadows cast by HLists on less expressive type systems.↩︎

  7. Because they are just regular values↩︎

  8. Idris doesn't actually have a notion of of "kinds", Idris 2 currently has Type : Type (the type of Type is Type), though this won't be the case forever, Idris 2 plans to implement Idris 1's hierarchy of universes.↩︎

  9. Idris isn't great about remembering that aliases are used when displaying types at the REPL or on your editor, when you see something of the form All id ts, that's probably an HList.↩︎

  10. The 0 in front of the variable indicates that it has multiplicity 0, meaning it's erased at runtime↩︎

  11. Historically known as NonZero↩︎