Skip to content

Instantly share code, notes, and snippets.

@mbbx6spp
Last active February 4, 2019 20:45
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 mbbx6spp/34934e4ad8fd7d950bfaca5457d9278a to your computer and use it in GitHub Desktop.
Save mbbx6spp/34934e4ad8fd7d950bfaca5457d9278a to your computer and use it in GitHub Desktop.
Exercises to show how to abstract over Functors in our data types via type constructor.
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
import Control.Monad (mapM_)
import Data.Function (($))
import Data.Functor (Functor (..))
import Data.List ((++))
import GHC.Num (Integer, (+))
import GHC.Show
import System.IO (print)
-- Functors
newtype Identity a = MkIdentity a deriving (Functor, Show)
data Optional a = Nada | Some a deriving (Functor, Show)
data Errorable e a = MkError e | MkVal a deriving (Functor, Show)
data Futurable a = Delayed (() -> a) | Ready a deriving (Functor)
data Many a = Empty | a :. Many a deriving (Functor, Show)
infixr 4 :.
instance Show a => Show (Futurable a) where
show (Delayed _) = "Delayed"
show (Ready a) = "Ready " ++ show a
newtype OrderId (f :: * -> *) a = MkOrderId (f a) deriving (Functor, Show)
type AlwaysOrderId = OrderId Identity
type OptionalOrderId = OrderId Optional
type ErrorableOrderId = OrderId (Errorable OrderIdError)
type FuturableOrderId = OrderId Futurable
type ManyOrderId = OrderId Many
data OrderIdError = NoOrderIdFound | AmbiguousOrderId | UnknownOrderIdError deriving (Show)
increment :: Integer -> Integer
increment = (+1)
data0 = MkOrderId $ MkIdentity 5 :: AlwaysOrderId Integer
data1 = MkOrderId $ Some 5 :: OrderId Optional Integer
data2 = MkOrderId $ MkVal 5 :: OrderId (Errorable OrderIdError) Integer
data3 = MkOrderId $ Delayed (\() -> 5) :: OrderId Futurable Integer
data4 = MkOrderId $ Ready 5 :: OrderId Futurable Integer
data5 = MkOrderId $ 5 :. Empty :: OrderId Many Integer
data6 = MkOrderId $ Empty :: OrderId Many Integer
data7 = MkOrderId $ Nada :: OrderId Optional Integer
genericSolution :: forall (f :: * -> *). Functor f => f Integer -> f Integer
genericSolution = fmap increment
app0 = genericSolution data0
app1 = genericSolution data1
app2 = genericSolution data2
app3 = genericSolution data3
app4 = genericSolution data4
app5 = genericSolution data5
app6 = genericSolution data6
app7 = genericSolution data7
main = do
print app0
print app1
print app2
print app3
print app4
print app5
print app6
print app7
-- λ> :main
-- MkOrderId (MkIdentity 6)
-- MkOrderId (Some 6)
-- MkOrderId (MkVal 6)
-- MkOrderId Delayed
-- MkOrderId Ready 6
-- MkOrderId (6 :. Empty)
-- MkOrderId Empty
-- MkOrderId Nada
-- it :: ()
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment