Skip to content

Instantly share code, notes, and snippets.

@mjhoy
Last active January 9, 2019 14:31
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mjhoy/8a4590fea8f95dc3346d67ebc5693a15 to your computer and use it in GitHub Desktop.
Save mjhoy/8a4590fea8f95dc3346d67ebc5693a15 to your computer and use it in GitHub Desktop.
{-# LANGUAGE NoImplicitPrelude #-}
module Composition where
import Prelude (undefined, String, Show)
data Airport = Airport
{ iata :: String
, timezone :: String
} deriving (Show)
data Flight = Flight
{ destinationIata :: String
} deriving (Show)
findAirportByIata :: String -> Airport
findAirportByIata "ORD" = chicago
chicago = Airport { iata = "ORD", timezone = "CST" }
testFlight = Flight { destinationIata = "ORD" }
-- 1. Function composition. f . g = \x -> f (g a)
(.) :: (b -> c) -> (a -> b) -> (a -> c)
f . g = \x -> f (g x)
-- The functions are equivalent:
flightAirport :: Flight -> Airport
flightAirport flight = findAirportByIata (destinationIata flight)
flightAirport' :: Flight -> Airport
flightAirport' = findAirportByIata . destinationIata
-- ghci> flightAirport' testFlight
-- Airport {iata = "ORD", timezone = "CST"}
-- Composing three functions:
flightDestTimezone :: Flight -> String
flightDestTimezone = timezone . findAirportByIata . destinationIata
-- ghci> flightDestTimezone testFlight
-- "CST"
{-# LANGUAGE NoImplicitPrelude #-}
module Composition2_Functor where
import Prelude (String, Show)
import Composition ((.))
data Maybe a = Just a | Nothing
deriving (Show)
data Airport = Airport
{ iata :: String
, timezone :: String
} deriving (Show)
data Flight = Flight
{ destinationIata :: String
} deriving (Show)
-- 2. Composition with functors.
-- Definition of `map` for the Maybe type:
mapMaybe :: (a -> b) -> (Maybe a -> Maybe b)
mapMaybe f (Just x) = Just (f x)
mapMaybe f Nothing = Nothing
findAirportByIata :: String -> Maybe Airport
findAirportByIata "ORD" = Just chicago
findAirportByIata _ = Nothing
chicago = Airport { iata = "ORD", timezone = "CST" }
testFlight = Flight { destinationIata = "ORD" }
testFlightUnknownIata = Flight { destinationIata = "LHR" }
flightDestAirport :: Flight -> Maybe Airport
flightDestAirport = findAirportByIata . destinationIata
-- timezone "lifted" into the Maybe context
flightDestTimezone :: Flight -> Maybe String
flightDestTimezone = (mapMaybe timezone) . flightDestAirport
-- ghci> flightDestTimezone testFlight
-- Just "CST"
-- ghci> flightDestTimezone testFlightUnknownIata
-- Nothing
-- a Functor is a type that can be "mapped" over. mapMaybe is the map
-- instance for the Maybe functor.
class Functor f where
map :: (a -> b) -> (f a -> f b)
instance Functor Maybe where
map = mapMaybe
{-# LANGUAGE NoImplicitPrelude #-}
module Composition3_Monad where
import Prelude (String, Show, undefined)
import Time (parseTime, Time)
import Composition ((.))
import Composition2_Functor (Maybe(..), Functor, map)
data Airport = Airport
{ iata :: String
, timezone :: String
} deriving (Show)
data Flight = Flight
{ destinationIata :: String
, arrivalTime :: Maybe String -- <- Added field.
} deriving (Show)
findAirportByIata :: String -> Maybe Airport
findAirportByIata "ORD" = Just chicago
findAirportByIata _ = Nothing
chicago = Airport { iata = "ORD", timezone = "CST" }
testFlight = Flight { destinationIata = "ORD", arrivalTime = Just "2018-10-10T10:00:00" }
testFlight2 = Flight { destinationIata = "ORD", arrivalTime = Just "bad data" }
testFlight3 = Flight { destinationIata = "ORD", arrivalTime = Nothing }
-- 3. Composition with Monads.
--
-- We have two functions to compose:
--
-- arrivalTime :: (Flight -> Maybe String)
-- and
-- parseTime :: (String -> Maybe Time)
--
-- Function composition: (b -> c) -> (a -> b) -> (a -> c)
-- Monadic composition: (b -> m c) -> (a -> m b) -> (a -> m c)
--
-- Monadic composition requires a function called "bind". Scala uses
-- "flatmap".
--
-- Definiting the Maybe monad:
maybeCompose :: (b -> Maybe c) -> (a -> Maybe b) -> (a -> Maybe c)
maybeCompose f g = \a -> bindMaybe (g a) f
bindMaybe :: Maybe b -> (b -> Maybe c) -> Maybe c
bindMaybe (Just x) f = f x
bindMaybe Nothing f = Nothing
flightArrivalTime :: Flight -> Maybe Time
flightArrivalTime = maybeCompose parseTime arrivalTime
-- ghci> flightArrivalTime testFlight
-- Just 2018-10-10 10:00:00 UTC
--
-- ghci> flightArrivalTime testFlight2
-- Nothing
--
-- ghci> flightArrivalTime testFlight3
-- Nothing
-- A monad is some type m with an associated bind function, and a unit
-- (identity) function.
class Monad m where
bind :: m b -> (b -> m c) -> m c
unit :: a -> m a
instance Monad Maybe where
bind = bindMaybe
unit x = Just x
module Time where
-- Helper module to define `parseTime` and `parseTimeWithZone`
import Data.Time (UTCTime)
import Data.Time.Format as F (parseTime, defaultTimeLocale)
import qualified Composition2_Functor as C (Maybe(..))
data Time = Time UTCTime
instance Show Time where
show (Time t) = show t
parseTime :: String -> C.Maybe Time
parseTime ts = case F.parseTime F.defaultTimeLocale "%Y-%m-%dT%H:%M:%S" ts of
Just x -> C.Just (Time x)
Nothing -> C.Nothing
parseTimeWithZone :: String -> String -> C.Maybe Time
parseTimeWithZone ts zn = case F.parseTime F.defaultTimeLocale "%Y-%m-%dT%H:%M:%S %Z" (ts ++ " " ++ zn) of
Just x -> C.Just (Time x)
Nothing -> C.Nothing
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment