How is `Just organ` being destructured

In this code sample:

processAndReport :: Maybe Organ -> String
processAndReport (Just organ) = report (process organ)
processAndReport Nothing = "error, id not found"

I’m not understanding the processAndReport (Just organ) = report (process organ) line.

I think I see what is happening but I don’t understand how.

If a Just organ is passed to procesAndReport then organ is passed to process which expects an Organ - all good there.

process :: Organ -> (Location, Container)
process organ = placeInLocation (organToContainer organ)

It appears that somehow the organ is being taken out of Just organ so it can be passed to process. However, I’m left asking myself ‘what mechanism’ or ‘Haskell thingy’ is makeing that happen.

I don’t think it is needed, but just in case, here is the entire code sample:

import qualified Data.Map as Map
import Data.List ( intercalate )

data Organ = Heart | Brain | Kidney | Spleen deriving (Show, Eq)

organs :: [Organ]
organs = [Heart,Heart,Brain,Spleen,Spleen,Kidney]

ids :: [Int]
ids = [2,7,13,14,21,24]

organPairs :: [(Int,Organ)]
organPairs = zip ids organs

-- use `Map.lookup 7 organCatalog` to get an organ
organCatalog :: Map.Map Int Organ
organCatalog = Map.fromList organPairs
  
possibleDrawers :: [Int]
possibleDrawers = [1 .. 50]

getDrawerContents :: [Int] -> Map.Map Int Organ -> [Maybe Organ]
getDrawerContents ids catalog = map getContents ids
	where getContents = \id -> Map.lookup id catalog

availableOrgans :: [Maybe Organ]
availableOrgans = getDrawerContents possibleDrawers organCatalog

countOrgan :: Organ -> [Maybe Organ] -> Int
countOrgan organ available = length (filter (\x -> x == Just organ) available)

isSomething :: Maybe Organ -> Bool
isSomething Nothing = False
isSomething (Just _) = True

justTheOrgans :: [Maybe Organ]
justTheOrgans = filter isSomething availableOrgans

showOrgan :: Maybe Organ -> String
showOrgan (Just organ) = show organ
showOrgan Nothing = ""

organList :: [String]
organList = map showOrgan justTheOrgans

cleanList :: String
cleanList = intercalate ", " organList

data Container = Vat Organ | Cooler Organ | Bag Organ

instance Show Container where
	show (Vat organ) = show organ ++ " in a vat"
	show (Cooler organ) = show organ ++ " in a cooler"
	show (Bag organ) = show organ ++ " in a bag"

data Location = Lab | Kitchen | Bathroom deriving Show

organToContainer :: Organ -> Container
organToContainer Brain = Vat Brain
organToContainer Heart = Cooler Heart
organToContainer organ = Bag organ

placeInLocation :: Container -> (Location,Container)
placeInLocation (Vat a) = (Lab, Vat a)
placeInLocation (Cooler a) = (Lab, Cooler a)
placeInLocation (Bag a) = (Kitchen, Bag a)

process :: Organ -> (Location, Container)
process organ = placeInLocation (organToContainer organ)

report ::(Location,Container) -> String
report (location,container) = show container ++
								  " in the " ++
								  show location

processAndReport :: Maybe Organ -> String
processAndReport (Just organ) = report (process organ)
processAndReport Nothing = "error, id not found"

I’m not sure what precisely you mean here because right above it you say:

The ‘Haskell thingy’ that takes the organ out of Just organ is pattern matching in the definition of processAndReport. By writing that (Just organ) pattern on the left hand side of the equality sign you define that the organ is to be taken out of the Just organ wrapper. Then you can use the organ variable on the right hand side to mean the thing you get out of that wrapper.

2 Likes

Yep, pattern matching is the answer. This is speculation, but possibly what’s confusing you is that we’re getting an x out of a Just x, and you’re aware that e.g. getting an a out of Maybe a is in general impossible. If so, then the answer is that there’s a confusion of values and types. Just x is a value, and in fact is isomorphic to x (the two values contain the same information). So there’s no problem writing: foo (Just x) = x. Maybe a is a type, and is not isomorphic to the type a. If any of that is relevant to the question, let me know, and I can add more clarification (but if not, disregard :slight_smile: )

1 Like

What is “isomorphic”?

Can be transformed into each other, are equivalent.

Formally, two types A and B are isomorphic if there are functions f :: A -> B and g :: B -> A such that f . g === g.f === id . But intuitively it just means that the two things are the same. For example, the types Bool -> Int and (Int, Int) are isomorphic. The types Either () a and Maybe a are isomorphic.

2 Likes
  • Not sure that is what was confusing me or not but I certainty had not thought about it.
  • I’m assuming by types you mean type constructors and by values you mean data constructors?
  • So is it true that you can never pattern match on a type but can always do so on a value.?

Now that you point out that it is pattern matching I’m wondering why I didn’t see that already since I have used it many times now. I think it is just something about the context that threw me off.

Actually no, I did mean type and value. For example, Maybe Int is a type, and Just 4 is a value of type Maybe Int.

If you have a function of type e.g. Maybe Int -> Int, you can pattern match to build a function out of that type, such as:

example (Just i) = i
example Nothing = 0

So I guess it’s a linguistic question on whether pattern matching happens on types or values: the thing in the pattern is always a value, but it’s determined by the type.

1 Like

The original question is answered so I could file this as something to keep aware of while continuing to learn but one more try:

So

  • Just 5 you call a value
  • but Just a as part of a type signature is a type
    ??
  • Yep, Just 5 is a “value.”
  • Just a cannot be part of a type signature. Rather Maybe a can be part of a type signature, and then Maybe a is a “type.”
  • You can also have Maybe on its own (like instance Functor Maybe where ..., and then Maybe is a “type constructor,” because it will construct a type for you if you give it a type. Give it an Int, and Maybe Int is now a type.
  • You can also have Just on its own (like
fn :: Functor f => f a -> f (Maybe a)
fn = fmap Just

) and then Just is a “value constructor,” or commonly just a “constructor.” A constructor is pretty much just a function. Just is a constructor of type a -> Maybe a. Nothing happens to be called a “nullary constructor” or a “constructor of zero arguments” and so is a constructor of type Maybe a (forall a).

2 Likes

Yep, as above. Just 5 is a value. If x is any value, Just x is also a value. For any type a, Maybe a is also a type. You’ll never see Just in a type or Maybe in a value.

1 Like

Don’t fully understand this yet but got a lot out of the discussion. Thank you all!

No problem! I found the Maybe type (and its relation to Just) extremely confusing when I was learning Haskell, and once I finally felt comfortable with it, a lot of concepts like functors and monads suddenly became a lot clearer (because understanding Maybe forced me to understand the type system in general). So do feel free to ask follow up questions if stuff remains unclear

3 Likes

It’s worth spending enough time with both Maybe and pattern matching such that you feel very comfortable and confident with them. You will use them a lot in real-world haskell for industrial use.

1 Like