Skip to content

Instantly share code, notes, and snippets.

@dgendill
Last active May 11, 2017 13:20
Show Gist options
  • Save dgendill/45bfcac3cf142daaa165323ae45069cd to your computer and use it in GitHub Desktop.
Save dgendill/45bfcac3cf142daaa165323ae45069cd to your computer and use it in GitHub Desktop.
Example using the Writer monad's listen, past, and listens functions in PureScript. Also exercise 11.6 part 2
-- http://try.purescript.org/?gist=45bfcac3cf142daaa165323ae45069cd
module Main where
import Prelude
import Control.Monad.Writer(Writer(..), tell, listen, listens, pass, runWriter)
import Data.Array(tail, head, drop, length)
import Data.String(joinWith)
import Data.Tuple(fst, snd, Tuple(..))
import Math (remainder, (%))
import Control.Monad.Eff.Console (log, logShow)
import Data.Foldable (fold)
import TryPureScript
-- Find the next number in a collatz sequence
collatz :: Number -> Number
collatz n = case (n % 2.0 == 0.0) of
true -> n / 2.0
false -> 3.0 * n + 1.0
-- Calculate the next collatz number in the Writer monad
collatzW :: Number -> Writer (Array Number) Number
collatzW n = do
tell [n]
pure $ collatz n
-- Calculate a collatz sequence
collatzSeq :: Number -> (Writer (Array Number)) Int
collatzSeq n = lengthOfSeq $ seq n
where
seq n = do
v <- collatzW n
case (v) of
1.0 -> do
pure 1
_ -> seq v
lengthOfSeq :: Writer (Array Number) Int -> Writer (Array Number) Int
lengthOfSeq c = pass $ (do
-- a = Number
-- w = Array Number
Tuple a w <- listen c
pure $ Tuple (length w) (const w)
)
-- Alternative to lengthOfSeq tha uses `listens`
lengthOfSeq2 :: Writer (Array Number) Int -> Writer (Array Number) Int
lengthOfSeq2 c = do
a <- snd <$> listens id c
pure $ length a
-- `listens` has type
-- `(Monoid w, Monad m) => forall w m a b. MonadWriter w m => (w -> b) -> m a -> m (Tuple a b)`.
-- If we use the `id` function the type would be...
--
-- MonadWriter w m => (w -> b) -> m a -> m (Tuple a b)
-- And in this context the specific type is...
--
-- w = Array Number
-- m = WriterT (Array Number) Identity (alias: Writer (Array Number) )
-- b = Array Number
-- a = Number
--
-- (Array Number -> Array Number) ->
-- Writer (Array Number) Number ->
-- Writer (Array Number) (Tuple Number (Array Number))
--
-- So listens essentially unwraps a Writer computation, so it can be read or
-- transformed
showSequence :: Number -> String
showSequence n = "Seed: " <> (show n) <>
"<br>Length: " <> (show $ fst seq) <> "<br>" <>
"Sequence: " <> (show $ snd seq) <> "<br>-------"
where
seq = runWriter (collatzSeq n)
main = do
render $ fold [
p (text $ append "<br><br>" $ joinWith "<br><br>" $ map showSequence numbers)
]
where numbers = [
10.0, 11.0, 12.0, 13.0, 14.0, 15.0
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment