Skip to content

Instantly share code, notes, and snippets.

@mbbx6spp
Last active January 5, 2017 04:00
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/c4a0e26eacb4c1e19c04bd2dc4399310 to your computer and use it in GitHub Desktop.
Save mbbx6spp/c4a0e26eacb4c1e19c04bd2dc4399310 to your computer and use it in GitHub Desktop.
Initial motivating example for using recursion schemes
-- module of natural number properties ... and stuff
module Naturally where
import Prelude hiding (even, odd)
-- recursive data structure
data Nat = Zero -- base case is "zero"
| Succ Nat -- successor of another Nat is the "recursive" case data constructor
deriving (Eq)
instance Show Nat where
show Zero = "0"
show (Succ n) = show $ sum (Succ n)
where
sum :: Nat -> Int
sum Zero acc = acc
sum (Succ n) acc = sum n (acc + 1)
-- TODO Num Nat instance
even :: Nat -> Bool
even Zero = True
even Succ n = odd n
odd :: Nat -> Bool
odd Zero = False
odd (Succ n) = even n
-- now let's define the fusion of the functions in one equivalent one
evenOdd :: Nat -> (Bool, Bool)
evenOdd Zero = (True, False)
evenOdd (Succ n) = swap (evenOdd n)
-- We have a [tennis] tournament that we want to model
module Tournament where
type Name = String
data Player = MkPlayer Name deriving (Show)
data Draw =
-- on the "leaves" or initial scheduled games we have "matches"
MkMatch { leftPlayer :: Player, rightPlayer :: Player }
-- on the non-leaves we have unknown future matches that are defined in terms of winners of prior (future-)matches.
| MkFutureMatch { leftDraw :: Draw, rightDraw :: Draw }
deriving (Show)
-- Given a draw we might want to know how many players there are in a tournament
players :: Draw -> Int
players (MkMatch _ _) = 2
players (MkFutureMatch l r) = players l + players r -- NOTE: recursive calls on left and right parts; not tail recursive
-- alternatively maybe we want to know how many rounds are in the tournament based on the given draw tree
rounds :: Draw -> Int
rounds (MkMatch _ _) = 1
rounds (MkFutureMatch l r) = rounds l + rounds r -- NOTE: recursive calls on left and right parts; not tail recusive
-- we might want to construct a draw for the tournament based on a list of players
fromList :: [Player] -> Maybe Draw
fromList [p] = Nothing
fromList (p : [q]) = Just $ MkMatch p q
fromList ps = undefined -- TODO: will be recursive calls; not tail recursive
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment