[GHC] #10465: Make listArray non-strict in structure of argument list
GHC
ghc-devs at haskell.org
Sat May 30 15:28:48 UTC 2015
#10465: Make listArray non-strict in structure of argument list
-------------------------------------+-------------------------------------
Reporter: atze | Owner: ekmett
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.10.1
Resolution: | Keywords: laziness
Operating System: Unknown/Multiple | array
Type of failure: Runtime crash | Architecture:
Blocked By: | Unknown/Multiple
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by atze:
Old description:
> There is a subtle caveat when using Data.Array.IArray.listArray, which
> could be easily avoided.
>
> The problem is that listArray strict in the structure of the list, and
> hence if this structure depends on the result of listArray, then the
> result is undefined. However, listArray does not have to be strict in the
> structure of the list.
>
> As an example, consider computing the "failure function" for the Knuth-
> Morris-Pratt algorithm:
>
> {{{#!hs
> failureFunc :: Eq a => Array Int a -> Array Int Int
> failureFunc string = result where
> result = listArray (bounds string) (-1 : 0 : getMatch 2 0)
> getMatch :: Int -> Int -> [Int]
> getMatch p matchPos
> | matchPos < 0 = 0 : getMatch (p+1) 0
> | string ! (p - 1) == string ! matchPos = matchPos + 1 : getMatch
> (p+1) (matchPos+1)
> | otherwise = getMatch p (result ! matchPos) -- use result!
> }}}
>
> This seems reasonable, we just use the result of elements < i to
> construct element i. However, it does not work:
>
> {{{#!hs
> Main> elems $ failureFunc (listArray (0,23) "participate in parachute")
> *** Exception: <<loop>>
> }}}
> The problem is that listArray is equivalent to:
> {{{#!hs
> listArray b l = array b (zip (range b) l)
> }}}
> (Recall that array is strict in the structure of the given list, and in
> the first elements of the tuples in this list, but not in the elements.)
>
> The structure of the list l=(-1 : 0 : getMatch 2 0) depends on the
> observing elements of the array (result ! matchPos). The structure of
> (zip (range b) l) is strict in the structure of l, and hence failure
> loops.
>
> Proposed solution: redefine listArray as equivalent to:
> {{{#!hs
> listArray b l = array b (zipLazyRight (range b) l)
>
> zipLazyRight :: [a] -> [b] -> [(a,b)]
> zipLazyRight [] _ = []
> zipLazyRight (h:t) l = (h,head l): zipLazyRight t (tail l)
> }}}
>
> The difference is that listArray is now non-strict in the structure of
> the argument list, because zipLazyRight is non-strict in the right
> argument. Using this definition, failureFunc does not fail:
> {{{#!hs
> Main> elems $ failureFuncArr (toArr "participate in parachute")
> [-1,0,0,0,0,0,0,0,1,2,0,0,0,0,0,0,1,2,3,0,0,0,0,0]
> }}}
> This does not change the semantics uses of listArray which were already
> defined: it just makes more uses of listArray defined.
New description:
There is a subtle caveat when using Data.Array.IArray.listArray, which
could be easily avoided.
The problem is that listArray strict in the structure of the list, and
hence if this structure depends on the result of listArray, then the
result is undefined. However, listArray does not have to be strict in the
structure of the list.
As an example, consider computing the "failure function" for the Knuth-
Morris-Pratt algorithm:
{{{#!hs
failureFunc :: Eq a => Array Int a -> Array Int Int
failureFunc string = result where
result = listArray (bounds string) (-1 : 0 : getMatch 2 0)
getMatch :: Int -> Int -> [Int]
getMatch p matchPos
| matchPos < 0 = 0 : getMatch (p+1) 0
| string ! (p - 1) == string ! matchPos = matchPos + 1 : getMatch
(p+1) (matchPos+1)
| otherwise = getMatch p (result ! matchPos) -- use result!
}}}
This seems reasonable, we just use the result of elements < i to construct
element i. However, it does not work:
{{{#!hs
Main> elems $ failureFunc (listArray (0,23) "participate in parachute")
*** Exception: <<loop>>
}}}
The problem is that listArray is equivalent to:
{{{#!hs
listArray b l = array b (zip (range b) l)
}}}
(Recall that array is strict in the structure of the given list, and in
the first elements of the tuples in this list, but not in the second
elements of the tuples.)
The structure of the list l=(-1 : 0 : getMatch 2 0) depends on the
observing elements of the array (result ! matchPos). The structure of
(zip (range b) l) is strict in the structure of l, and hence failure
loops.
Proposed solution: redefine listArray as equivalent to:
{{{#!hs
listArray b l = array b (zipLazyRight (range b) l)
zipLazyRight :: [a] -> [b] -> [(a,b)]
zipLazyRight [] _ = []
zipLazyRight (h:t) l = (h,head l): zipLazyRight t (tail l)
}}}
The difference is that listArray is now non-strict in the structure of the
argument list, because zipLazyRight is non-strict in the right argument.
Using this definition, failureFunc does not fail:
{{{#!hs
Main> elems $ failureFuncArr (toArr "participate in parachute")
[-1,0,0,0,0,0,0,0,1,2,0,0,0,0,0,0,1,2,3,0,0,0,0,0]
}}}
This does not change the semantics uses of listArray which were already
defined: it just makes more uses of listArray defined.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10465#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list