Trying to understand `lastbut1 :: Foldable f => f a -> a`

I’m not getting this type signature and I likely just don’t understand the notation.

lastbut1 :: Foldable f => f a -> a
lastbut1 = fst . foldl (\(a,b) x -> (b,x)) (err1,err2)
  where
    err1 = error "lastbut1: Empty list"
    err2 = error "lastbut1: Singleton"

Since lastbut1 takes one argument (e.g., [1,2,3,4]) why is there both f and a on the right side of =>?

As I look at it I’m thinking that lastbut1 takes something foldable and returns a single value of the same type. So why wouldn’t the signature be:

lastbut1 :: Foldable a => a -> a

The notation I likely don’t understand is the space between f and a in f a -> a.

The f in this case point to a “container” over which you can fold, like a list []. Or to be specific, a type with kind * -> * (or Type -> Type).
The single argument [1,2,3,4], in this case is of type [Int] (or differently written [] Int: “list of int”). The list here [] is foldable, which is the f, the Int is just the elements of the foldable thing, which is the a.

If it would be Foldable a => a -> a, there would be a few problems:

  • You wouldn’t be able to fold a [Int] into an Int, because if a is [Int], the result would also be a [Int]. And folding all the Ints into one Int is the whole point of Foldable.
  • If [Int] would be Foldable (i.e. has a Foldable instance), that would also mean you’d have to reimplement instances for [String], [Char], [Double], etc. etc. etc. Which is a lot of copy pasting and generally superfluous, because it should just work over any list [] (which is why the f is just list, i.e. [])

Other Foldable types are Maybe, Map k, Set, etc. where you can also see, these are all types that need one more type to become a concrete type (MaybeMaybe a, Map kMap k a, SetSet a)

I hope this somewhat explains the type at least.

4 Likes

Here is how I would read the type signature Foldable f => f a -> a: the type of functions from a foldable container of as to an a. I think the thing that’s throwing you off is that (f a) is a type. How? Well, a is a type, and f is a function from types to types, so by applying f to the argument a, you get a new type f a. This kind of thing can be confusing when learning Haskell.

The point of this signature is to say: I’m a function that takes some kind of collection of as (could be a list, but could be anything else that’s an instance of the Foldable class too), and I’ll give you back an a.

1 Like

The GHCi :info command is your friend. (I’m cherry picking the info it shows.)

>:info Foldable
class Foldable t where
  ...
  null :: t a -> Bool
  length :: t a -> Int
  elem :: Eq a => a -> t a -> Bool

You’ll see in all the signatures for Foldable's methods, they have t a -> ; there’s no bare t -> .

Foldable is a “Constructor class” – that is, its type param t applies to the element’s type a to construct a Type. That’s what the first bit of :info is telling you:

type Foldable :: (* -> *) -> Constraint

You can read t a or the f a in Foldable f => f a -> ... as a structure containing elements a over which you can fold some operation on the as.

I find it possible to think about Foldable f meaning f is a Foldable and as such it needs a parameter to initialize (which is a). That works for me.

And I’m guess that f as a function means that Foldable f creates a class constructor and f a is the initialization where a is the value being passed into the constructor. Is that correct?

1 Like

No. Classes are best not though of as concrete things. The Foldable f is a constraint, meaning that there exists an implementation of Foldable for f. It also has no bearing on the semantics of f a later on.

You can think of f as a function that takes a type and returns another type.
For instance, f might be the list type, which would take a and turn it into [a]. This is easy to see for lists, because lists have special notation, but, in general, a parameterized type (in other languages it’s often called generic, but that means something else in Haskell) is a type constructor, so the type is represented by function application—just like Just x is what you get when you call Just on x, f x is just the way to write the type you get when you apply f to x.

1 Like

Expressions to the left of => are just conditions a type must fulfill in order for the function/value to exist for that type. For instance, 1 :: Num a => a means 1 is any type, as long as there exists an implementation of Num for it.

1 Like