John Chee
@chee1bot on Twitter | @cheecheeo on Github
module JustHaskellOrNothing where
import Control.Applicative
import Data.Maybe
import Data.MonoidIn Javascript:
> 20 * 2 + 2 + null
42In SQL:
mysql> select 20 * 2 + 2 + null;
+-------------------+
| 20 * 2 + 2 + null |
+-------------------+
| NULL |
+-------------------+
1 row in set (0.01 sec)In Haskell:
λ: fmap (20 * 2 + 2 +) Nothing
NothingRather than:
λ: head []
*** Exception: Prelude.head: empty listλ: safeHead []
Nothing
λ: safeHead [1,2,3,4]
Just 1
λ: safeHead [42]
Just 42Or:
λ: 12 `div` 0
*** Exception: divide by zeroλ: 12 `safeDiv` 0
Nothing
λ: 42 `safeDiv` 2
Just 21data Maybe a = Nothing | Just aMaybe Foo you know you have values like:
FooIntegersMaybe IntegersBoolsMaybe Boolsλ: [0..5]
[0,1,2,3,4,5]λ: [Nothing] ++ map Just [0..5]
[Nothing,Just 0,Just 1,Just 2,Just 3,Just 4,Just 5]λ: [True, False]
[True,False]λ: [Nothing] ++ map Just [True, False]
[Nothing,Just True,Just False]MaybessafeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x : _) = Just xsafeDiv :: Integer -> Integer -> Maybe Integer
safeDiv n d =
if d == 0
then Nothing
else Just (n `div` d)In this case a phone number that isn't valid maps to Nothing.
data PhoneNumber = PhoneNumber Integer Integer Integer
deriving (Show)
parsePhoneNumber :: Integer -> Maybe PhoneNumber
parsePhoneNumber n =
if n >= 2002000000 && n < 10000000000 -- the correct number of digits
then let (areaCode, m) = n `divMod` 10000000
(centralOfficeCode, subscriberNumber) = m `divMod` 10000
in if areaCode >= 200 && centralOfficeCode >= 200 && centralOfficeCode `mod` 100 /= 11
then Just (PhoneNumber areaCode centralOfficeCode subscriberNumber)
else Nothing
else NothingExamples:
λ: parsePhoneNumber 1234567890
Nothing
λ: parsePhoneNumber 4155551234
Just (PhoneNumber 415 555 1234)
λ: parsePhoneNumber 4159112277
Nothing
λ: parsePhoneNumber 4159128347
Just (PhoneNumber 415 912 8347)If we have a Maybe and we're ready to handle both the Nothing case and the Just case we can:
pattern match:
showMaybeInteger :: Maybe Integer -> String
showMaybeInteger m =
case m of
Nothing -> "There's nothing here."
Just x -> "I have something: " <> show xλ: showMaybeInteger Nothing
"There's nothing here."
λ: showMaybeInteger (Just 42)
"I have something: 42"or eliminate:
maybe :: b -> (a -> b) -> Maybe a -> bshowMaybeInteger' :: Maybe Integer -> String
showMaybeInteger' m =
maybe
"There's nothing here." -- Nothing
(\x -> "I have something: " <> show x) -- Just x
mmaybe function can you? (audience involvement)maybemaybe :: b -> (a -> b) -> Maybe a -> bJust to Some or Nothing to None
MaybesMaybe values all over the place
fromMaybe :: a -> Maybe a -> aIf we want to do the Javascript thing and make Nothing be 0
λ: let (x, y) = (Nothing, Just 30000)
λ: let jsNumbers = fromMaybe 0
λ: 20 * 2 + 2 + jsNumbers x
42
λ: jsNumbers y + 1337
31337MaybeslistToMaybe :: [a] -> Maybe a
maybeToList :: Maybe a -> [a]safeHead' = listToMaybeλ: maybeToList Nothing
[]
λ: maybeToList (Just "hello")
["hello"]
λ: listToMaybe [1..10]
Just 1
λ: listToMaybe []
NothingMaybescatMaybes :: [Maybe a] -> [a]
mapMaybe :: (a -> Maybe b) -> [a] -> [b]λ: catMaybes [Nothing,Just 1,Just 2,Nothing,Just 4,Just 5]
[1,2,4,5]
λ: length . mapMaybe parsePhoneNumber $ [4150000000..4159999999]
7920000maybe you can write a large number of useful programsfmappable things AKA Functor instancesmap (or equivalently fmap) across listsfmap across Maybesfmap :: (a -> b) -> Maybe a -> Maybe bWe can write our function without being concerned about Maybe:
call :: PhoneNumber -> String
call (PhoneNumber areaCode centralOfficeCode subscriberNumber) =
"I called (" <> show areaCode <> ") "
<> show centralOfficeCode <> " " <> show subscriberNumber
<> " and had a great conversation!"and we'll perform computations if we have a Just and otherwise get Nothing
λ: fmap call (parsePhoneNumber 4155551234)
Just "I called (415) 555 1234 and had a great conversation!"
λ: fmap call (parsePhoneNumber 1234567890)
Nothingtext toodata Phone = Android | IPhone | Hipstertext :: Phone -> String
text p =
case p of
Android -> "I love swiping when I text."
IPhone -> "I love to type character by character."
Hipster -> "Texting is so 2014."We can use Maybe Phone to represent those rare times when you forget your cell phone.
λ: fmap text (Just Android)
Just "I love swiping when I text."
λ: fmap text (Just Hipster)
Just "Texting is so 2014."
λ: fmap text Nothing
NothingApplicative instancePhone and PhoneNumbercallWithPhone :: Phone -> PhoneNumber -> String
callWithPhone phone (PhoneNumber areaCode centralOfficeCode subscriberNumber) =
let prettyPhoneNumber = "(" <> show areaCode <> ") " <> show centralOfficeCode <> " " <> show subscriberNumber
in case phone of
Android -> "Google knows I just called " <> prettyPhoneNumber <> "."
IPhone -> "I called " <> prettyPhoneNumber <> " on the best phone!"
Hipster -> "I called " <> prettyPhoneNumber <> " and asked for their Snapchat ID."Maybe is also an Applicative instance
Maybes using JustMaybe computations using (<*>)Maybe Phone and a Maybe PhoneNumber?
λ: (pure callWithPhone) <*> (pure Android) <*> (parsePhoneNumber 4155551234)
Just "Google knows I just called (415) 555 1234."
λ: (pure callWithPhone) <*> (pure IPhone) <*> (parsePhoneNumber 1234567890)
Nothing
λ: (pure callWithPhone) <*> (pure Hipster) <*> (parsePhoneNumber 5035551234)
Just "I called (503) 555 1234 and asked for their Snapchat ID."
λ: (pure callWithPhone) <*> Nothing <*> (parsePhoneNumber 1234567890)
NothingWhat about? (audience participation)
λ: Nothing <*> Nothing <*> Nothing