Skip to content

Instantly share code, notes, and snippets.

@jki127
Created November 14, 2019 21:40
Show Gist options
  • Save jki127/271692a4ae3b677b8f4c927ca53178ae to your computer and use it in GitHub Desktop.
Save jki127/271692a4ae3b677b8f4c927ca53178ae to your computer and use it in GitHub Desktop.

Monads - Programming Languages - Nov 7th, 2019

This is a continuation of the previous lecture (Lecture 16).

During last lecture we made stateful structures for the Fibonacci function, but we need something more general so that we can use state for other problems.

That's where Monads come in.

Monad Typeclass

Definition

Here's the definition of the Monad Typeclass:

class Applicative m => Monad m where
	(>>=) :: m a -> (a -> m b) -> m b  -- bind
	pure :: a -> m a

Note: the real name of the second function is not pure, it is actually return. Most Haskell users agree that naming it return was a huge mistake by the designers of Haskell.

Recreating FibStateful

module FibMonad where

data FibState = FibState {
	previousNumber :: Integer,
	previousPreviousNumber :: Integer,
	currentNumber :: Integer
}

-- FibMonad is the same as FibStateful
data FibMonad a = FibMonad {
	runFib :: FibState -> (FibState, a)
}

instance Monad FibMonad where
	-- (>>=) :: m a -> (a -> m b) -> m b  -- bind
	(FibMonad f) >>= g = FibMonad (\oldstate ->
		let (newstate, value) = f oldstate
			FibMonad rg = (g value)
		in rg newstate)
	-- pure :: a -> m a
	pure x = FibMonad (\s -> (s, x))

getFibState :: FibMonad FibState
getFibState = FibMoad (\s -> (s, s))

setFibState :: FibState -> FibMonad ()
setFibState newstate = FibState (\s -> (newstate, ()))

getPreviousNumber :: FibMonad Integer
getPreviousNumber =
	getFibState >>= \s -> pure (previousNumber s)

setPreviousNumber :: Integer -> FibMonad ()
setPreviousNumber i = 
	getFibState >>= \s -> setFibState newstate
	where newstate = FibState {
		previousNumber = i,
		previousPreviousNumber = previousPreviousNumber s,
		currentNumber = currentNumber s
	}

-- Add other getters and setters here
doFibMonad :: FibState -> FibMonad a -> a
doFibMonad initialState gm = 
	let (finalstate, result) = (runFib gm) initialState
	in result

Alternative bind operator

-- bind
(>>=) :: Monad m => m a -> (a -> m b) -> m b
-- alternative bind
(>>) :: Monad m => m a -> m b -> m b

The second parameter of << does not need an input parameter. This is perfect for binding to our getter functions.

Syntatic Sugar

<- is similar to an assignment operator. We can use it after a do

fibAlgorithm n = 
	repeatTimes n (
		do pn <- getPreviousNumber
		setPreviousPreviousNumber pn
		cn <- getCurrentNumber
		setPreviousNumber cn

		newpn <- getPreviousNumber
		newppn <- getPreviousPreviousNumber
		setCurrentNumber (newpn + newppn)

		getCurrentNumber
	)

Hello World

IO is a monad

-- hello.hs
main :: IO()
main = putStrLn "Hello World"

Then we can use compile the program using: ghc hello.hs

File IO

main :: IO ()
main = do "Enter a file name: "
	-- gets input from the stdin 
	filename <- getLine
	filecontent <- readFile "helloworld.hs"
	let firstchar = head filecontent
	print firstchar

Control Monad State

put is for our setters. get is for our getters.

evalState starts the function with initial state.

import Control.Monad.State
import Control.Monad (forM)

fib:: Int -> Int
fib = evalState (
		do forM [1..n] (\_ ->
			do (a,b) <- get
				put (b, a+b))
			(a, b) <- get
			pure b
		)
	) (0, 1)

ST Monads

  • newSTRef
  • readSTRef

Big Picture

Understand the bind function and the pure function (actually named return)

#school/f19/proglang-f19

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment