Skip to content

Instantly share code, notes, and snippets.

@quephird
Created September 5, 2015 21:52
Show Gist options
  • Save quephird/111bbfa2229ac4a54e2f to your computer and use it in GitHub Desktop.
Save quephird/111bbfa2229ac4a54e2f to your computer and use it in GitHub Desktop.
Solution to exercise 5 in section 8.7 in PureScript by Example
module FilterM where
import Prelude (Monad, ($), (<), (>), (/=), bind, return)
import Data.List (List(..))
import Data.Maybe (Maybe(..))
filterM' :: forall m a. (Monad m) => (a -> m Boolean) -> List a -> List a -> m (List a)
filterM' p acc Nil = return acc
filterM' p acc (Cons x xs) = do
keep <- p x
case keep of
true -> filterM' p (Cons x acc) xs
false -> filterM' p acc xs
filterM :: forall m a. (Monad m) => (a -> m Boolean) -> List a -> m (List a)
filterM p lst = filterM' p Nil lst
positive n| n>0 = Just true
positive n| n<0 = Just false
positive _ = Nothing
@BekaValentine
Copy link

i'm going to do this in haskell but the point should be equivalent in purescript.

our goal here is to provide a function

filterM :: forall m a. Monad m => (a -> m Bool) -> [a] -> m [a]
filterM p xs = _

I've put in an underscore (a hole in Haskell) for the RHS so we can have partial programs while we're writing it.

Presumably, filterM should be like filter, only for effectful tests. So we should probably start by trying to treat this like filter, and do a case split on xs:

filterM p [] = _
filterM p (x:xs) = _

For the [] case, now, we can just return the empty list, without any effects from the test, because no tests have to be run:

filterM p [] = return []
filterM p (x:xs) = _

But the x:xs case is trickier. If this were normal filter, we'd just write

filter p (x:xs) = let xs' = filter p xs
                  in if p x
                     then x:xs'
                     else xs'

but we can't do this for two reasons: 1) p is a monadic test so its result isnt a Bool so we can't put the result into if, and 2) filterM is monadic also so we can't put the result into (:).

But wait! Monads give us a way to get out the "wrapped value", so to speak, provided we keep it inside a region that produces monadic results. Namely, (>>=) / do! So let's get the values out with do:

filterM p (x:xs) = do xs' <- filterM p xs
                      b <- p x
                      (if b
                       then x:xs'
                       else xs')

And they presto! it works!

But also... well, this is a correct implementation of the type. HOWEVER: we probably should be sequencing the effects of the monad in the other of the elements, whereas the way I defined it, this happens to do them in reserve order. We just need to flip the two binds:

filterM p (x:xs) = do b <- p x
                      xs' <- filterM p xs
                      (if b
                       then x:xs'
                       else xs')

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