[Haskell] timing/timeout (how to express that in Haskell)
kahl at cas.mcmaster.ca
kahl at cas.mcmaster.ca
Fri May 12 09:58:51 EDT 2006
>
> It's just annoying that turning a partial function into a total one
> looses so much strictness, since it prevents strictness propagation. Of
> course, this is easily solved using a `strict' Maybe:
> data Perhaps a = Just' !a | Nothing'
>
> Are other people experiencing the same thing, or is it just an academic
> issue and can Haskell compilers optimize it?
I am using StrictMaybe.Maybe'.
I haven't tried to quantify the effect of the optimization pragmas...
Wolfram
==================================================================
%include polycode.fmt
\section{Strict Maybe Variant}
\begin{code}
module Data.Rel.Utils.StrictMaybe where
import Control.Monad
\end{code}
\begin{code}
data Maybe' a = Nothing' | Just' {fromJust' :: {-# UNPACK #-} ! a}
deriving (Eq, Ord, Show, Read)
\end{code}
\begin{code}
maybe' r f Nothing' = r
maybe' r f (Just' x) = f x
\end{code}
\begin{code}
instance Functor Maybe' where
fmap f Nothing' = Nothing'
fmap f (Just' x) = Just' (f x)
{-# INLINE fmap #-}
\end{code}
\begin{code}
instance Monad Maybe' where
return = Just'
Nothing' >>= f = Nothing'
(Just' x) >>= f = f x
{-# INLINE (>>=) #-}
fail = const Nothing'
\end{code}
\begin{code}
instance MonadPlus Maybe' where
mzero = Nothing'
Nothing' `mplus` m = m
m@(Just' x) `mplus` _ = m
\end{code}
More information about the Haskell
mailing list