Proposal: Add a strict version of <$> for monads
Tom Ellis
tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Fri Nov 29 18:42:57 UTC 2013
On Fri, Nov 29, 2013 at 12:03:43PM -0500, Carter Schonwald wrote:
> could someone explain to me why this <$!> would be for monads rather being
> more generally also for functors or applicatives?
It's not clear whether such a thing can be implemented for a functor or
applicative. It seemingly needs to exploit the fact that the next action in
a bind can depend on the "value returned by" the previous action.
Still, the semantics depend very much on the laziness properties of the
monad in question.
f <$!> m = do
a <- m
return $! f a
data R x = R x
data S x = S x
data T x = T x
instance Monad T where
return = T
m >>= f = T (case m of T m' -> case f m' of T y -> y)
instance Monad S where
return = S
m >>= f = case m of S m' -> S (case f m' of S y -> y)
-- Equivalent implementation
-- S m' >>= f = S (case f m' of S y -> y)
instance Monad R where
return = R
m >>= f = case m of R m' -> case f m' of R y -> R y
-- Equivalent implementations:
-- m >>= f = case m of R m' -> f m'
-- R m' >>= f = f m'
try :: Monad m => m Int -> ()
try l = (+1) <$!> l `seq` ()
*Main> try (undefined :: T Int)
()
*Main> try (T undefined :: T Int)
()
*Main> try (undefined :: S Int)
*** Exception: Prelude.undefined
*Main> try (S undefined :: S Int)
()
*Main> try (undefined :: R Int)
*** Exception: Prelude.undefined
*Main> try (R undefined :: R Int)
*** Exception: Prelude.undefined
Tom
More information about the Libraries
mailing list