[Haskell-cafe] Re[2]: strict Haskell dialect

Chris Kuklewicz haskell at list.mightyreason.com
Fri Feb 3 16:06:20 EST 2006


Brian Hulley wrote:
> > ...
>
> [Apologies for replying to a reply of a reply but I don't seem to have
> received the original post]
> 
> I've been thinking along these lines too, because it has always seemed
> to me that laziness is just a real nuisance because it hides a lot of
> inefficiency under the carpet as well as making the time/space behaviour
> of programs difficult to understand...
> 
> One question is how to get some kind of "do" notation that would work
> well in a strict setting.
> The existing "do" notation makes use of lazyness in so far as the second
> arg of  >> is only evaluated when needed. Perhaps a new keyword such as
> "go" could be used to use >>= instead ie:
> 
> go {e1;e2;e3}   ===           e1 >>= (\_-> (e2 >>= (\_->e3)))
> 
> Of course this doesn't solve the problem of how to translate programs
> that make heavy use of mapM etc.
> 
> I wonder: is monadic programming really dependent on lazyness or is
> there a realistic (ie not impossibly complicated) way to use monads in a
> strict setting?
> 
> A related question is: could monadic programming ever be as efficient as
> side-effect programming?
> 
> Regards, Brian.

What about writing functions in a modified form of Control.Monad.Identity that
ensures the return value that forces the return values:

> module Control.Monad.Strict (Weak,mkWeak,unsafeMkWeak,runWeak,
>                              Deep,mkDeep,unsafeMkDeep,runDeep) where

Weak uses seq to achieve WHNF for it's argument

> newtype Weak a = WeakCon {runWeak :: a}
> mkWeak x = seq x (WeakCon x)
> unsafeMkWeak x = WeakCon x
>
> instance Functor Weak where
>     fmap f w = mkWeak (f (runWeak w))
>
> instance Monad Weak where
>     return x = mkWeak x
>     w >>= f = f (runWeak w)
>

I can't make the deepSeq version typecheck:

Deep uses deepSeq to evaluate it's argument

> newtype Deep a = DeepCon {runDeep :: a}
> mkDeep x = deepSeq x (DeepCon a)
> unsafeDeep x = DeepCon x
>
> instance Functor Deep where
>     fmap f d = mkDeep (f (runDeep d))
>
> instance Monad Deep where
>     return d = mkDeep d
>     d >>= f = f (runDeep d)



More information about the Haskell-Cafe mailing list