[Haskell-cafe] Re: How to make code least strict?

Ryan Ingram ryani.spam at gmail.com
Mon Jan 19 18:01:27 EST 2009


Actually, I see a nice pattern here for unamb + pattern matching:

> zip xs ys = foldr unamb undefined [p1 xs ys, p2 xs ys, p3 xs ys] where
>     p1 [] _ = []
>     p2 _ [] = []
>     p3 (x:xs) (y:ys) = (x,y) : zip xs ys

Basically, split each pattern out into a separate function (which by
definition is _|_ if there is no match), then use unamb to combine
them.

The invariant you need to maintain is that potentially overlapping
pattern matches (p1 and p2, here) must return the same result.

With a little typeclass hackery you could turn this into

> zip = unambPatterns [p1,p2,p3] where {- p1, p2, p3 as above -}

Sadly, I believe the performance of "parallel-or"-style operations is
pretty hideous right now.  Conal?

  -- ryan

On Mon, Jan 19, 2009 at 2:42 PM, Conal Elliott <conal at conal.net> wrote:
> I second Ryan's recommendation of using unamb [1,2,3] to give you unbiased
> (symmetric) laziness.
>
> The zip definition could also be written as
>
>     zip xs@(x:xs') ys@(y:ys') =
>       assuming (xs == []) [] `unamb`
>       assuming (ys == []) [] `unamb`
>       (x,y) : zip xs' ys'
>
> The 'assuming' function yields a value if a condition is true and otherwise
> is bottom:
>
>     assuming :: Bool -> a -> a
>     assuming True  a = a
>     assuming False _ = undefined
>
> This zip definition is a special case of the annihilator pattern, so
>
>     zip = parAnnihilator (\ (x:xs') (y:ys') -> (x,y) : zip xs' ys') []
>
> where 'parAnnihilator' is defined in Data.Unamb (along with other goodies)
> as follows:
>
>     parAnnihilator :: Eq a => (a -> a -> a) -> a -> (a -> a -> a)
>     parAnnihilator op ann x y =
>       assuming (x == ann) ann `unamb`
>       assuming (y == ann) ann `unamb`
>       (x `op` y)
>
> [1] http://haskell.org/haskellwiki/Unamb
> [2]
> http://hackage.haskell.org/packages/archive/unamb/latest/doc/html/Data-Unamb.html
> [3] http://conal.net/blog/tag/unamb/
>
>    - conal
>
> On Mon, Jan 19, 2009 at 12:27 PM, Ryan Ingram <ryani.spam at gmail.com> wrote:
>>
>> On Mon, Jan 19, 2009 at 9:10 AM, ChrisK <haskell at list.mightyreason.com>
>> wrote:
>> > Consider that the order of pattern matching can matter as well, the
>> > simplest
>> > common case being zip:
>> >
>> > zip xs [] = []
>> > zip [] ys = []
>> > zip (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> If you are obsessive about least-strictness and performance isn't a
>> giant concern, this seems like a perfect use for Conal's unamb[1]
>> operator.
>>
>> zipR xs [] = []
>> zipR [] ys = []
>> zipR (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zipL [] ys = []
>> zipL xs [] = []
>> zipL (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zip xs ys = unamb (zipL xs ys) (zipR xs ys)
>>
>> This runs both zipL and zipR in parallel until one of them gives a
>> result; if neither of them is _|_ they are guaranteed to be identical,
>> so we can "unambiguously choose" whichever one gives a result first.
>>
>>  -- ryan
>>
>> [1]
>> http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list