[Haskell-cafe] Mystery operator?
Daniel Fischer
daniel.is.fischer at web.de
Mon Nov 30 15:10:45 EST 2009
Am Montag 30 November 2009 20:01:04 schrieb michael rice:
> Hi all,
>
> A lot of things posted here I wasn't aware of. My original example involved
> ~(x,y), so, returning to that context, how would these two simple cases
> vary:
>
> add2 :: (Int,Int) -> Int
> add2 (x,y) = x+y
>
> add2 :: (Int,Int) -> Int
> add2 ~(x,y) = x+y
For the type (Int,Int) -> Int, the two definitions wouldn't expose different behaviour
(okay, faced with add2 undefined, one would raise the Prelude.undefined exception while
pattern-matching undefined to (x,y), the other a few nanoseconds later when trying to
extract to bona fide Ints from undefined for the addition). For other types, it can make a
difference:
-----------------------------------
module TestLazyPat where
add2' :: Num a => (a,a) -> a
add2' (x,y) = x+y
add2 :: Num a => (a,a) -> a
add2 ~(x,y) = x+y
data StupidNum = S
deriving (Eq, Ord, Show)
instance Num StupidNum where
_ + _ = S
_ - _ = S
_ * _ = S
signum _ = S
abs _ = S
negate _ = S
fromInteger _ = S
---------------------------------
*TestLazyPat> add2 undefined :: StupidNum
S
*TestLazyPat> add2' undefined :: StupidNum
*** Exception: Prelude.undefined
*TestLazyPat> add2' (undefined,undefined) :: StupidNum
S
That's not a very useful example, though.
>
> I guess what I'm looking for is the concept that would dictate choosing one
> over the other.
One thing may be "would you like your function to be able to cope with undefined?".
More common is the usecase of the example from your first post,
foldr (\a (~(x,y)) -> (a:y,x)) ([],[]) xs
With a strict tuple-pattern, the system can't know whether the computation produces a pair
or bottom, so it can't actually start building the answer before the whole list has been
traversed to make sure that yes, indeed, we have a tuple.
And if the list is infinite, the second argument to the folded function is indeed not a
tuple but bottom.
When you tell the compiler to just assume it will receive a pair here, it can start
assembling right away (and thus making the assumption come true).
When *you* know something will have a certain structure, but the compiler can't know it
(for it might be bottom), use a lazy pattern to get things underway.
>
> Thanks,
>
> Michael
More information about the Haskell-Cafe
mailing list