I have something like the following:
[bla z|n<-[0..], let z = foo n, z < 42]
The thing is, I want the list comprehension to end as soon as z < 42
fails, as if it were a takeWhile. I know I could refactor this into a bunch of filters and maps, but it will be much more elegant with a list comprehension.
What is the most elegant way to combine list comprehensions and takeWhile?
Since list comprehensions do not allow this, I have hacked a bit using monad comprehensions and defining a custom monad. The outcome of that is that the following works:
example :: [Int]
example = toList [1000 + n
| n <- fromList [0..]
, _ <- nonStopGuard (n > 1)
, let z = 10*n
, _ <- stopGuard (z < 42) ]
-- Output: [1002,1003,1004]
The above works as a normal list comprehension, but has two different kinds of guard. A nonStopGuard
works as a regular guard, except for requiring a bizarre syntax. A stopGuard
instead does something more: as soon as it become false, it stops further choices in the previous generators (such as <-[0..]
) to be considered.
The small library I wrote is shown below:
{-# LANGUAGE DeriveFunctor, MonadComprehensions #-}
import Control.Monad
import Control.Applicative
data F a = F [a] Bool
deriving (Functor, Show)
The Bool
above is a stop bit, signaling we must stop considering further choices.
instance Applicative F where pure = return; (<*>) = ap
instance Monad F where
return x = F [x] False
F [] s >>= _ = F [] s
F (x:xs) sx >>= f = F (ys ++ zs) (sx || sy || sz)
where
F ys sy = f x
F zs sz = if sy then F [] False else F xs sx >>= f
The last if
will discard the xs
part when f x
signals to stop.
nonStopGuard :: Bool -> F ()
nonStopGuard True = F [()] False
nonStopGuard False = F [] False
A regular guard never signals to stop. It just provides one or zero choices.
stopGuard :: Bool -> F ()
stopGuard True = F [()] False
stopGuard False = F [] True
A stopping guard instead signals to stop as soon as it becomes false.
fromList :: [a] -> F a
fromList xs = F xs False
toList :: F a -> [a]
toList (F xs _) = xs
Last caveat: I'm not completely sure my monad instance defines an actual monad, i.e. whether it satisfies the monad laws.
Following the suggestion of @icktoofay, I wrote a few quickcheck tests:
instance Arbitrary a => Arbitrary (F a) where
arbitrary = F <$> arbitrary <*> arbitrary
instance Show (a -> b) where
show _ = "function"
prop_monadRight :: F Int -> Bool
prop_monadRight m =
(m >>= return) == m
prop_monadLeft :: Int -> (Int -> F Int) -> Bool
prop_monadLeft x f =
(return x >>= f) == f x
prop_monadAssoc :: F Int -> (Int -> F Int) -> (Int -> F Int) -> Bool
prop_monadAssoc m f g =
((m >>= f) >>= g)
==
(m >>= (\x -> f x >>= g))
Running 100000 tests found no counterexamples. So, it's likely that the above F
is an actual monad.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With