3

Reading this blog post – https://www.haskellforall.com/2021/05/the-trick-to-avoid-deeply-nested-error.html – I realised I don't understand why the 'trick' actually works in this situation:

{-# LANGUAGE NamedFieldPuns #-}

import Text.Read (readMaybe)

data Person = Person { age :: Int, alive :: Bool } deriving (Show)

example :: String -> String -> Either String Person
example ageString aliveString = do
    age <- case readMaybe ageString of
        Nothing  -> Left "Invalid age string"
        Just age -> pure age

    if age < 0
        then Left "Negative age"
        else pure ()

    alive <- case readMaybe aliveString of
        Nothing    -> Left "Invalid alive string"
        Just alive -> pure alive

    pure Person{ age, alive }

Specifically I'm struggling to understand why this bit

    if age < 0
        then Left "Negative age"
        else pure ()

type checks.

Left "Negative age" has a type of Either String b

while

pure () is of type Either a ()

Why does this work the way it does?


EDIT: I simplified and re-wrote the code into bind operations instead of do block, and then saw Will's edit to his already excellent answer:

{-# LANGUAGE NamedFieldPuns #-}

import           Text.Read (readMaybe)

newtype Person = Person { age :: Int} deriving (Show)

example :: String -> Either String Person
example ageString =
    getAge ageString
    >>= (\age -> checkAge age
        >>= (\()-> createPerson age))

getAge :: Read b => String -> Either [Char] b
getAge ageString = case readMaybe ageString of
       Nothing  -> Left "Invalid age string"
       Just age -> pure age

checkAge :: (Ord a, Num a) => a -> Either [Char] ()
checkAge a = if a < 0
       then Left "Negative age"
       else pure ()

createPerson :: Applicative f => Int -> f Person
createPerson a = pure Person { age = a }

I think this makes the 'trick' of passing the () through binds much more visible - the values are taken from an outer scope, while Left indeed short-circuits the processing.

Will Ness
  • 62,652
  • 8
  • 86
  • 167
Iarek
  • 1,305
  • 15
  • 39
  • Pretty sure there is a formal argument that `Either String Person` is a subtype of both `Either a ()` and `Either String b`, but I failed to make it in my (now deleted) answer. – chepner May 13 '21 at 16:12
  • I.e., `Left "Invalid alive string"` can be treated as a value of type `Either String b` no matter what type you choose for `b`, because no value of type `b` is used in the value. – chepner May 13 '21 at 16:14
  • 1
    @chepner it doesn't have to be `Either String Person`, `Either String anything` is enough. It's in the _middle_ of the do block, and there's no value "extraction". :) so it serves as a guard. – Will Ness May 13 '21 at 16:14
  • @WillNess But the definition of `>>=` for `Either a` means it will be used as the return value. `pure ()` only type checks because it's not the last expression in the `do` block. – chepner May 13 '21 at 16:48
  • @chepner "_it_ will be used as the return value" you mean `String`? it's not "value", it's part of the "shell": in `Either String b`, `Either String` is the vessel (so, in `Either` "language", `String` is the "error signal"), `b` is the contents / value. of course the reified computation `Either String b` is a value itself, but we treat it as computation denotation, mentally. – Will Ness May 13 '21 at 17:21
  • No, the value `Left "foo"`. On its *own*, it's a value of type `forall a. Either String a`, but it needs to be a value of type `Either String Person` to be used as the return value of `example`. I thought the question was how the value can have both types. – chepner May 13 '21 at 17:23
  • @chepner but it's _not_ the _last_ value, so it only needs to be `Either String _`. – Will Ness May 13 '21 at 17:25
  • It *effectively* is the last value, as the rest of the block won't be evaluated, since `Left x >>= _ == Left x`. – chepner May 13 '21 at 17:27
  • 3
    @chepner ah, yes, but *no*: it's ***not*** `l@(Left x) >>= _ = l` ! the `Left x` on the right creates a _new_ value, of _another_ type, `Either String Person` indeed! (using the same `x`, hence it _had_ to be `Either String _` (writing informally)). it's not the same value having two types, it's two values. – Will Ness May 13 '21 at 17:33

1 Answers1

7

It typechecks because Either String b and Either a () unify successfully, with String ~ a and b ~ ():

     Either String b
     Either a      ()
   ------------------
     Either String ()      a ~ String, b ~ ()

It appears in the do block of type Either String Person, so it's OK, since it's the same monad, Either, with the same "error signal" type, String.

It appears in the middle of the do block, and there's no value "extraction". So it serves as a guard.

It goes like this: if it was Right y, then the do block's translation is

      Right y >>= (\ _ -> .....)

and the computation continues inside ..... with the y value ignored. But if it was Left x, then

      Left x >>= _  =  Left x

according to the definition of >>= for Either. Crucially, the Left x on the right is not the same value as Left x on the left. The one on the left has type Either String (); the one on the right has type Either String Person indeed, as demanded by the return type of the do block overall.

The two Left x are two different values, each with its own specific type. The x :: String is the same, of course.

Will Ness
  • 62,652
  • 8
  • 86
  • 167
  • Ah I get it now! I think. So as it's in the middle of the do block, the type of the `if` block doesn't have to match the function return type, as it's piped into another function? – Iarek May 13 '21 at 16:48
  • yes. see comments under the question. :) – Will Ness May 13 '21 at 17:29
  • 2
    @larek, yes, but the two `if` branches still have to match. And here they do, because one can have anything on the left, and the other can have anything on the right. – luqui May 13 '21 at 22:22
  • Thank you for the excellent answer! Took me to rewrite it with binds (see edit) to properly internalise what's going on – Iarek May 13 '21 at 22:57
  • By which I mean: `do` blocks are hard on my brain – Iarek May 13 '21 at 22:57
  • @Iarek [do notation is our friend](https://stackoverflow.com/search?q=user%3A849891+%5Bdo-notation%5D+friend). it is there to help us. of course first we must work through the particular type's `>>=` code closely, to see exactly what is going on. but then it helps us _separate the concerns_ -- one realm is the machinations in the computation pipeline, the other is what we the programmer are doing. – Will Ness May 14 '21 at 10:43
  • @Iarek regarding your edit: see https://stackoverflow.com/tags/do-notation/info and https://stackoverflow.com/questions/44727803/does-the-main-function-in-haskell-always-start-with-main-do/44728131#44728131. we can always write `do { ... – Will Ness May 14 '21 at 10:54
  • 1
    @WillNess thank you! That's very helpful – Iarek May 14 '21 at 11:12