Skip to content

Instantly share code, notes, and snippets.

@jsoo1
Last active September 17, 2019 04:07
Show Gist options
  • Save jsoo1/99d4340c48f47c14aa7f00e9442ee45e to your computer and use it in GitHub Desktop.
Save jsoo1/99d4340c48f47c14aa7f00e9442ee45e to your computer and use it in GitHub Desktop.
Orange Combinator Notes 2019-09-16
{-# LANGUAGE DeriveFunctor #-}
module Main where
import Prelude hiding (map)
main :: IO ()
main = undefined
-- f is the name of a definition
f x = x -- < body
-- ^
-- parameter
-- Recursive, but
-- Not tail recursive
-- This is to address why the stack is not necessarily a problem
fact n =
if n < 2
then 1
else n * fact (n - 1)
-- Tail recursion approx. while loop
fact' n = go 1 n
where go a 0 = a
go a n = go (a * n) (n - 1)
-- Tail recursion (can be called TCO elsewhere) not always beneficial.
-- Let's find out why
-- `a` is a type variable
data Tree a = Leaf a -- `Leaf` and `Node` are called Constructors
| Node (Tree a) (Tree a)
deriving (Show, Functor)
addOne :: Tree Int -> Tree Int
addOne (Leaf v) = Leaf (v + 1)
addOne (Node l r) = Node (addOne l) (addOne r)
-- addOne' works for all things with Num (polynomials, maybe)
addOne' :: (Num a) => Tree a -> Tree a
addOne' (Leaf v) = Leaf (v + 1) -- Note we stay in Leaf here
addOne' (Node l r) = Node (addOne' l) (addOne' r) -- Note we stay in Node here
-- Now let us abstract over the recursion
-- we wrote a higher order function here
-- (a -> b) denotes a function f we take as an argument
addOne'' :: (a -> b) -> Tree a -> Tree b
addOne'' f (Leaf x) = Leaf (f x)
addOne'' f (Node l r) = Node (addOne'' f l) (addOne'' f r)
exTree :: Tree Int
exTree =
Node
(Leaf 1)
(Node (Leaf 2)
(Node (Leaf 3)
(Leaf 4)))
-- Now our name is bad, let's rename it
mapTree :: (a -> b) -> Tree a -> Tree b
mapTree = addOne''
-- What is Functor ?
-- Well, it must have a type variable
-- data Tree a <-- Remember this a? That means it can be a functor
-- a type (f :: Type -> Type) is is a functor if it:
-- * has fmap :: (a -> b) -> f a -> f b
-- * fmap f . fmap g = fmap (f . g)
-- * fmap id = id
data Things = Number Int
| Str String
| Logic Bool
things :: [Things]
things = [ Number 4, Str "fifty", Logic False ]
f2cBad :: Float -> Float
-- This can be bad because Float can behave however it wants
f2cBad = undefined
newtype Fahr = F Float -- F and C are still called constructors
newtype Cel = C Float
-- ^^^^ newtype incurs no runtime cost (unboxed)
-- Fahr and Cel cannot be used in place of each other
f2c :: Fahr -> Cel
f2c (F d) = C (d * 5.0 - 32.0)
-- Laziness means you can work with infinite lists
fiveNums = take 5 [1..]
map :: (a -> b) -> [a] -> [b]
map f [] = []
map f (x:xs) = f x : map f xs
-- ^ This single colon is called cons (which comes from LISP)
exList = map (* 2) [1,2]
unNaturals = map (+1 ) [1..]
-- It is cases like exList and unNaturals that
-- make direct expression (as opposed to tail recursion) the better option
naturals = iterate (+ 1) 0
-- Loop fusion
fusionEx = map (+ 5) (map (* 2) [1,2,3])
-- Because map is (again) a Functor
-- Then map f . map g = map (f . g)
-- That means the compiler can simplify this to
-- map (\x -> 2 * x + 5) [1, 2, 3]
-- What have we covered today?
-- * Functions - They can be composed
-- * Higher order functions - They can often be derived and (can, among other things) abstract recursion
-- * Called algebraic data types - Sum Types (Remember Tree?), Product types (Node, Tuples)
-- * typeclasses - Type Num, Functor, et cetera. They abstract behavior across types and can often be derived
-- * Abstraction
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment