Skip to content

D.HM.I.Array.index causes thunks #538

@sjakobi

Description

@sjakobi

index :: Array a -> Int -> a
index ary _i@(I# i#) =
CHECK_BOUNDS("index", length ary, _i)
case indexSmallArray# (unArray ary) i# of (# b #) -> b
{-# INLINE index #-}

Here are some examples from intersectionWithKey#, compiled with GHC 9.12.2:

go s t1@(Collision h1 _ls1) (BitmapIndexed b2 ary2)
| b2 .&. m1 == 0 = Empty
| otherwise = go (nextShift s) t1 (A.index ary2 i)

                  case and# bx m2 of {
                    __DEFAULT ->
                      $s$wgo
                        sc
                        sc1
                        (case indexSmallArray#
                                @Lifted
                                @(HashMap k v1)
                                bx1
                                (word2Int# (popCnt# (and# bx (minusWord# m2 1##))))
                         of
                         { (# ipv #) ->
                         ipv
                         })
                        (+# sc3 5#);

go s t1@(Collision h1 _ls1) (Full ary2) = go (nextShift s) t1 (A.index ary2 i)
where
i = index h1 s

                Full bx ->
                  $s$wgo
                    sc
                    sc1
                    (case indexSmallArray#
                            @Lifted
                            @(HashMap k v1)
                            bx
                            (word2Int# (and# (uncheckedShiftRL# sc sc3) 31##))
                     of
                     { (# ipv #) ->
                     ipv
                     })
                    (+# sc3 5#);

What we want instead is something like this:

                  case indexSmallArray#
                         @(HashMap k v2)
                         dt
                         (word2Int# (and# (uncheckedShiftRL# sc1 sc3) 31##))
                  of
                  { (# ipv #) ->
                  $s$wgo ipv sc1 sc2 (+# sc3 5#)

Array.indexM does this reliably.

It seems that GHC 9.2 was a bit more reluctant to create thunks, but it didn't avoid them entirely.

My suggestion would be to change the type of index:

-index :: Array a -> Int -> a
+index :: Array a -> Int -> (# a #)

Metadata

Metadata

Assignees

No one assigned

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions