Difference between let and <-

While learning Haskell, I came across these kinds of lines

manager <- newManager tlsManagerSettings
let request = setRequestManager manager "http://httpbin.org/get"

From my observation both assign value to these two variables, so what’s the difference and what’s the use case?

4 Likes

<- is valid in do-notation and it doesn’t just assign a value but also “unwraps” or “extracts” it from a monad.

Let us look at a Maybe Int example. We will take Just 1 and increment it by 1.

Here is the first attempt with let:

onePlusOne :: Maybe Int
onePlusOne = do
    let valueInMaybe = Just 1
    Just (valueInMaybe + 1)

This code won’t compile obviously, because let valueInMaybe = Just 1 is just a binding; valueInMaybe is Just 1 and I can’t add one to it, Just 1 isn’t of the same type as 1, it isn’t an Int.

But consider:

onePlusOne :: Maybe Int
onePlusOne = do
    valueInMaybe <- Just 1
    Just (valueInMaybe + 1)

This code compiles and returns Just 2. valueInMaybe <- Just 1 extracts 1 from Just 1 and binds it to valueInMaybe. In the next line, we sum 2 integers, valueInMaybe and 1. Finally we wrap the result 2 back into a Maybe. And we have to, because do-notation is a jail, we can’t escape from; if we’re working with a specific monad, we have to give this monad back at the end.

So what happens if valueInMaybe <- Nothing? The next line won’t be executed and the function will return Nothing. This is the reason why we have to return Maybe Int at the end and not just Int, because the result can be Nothing.

10 Likes

To bring this back to the example in the question:

If you look at the type newManager :: ManagerSettings -> IO Manager you see that newManager applied to tlsManagerSettings will produce a value of type IO Manager. Haskell cannot automatically ‘cast’ this type to Manager, so you have to manually indicate that you want this value to be unwrapped by using the <- symbol in do notation.

The type setRequestManager :: Manager -> Request -> Request for setRequestManager on the second line indicates that this is a pure function. Applying setRequestManager to manager and "http://httpbin.org/get" produces a value of type Request which does not need unwrapping.

6 Likes

Thanks! @belka @jaror It’s pretty clear to me now :ok_hand: :grin:

This was very helpful. So <- only works with types that take a single argument? How does one work with other types in do?

As an experiment, I tried this in ghci:

data IntList = Nil | List {val :: Int, next :: IntList} deriving Show
do {x <- List 5 Nil; List 42 Nil}
do {(List v n) <- List 5 Nil; List 42 Nil}
do {v <- val (List 5 Nil); List 42 Nil}

Each <- line produced error messages that are probably very helpful to people who understand more than I do. :slight_smile:

(I included List 42 Nil at the end just to return (not return!) something that I know works without the previous <- assignment (or binding or unwrapping or whatever it’s called–not sure.))

1 Like

This was very helpful. So <- only works with types that take a single argument? How does one work with other types in do?

It is important here to make a clear distinction between terms and types. In your example:

data IntList = Nil | List {val :: Int, next :: IntList} deriving Show

The type is IntList and it has terms Nil :: IntList and List :: Int -> IntList -> IntList. You see that IntList is a type without any arguments, Nil is a term without arguments and List is a term with two arguments.

The main requirement to using a type with <- is that it needs to be a Monad*:

class Monad m where
  return :: a -> m a
  (>>=) :: m a -> (a -> m b) -> m b

This means that you must be able to define two functions: return and (>>=) with those types. For a concrete type like IntList you can just fill in IntList at every place where there is a m variable in the type signatures of those two functions. That yields: return :: a -> IntList a and (>>=) :: IntList a -> (a -> IntList b) -> IntList b. Here you can see the problem. IntList is a type without any arguments, so writing IntList a does not make any sense. To be able to use a type in do notation it needs to have at least one argument.

You can make your list a bit more general like this:

data List a = Nil | Cons a (List a) deriving Show

Now we can write an instance of Monad for this list*:

append :: List a -> List a -> List a
append Nil ys = ys
append (Cons x xs) ys = Cons x (append xs ys)

instance Monad List where
  return :: a -> List a
  return x = Cons x Nil

  (>>=) :: List a -> (a -> List b) -> List b
  Nil       >>= _ = Nil
  Cons x xs >>= f = append (f x) (xs >>= f)

And now we can use it in do notation:

do
  x <- Cons 5 Nil
  Cons 42 Nil -- Note that this is the same as `return 42`

Internally, Haskell will rewrite this to:

Cons 5 Nil >>= (\x -> Cons 42 Nil)

Can you use the definition of (>>=) to calculate the result of this expression with pen and paper?

Solution
  Cons 5 Nil >>= (\x -> Cons 42 Nil)
= { using the definition of Cons x xs >>= f }
  append ((\x -> Cons 42 Nil) 5) (Nil >>= (\x -> Cons 42 Nil))
= { applying the (\x -> Cons 42 Nil) lambda to the argument 5 }
  append (Cons 42 Nil) (Nil >>= (\x -> Cons 42 Nil))
= { using the definition of append (Cons x xs) ys } 
  Cons 42 (append Nil (Nil >>= (\x -> Cons 42 Nil)))
= { using the definition of append Nil ys }
  Cons 42 (Nil >>= (\x -> Cons 42 Nil))
= { using the definition of Nil >>= _ }
  Cons 42 Nil

* Monad actually also requires that the type is an instance of Applicative, but I have chosen to leave that out for this explanation.

5 Likes

Wow–that’s extremely clear and helpful, @jaror.

1 Like

You already got some nice answers, but I’ll add my two cents. let is a binder keyword, that will associate a name to a value in the rest of your term. <- is not a real keyword but only syntactic sugar.

a <- computeA arg
b <- computeB a arg2
c
return d

will be translated by a preprocessor to

computeA arg >>= \a ->
computeB a arg2 >>= \b ->
c >>= \_ ->
return d

Understanding the underlying syntax helps think about the do notation. This syntactic sugar really makes us humans think there is some state involved, or imperative style evaluation order, and this might seem confusing sometimes. I hope I did not make any mistakes explaining this.

4 Likes

Where

c >>= \_ ->

is the same as

c >>

2 Likes