(original) (raw)
{-# LANGUAGE Unsafe #-} {-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, RoleAnnotations #-} {-# LANGUAGE BangPatterns #-} {-# OPTIONS_HADDOCK hide #-}
module GHC.Arr ( Ix(..), Array(..), STArray(..),
[indexError](GHC.Arr.html#indexError), [hopelessIndexError](GHC.Arr.html#hopelessIndexError),
[arrEleBottom](GHC.Arr.html#arrEleBottom), [array](GHC.Arr.html#array), [listArray](GHC.Arr.html#listArray),
(!), [safeRangeSize](GHC.Arr.html#safeRangeSize), [negRange](GHC.Arr.html#negRange), [safeIndex](GHC.Arr.html#safeIndex), [badSafeIndex](GHC.Arr.html#badSafeIndex),
[bounds](GHC.Arr.html#bounds), [numElements](GHC.Arr.html#numElements), [numElementsSTArray](GHC.Arr.html#numElementsSTArray), [indices](GHC.Arr.html#indices), [elems](GHC.Arr.html#elems),
[assocs](GHC.Arr.html#assocs), [accumArray](GHC.Arr.html#accumArray), [adjust](GHC.Arr.html#adjust), ([//](GHC.Arr.html#%2F%2F)), [accum](GHC.Arr.html#accum),
[amap](GHC.Arr.html#amap), [ixmap](GHC.Arr.html#ixmap),
[eqArray](GHC.Arr.html#eqArray), [cmpArray](GHC.Arr.html#cmpArray), [cmpIntArray](GHC.Arr.html#cmpIntArray),
[newSTArray](GHC.Arr.html#newSTArray), [boundsSTArray](GHC.Arr.html#boundsSTArray),
[readSTArray](GHC.Arr.html#readSTArray), [writeSTArray](GHC.Arr.html#writeSTArray),
[freezeSTArray](GHC.Arr.html#freezeSTArray), [thawSTArray](GHC.Arr.html#thawSTArray),
[foldlElems](GHC.Arr.html#foldlElems), [foldlElems'](GHC.Arr.html#foldlElems%27), [foldl1Elems](GHC.Arr.html#foldl1Elems),
[foldrElems](GHC.Arr.html#foldrElems), [foldrElems'](GHC.Arr.html#foldrElems%27), [foldr1Elems](GHC.Arr.html#foldr1Elems),
[fill](GHC.Arr.html#fill), [done](GHC.Arr.html#done),
[unsafeArray](GHC.Arr.html#unsafeArray), [unsafeArray'](GHC.Arr.html#unsafeArray%27),
[lessSafeIndex](GHC.Arr.html#lessSafeIndex), [unsafeAt](GHC.Arr.html#unsafeAt), [unsafeReplace](GHC.Arr.html#unsafeReplace),
[unsafeAccumArray](GHC.Arr.html#unsafeAccumArray), [unsafeAccumArray'](GHC.Arr.html#unsafeAccumArray%27), [unsafeAccum](GHC.Arr.html#unsafeAccum),
[unsafeReadSTArray](GHC.Arr.html#unsafeReadSTArray), [unsafeWriteSTArray](GHC.Arr.html#unsafeWriteSTArray),
[unsafeFreezeSTArray](GHC.Arr.html#unsafeFreezeSTArray), [unsafeThawSTArray](GHC.Arr.html#unsafeThawSTArray),
) where
import GHC.Enum import GHC.Num import GHC.ST import GHC.Base import GHC.List import GHC.Real( fromIntegral ) import GHC.Show
infixl 9 !, //
default ()
class (Ord a) => Ix a where {-# MINIMAL range, (index | unsafeIndex), inRange #-}
[range](GHC.Arr.html#range) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> [[a](#local-6989586621679053236)]
[index](GHC.Arr.html#index) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> [a](#local-6989586621679053236) -> Int
[unsafeIndex](GHC.Arr.html#unsafeIndex) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> [a](#local-6989586621679053236) -> Int
[inRange](GHC.Arr.html#inRange) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> [a](#local-6989586621679053236) -> Bool
[rangeSize](GHC.Arr.html#rangeSize) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> Int
[unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) :: ([a](#local-6989586621679053236),[a](#local-6989586621679053236)) -> Int
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053237) [i](#local-6989586621679053238) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053237) [i](#local-6989586621679053238) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053237) [i](#local-6989586621679053238)
| [otherwise](GHC.Base.html#otherwise) = [hopelessIndexError](GHC.Arr.html#hopelessIndexError)
[unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053239) [i](#local-6989586621679053240) = [index](GHC.Arr.html#index) [b](#local-6989586621679053239) [i](#local-6989586621679053240)
[rangeSize](GHC.Arr.html#rangeSize) [b](#local-6989586621679053241)@([_l](#local-6989586621679053242),[h](#local-6989586621679053243)) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053241) [h](#local-6989586621679053243) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053241) [h](#local-6989586621679053243) [+](GHC.Num.html#%2B) 1
| [otherwise](GHC.Base.html#otherwise) = 0
[unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) [b](#local-6989586621679053244)@([_l](#local-6989586621679053245),[h](#local-6989586621679053246)) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053244) [h](#local-6989586621679053246) [+](GHC.Num.html#%2B) 1
{-# NOINLINE indexError #-} indexError :: Show a => (a,a) -> a -> String -> b indexError rng i tp = errorWithoutStackTrace (showString "Ix{" . showString tp . showString "}.index: Index " . showParen True (showsPrec 0 i) . showString " out of range " $ showParen True (showsPrec 0 rng) "")
hopelessIndexError :: Int hopelessIndexError = errorWithoutStackTrace "Error in array index"
instance Ix Char where {-# INLINE range #-} range (m,n) = [m..n]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([m](#local-6989586621679053459),[_n](#local-6989586621679053460)) [i](#local-6989586621679053461) = [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053461) - [fromEnum](GHC.Enum.html#fromEnum) [m](#local-6989586621679053459)
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053462) [i](#local-6989586621679053463) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053462) [i](#local-6989586621679053463) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053462) [i](#local-6989586621679053463)
| [otherwise](GHC.Base.html#otherwise) = [indexError](GHC.Arr.html#indexError) [b](#local-6989586621679053462) [i](#local-6989586621679053463) "Char"
[inRange](GHC.Arr.html#inRange) ([m](#local-6989586621679053464),[n](#local-6989586621679053465)) [i](#local-6989586621679053466) = [m](#local-6989586621679053464) <= [i](#local-6989586621679053466) && [i](#local-6989586621679053466) <= [n](#local-6989586621679053465)
instance Ix Int where {-# INLINE range #-}
[range](GHC.Arr.html#range) ([m](#local-6989586621679053447),[n](#local-6989586621679053448)) = [[m](#local-6989586621679053447)..[n](#local-6989586621679053448)]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([m](#local-6989586621679053449),[_n](#local-6989586621679053450)) [i](#local-6989586621679053451) = [i](#local-6989586621679053451) - [m](#local-6989586621679053449)
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053452) [i](#local-6989586621679053453) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053452) [i](#local-6989586621679053453) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053452) [i](#local-6989586621679053453)
| [otherwise](GHC.Base.html#otherwise) = [indexError](GHC.Arr.html#indexError) [b](#local-6989586621679053452) [i](#local-6989586621679053453) "Int"
{-# INLINE inRange #-}
[inRange](GHC.Arr.html#inRange) (I# [m](#local-6989586621679053454),I# [n](#local-6989586621679053455)) (I# [i](#local-6989586621679053456)) = isTrue# ([m](#local-6989586621679053454) <=# [i](#local-6989586621679053456)) && isTrue# ([i](#local-6989586621679053456) <=# [n](#local-6989586621679053455))
instance Ix Word where range (m,n) = [m..n] unsafeIndex (m,_) i = fromIntegral (i - m) inRange (m,n) i = m <= i && i <= n
instance Ix Integer where {-# INLINE range #-} range (m,n) = [m..n]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([m](#local-6989586621679053432),[_n](#local-6989586621679053433)) [i](#local-6989586621679053434) = [fromInteger](GHC.Num.html#fromInteger) ([i](#local-6989586621679053434) - [m](#local-6989586621679053432))
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053435) [i](#local-6989586621679053436) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053435) [i](#local-6989586621679053436) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053435) [i](#local-6989586621679053436)
| [otherwise](GHC.Base.html#otherwise) = [indexError](GHC.Arr.html#indexError) [b](#local-6989586621679053435) [i](#local-6989586621679053436) "Integer"
[inRange](GHC.Arr.html#inRange) ([m](#local-6989586621679053437),[n](#local-6989586621679053438)) [i](#local-6989586621679053439) = [m](#local-6989586621679053437) <= [i](#local-6989586621679053439) && [i](#local-6989586621679053439) <= [n](#local-6989586621679053438)
instance Ix Natural where range (m,n) = [m..n] inRange (m,n) i = m <= i && i <= n unsafeIndex (m,_) i = fromIntegral (i-m) index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Natural"
instance Ix Bool where {-# INLINE range #-} range (m,n) = [m..n]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l](#local-6989586621679053414),_) [i](#local-6989586621679053415) = [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053415) - [fromEnum](GHC.Enum.html#fromEnum) [l](#local-6989586621679053414)
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053416) [i](#local-6989586621679053417) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053416) [i](#local-6989586621679053417) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053416) [i](#local-6989586621679053417)
| [otherwise](GHC.Base.html#otherwise) = [indexError](GHC.Arr.html#indexError) [b](#local-6989586621679053416) [i](#local-6989586621679053417) "Bool"
[inRange](GHC.Arr.html#inRange) ([l](#local-6989586621679053418),[u](#local-6989586621679053419)) [i](#local-6989586621679053420) = [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053420) >= [fromEnum](GHC.Enum.html#fromEnum) [l](#local-6989586621679053418) && [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053420) <= [fromEnum](GHC.Enum.html#fromEnum) [u](#local-6989586621679053419)
instance Ix Ordering where {-# INLINE range #-} range (m,n) = [m..n]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l](#local-6989586621679053405),_) [i](#local-6989586621679053406) = [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053406) - [fromEnum](GHC.Enum.html#fromEnum) [l](#local-6989586621679053405)
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053407) [i](#local-6989586621679053408) | [inRange](GHC.Arr.html#inRange) [b](#local-6989586621679053407) [i](#local-6989586621679053408) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053407) [i](#local-6989586621679053408)
| [otherwise](GHC.Base.html#otherwise) = [indexError](GHC.Arr.html#indexError) [b](#local-6989586621679053407) [i](#local-6989586621679053408) "Ordering"
[inRange](GHC.Arr.html#inRange) ([l](#local-6989586621679053409),[u](#local-6989586621679053410)) [i](#local-6989586621679053411) = [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053411) >= [fromEnum](GHC.Enum.html#fromEnum) [l](#local-6989586621679053409) && [fromEnum](GHC.Enum.html#fromEnum) [i](#local-6989586621679053411) <= [fromEnum](GHC.Enum.html#fromEnum) [u](#local-6989586621679053410)
instance Ix () where {-# INLINE range #-} range ((), ()) = [()] {-# INLINE unsafeIndex #-} unsafeIndex ((), ()) () = 0 {-# INLINE inRange #-} inRange ((), ()) () = True
{-# INLINE index #-}
[index](GHC.Arr.html#index) [b](#local-6989586621679053401) [i](#local-6989586621679053402) = [unsafeIndex](GHC.Arr.html#unsafeIndex) [b](#local-6989586621679053401) [i](#local-6989586621679053402)
instance (Ix a, Ix b) => Ix (a, b) where {-# SPECIALISE instance Ix (Int,Int) #-}
{-# INLINE range #-}
[range](GHC.Arr.html#range) (([l1](#local-6989586621679053383),[l2](#local-6989586621679053384)),([u1](#local-6989586621679053385),[u2](#local-6989586621679053386))) =
[ ([i1](#local-6989586621679053387),[i2](#local-6989586621679053388)) | [i1](#local-6989586621679053387) <- [range](GHC.Arr.html#range) ([l1](#local-6989586621679053383),[u1](#local-6989586621679053385)), [i2](#local-6989586621679053388) <- [range](GHC.Arr.html#range) ([l2](#local-6989586621679053384),[u2](#local-6989586621679053386)) ]
{-# INLINE unsafeIndex #-}
[unsafeIndex](GHC.Arr.html#unsafeIndex) (([l1](#local-6989586621679053389),[l2](#local-6989586621679053390)),([u1](#local-6989586621679053391),[u2](#local-6989586621679053392))) ([i1](#local-6989586621679053393),[i2](#local-6989586621679053394)) =
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l1](#local-6989586621679053389),[u1](#local-6989586621679053391)) [i1](#local-6989586621679053393) [*](GHC.Num.html#%2A) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l2](#local-6989586621679053390),[u2](#local-6989586621679053392)) [+](GHC.Num.html#%2B) [unsafeIndex](GHC.Arr.html#unsafeIndex) ([l2](#local-6989586621679053390),[u2](#local-6989586621679053392)) [i2](#local-6989586621679053394)
{-# INLINE inRange #-}
[inRange](GHC.Arr.html#inRange) (([l1](#local-6989586621679053395),[l2](#local-6989586621679053396)),([u1](#local-6989586621679053397),[u2](#local-6989586621679053398))) ([i1](#local-6989586621679053399),[i2](#local-6989586621679053400)) =
[inRange](GHC.Arr.html#inRange) ([l1](#local-6989586621679053395),[u1](#local-6989586621679053397)) [i1](#local-6989586621679053399) && [inRange](GHC.Arr.html#inRange) ([l2](#local-6989586621679053396),[u2](#local-6989586621679053398)) [i2](#local-6989586621679053400)
instance (Ix a1, Ix a2, Ix a3) => Ix (a1,a2,a3) where {-# SPECIALISE instance Ix (Int,Int,Int) #-}
[range](GHC.Arr.html#range) (([l1](#local-6989586621679053354),[l2](#local-6989586621679053355),[l3](#local-6989586621679053356)),([u1](#local-6989586621679053357),[u2](#local-6989586621679053358),[u3](#local-6989586621679053359))) =
[([i1](#local-6989586621679053360),[i2](#local-6989586621679053361),[i3](#local-6989586621679053362)) | [i1](#local-6989586621679053360) <- [range](GHC.Arr.html#range) ([l1](#local-6989586621679053354),[u1](#local-6989586621679053357)),
[i2](#local-6989586621679053361) <- [range](GHC.Arr.html#range) ([l2](#local-6989586621679053355),[u2](#local-6989586621679053358)),
[i3](#local-6989586621679053362) <- [range](GHC.Arr.html#range) ([l3](#local-6989586621679053356),[u3](#local-6989586621679053359))]
[unsafeIndex](GHC.Arr.html#unsafeIndex) (([l1](#local-6989586621679053363),[l2](#local-6989586621679053364),[l3](#local-6989586621679053365)),([u1](#local-6989586621679053366),[u2](#local-6989586621679053367),[u3](#local-6989586621679053368))) ([i1](#local-6989586621679053369),[i2](#local-6989586621679053370),[i3](#local-6989586621679053371)) =
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l3](#local-6989586621679053365),[u3](#local-6989586621679053368)) [i3](#local-6989586621679053371) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l3](#local-6989586621679053365),[u3](#local-6989586621679053368)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l2](#local-6989586621679053364),[u2](#local-6989586621679053367)) [i2](#local-6989586621679053370) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l2](#local-6989586621679053364),[u2](#local-6989586621679053367)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l1](#local-6989586621679053363),[u1](#local-6989586621679053366)) [i1](#local-6989586621679053369)))
[inRange](GHC.Arr.html#inRange) (([l1](#local-6989586621679053372),[l2](#local-6989586621679053373),[l3](#local-6989586621679053374)),([u1](#local-6989586621679053375),[u2](#local-6989586621679053376),[u3](#local-6989586621679053377))) ([i1](#local-6989586621679053378),[i2](#local-6989586621679053379),[i3](#local-6989586621679053380)) =
[inRange](GHC.Arr.html#inRange) ([l1](#local-6989586621679053372),[u1](#local-6989586621679053375)) [i1](#local-6989586621679053378) && [inRange](GHC.Arr.html#inRange) ([l2](#local-6989586621679053373),[u2](#local-6989586621679053376)) [i2](#local-6989586621679053379) &&
[inRange](GHC.Arr.html#inRange) ([l3](#local-6989586621679053374),[u3](#local-6989586621679053377)) [i3](#local-6989586621679053380)
instance (Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1,a2,a3,a4) where range ((l1,l2,l3,l4),(u1,u2,u3,u4)) = [(i1,i2,i3,i4) | i1 <- range (l1,u1), i2 <- range (l2,u2), i3 <- range (l3,u3), i4 <- range (l4,u4)]
[unsafeIndex](GHC.Arr.html#unsafeIndex) (([l1](#local-6989586621679053327),[l2](#local-6989586621679053328),[l3](#local-6989586621679053329),[l4](#local-6989586621679053330)),([u1](#local-6989586621679053331),[u2](#local-6989586621679053332),[u3](#local-6989586621679053333),[u4](#local-6989586621679053334))) ([i1](#local-6989586621679053335),[i2](#local-6989586621679053336),[i3](#local-6989586621679053337),[i4](#local-6989586621679053338)) =
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l4](#local-6989586621679053330),[u4](#local-6989586621679053334)) [i4](#local-6989586621679053338) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l4](#local-6989586621679053330),[u4](#local-6989586621679053334)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l3](#local-6989586621679053329),[u3](#local-6989586621679053333)) [i3](#local-6989586621679053337) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l3](#local-6989586621679053329),[u3](#local-6989586621679053333)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l2](#local-6989586621679053328),[u2](#local-6989586621679053332)) [i2](#local-6989586621679053336) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l2](#local-6989586621679053328),[u2](#local-6989586621679053332)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l1](#local-6989586621679053327),[u1](#local-6989586621679053331)) [i1](#local-6989586621679053335))))
[inRange](GHC.Arr.html#inRange) (([l1](#local-6989586621679053339),[l2](#local-6989586621679053340),[l3](#local-6989586621679053341),[l4](#local-6989586621679053342)),([u1](#local-6989586621679053343),[u2](#local-6989586621679053344),[u3](#local-6989586621679053345),[u4](#local-6989586621679053346))) ([i1](#local-6989586621679053347),[i2](#local-6989586621679053348),[i3](#local-6989586621679053349),[i4](#local-6989586621679053350)) =
[inRange](GHC.Arr.html#inRange) ([l1](#local-6989586621679053339),[u1](#local-6989586621679053343)) [i1](#local-6989586621679053347) && [inRange](GHC.Arr.html#inRange) ([l2](#local-6989586621679053340),[u2](#local-6989586621679053344)) [i2](#local-6989586621679053348) &&
[inRange](GHC.Arr.html#inRange) ([l3](#local-6989586621679053341),[u3](#local-6989586621679053345)) [i3](#local-6989586621679053349) && [inRange](GHC.Arr.html#inRange) ([l4](#local-6989586621679053342),[u4](#local-6989586621679053346)) [i4](#local-6989586621679053350)
instance (Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1,a2,a3,a4,a5) where range ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) = [(i1,i2,i3,i4,i5) | i1 <- range (l1,u1), i2 <- range (l2,u2), i3 <- range (l3,u3), i4 <- range (l4,u4), i5 <- range (l5,u5)]
[unsafeIndex](GHC.Arr.html#unsafeIndex) (([l1](#local-6989586621679053281),[l2](#local-6989586621679053282),[l3](#local-6989586621679053283),[l4](#local-6989586621679053284),[l5](#local-6989586621679053285)),([u1](#local-6989586621679053286),[u2](#local-6989586621679053287),[u3](#local-6989586621679053288),[u4](#local-6989586621679053289),[u5](#local-6989586621679053290))) ([i1](#local-6989586621679053291),[i2](#local-6989586621679053292),[i3](#local-6989586621679053293),[i4](#local-6989586621679053294),[i5](#local-6989586621679053295)) =
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l5](#local-6989586621679053285),[u5](#local-6989586621679053290)) [i5](#local-6989586621679053295) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l5](#local-6989586621679053285),[u5](#local-6989586621679053290)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l4](#local-6989586621679053284),[u4](#local-6989586621679053289)) [i4](#local-6989586621679053294) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l4](#local-6989586621679053284),[u4](#local-6989586621679053289)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l3](#local-6989586621679053283),[u3](#local-6989586621679053288)) [i3](#local-6989586621679053293) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l3](#local-6989586621679053283),[u3](#local-6989586621679053288)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l2](#local-6989586621679053282),[u2](#local-6989586621679053287)) [i2](#local-6989586621679053292) [+](GHC.Num.html#%2B) [unsafeRangeSize](GHC.Arr.html#unsafeRangeSize) ([l2](#local-6989586621679053282),[u2](#local-6989586621679053287)) [*](GHC.Num.html#%2A) (
[unsafeIndex](GHC.Arr.html#unsafeIndex) ([l1](#local-6989586621679053281),[u1](#local-6989586621679053286)) [i1](#local-6989586621679053291)))))
[inRange](GHC.Arr.html#inRange) (([l1](#local-6989586621679053296),[l2](#local-6989586621679053297),[l3](#local-6989586621679053298),[l4](#local-6989586621679053299),[l5](#local-6989586621679053300)),([u1](#local-6989586621679053301),[u2](#local-6989586621679053302),[u3](#local-6989586621679053303),[u4](#local-6989586621679053304),[u5](#local-6989586621679053305))) ([i1](#local-6989586621679053306),[i2](#local-6989586621679053307),[i3](#local-6989586621679053308),[i4](#local-6989586621679053309),[i5](#local-6989586621679053310)) =
[inRange](GHC.Arr.html#inRange) ([l1](#local-6989586621679053296),[u1](#local-6989586621679053301)) [i1](#local-6989586621679053306) && [inRange](GHC.Arr.html#inRange) ([l2](#local-6989586621679053297),[u2](#local-6989586621679053302)) [i2](#local-6989586621679053307) &&
[inRange](GHC.Arr.html#inRange) ([l3](#local-6989586621679053298),[u3](#local-6989586621679053303)) [i3](#local-6989586621679053308) && [inRange](GHC.Arr.html#inRange) ([l4](#local-6989586621679053299),[u4](#local-6989586621679053304)) [i4](#local-6989586621679053309) &&
[inRange](GHC.Arr.html#inRange) ([l5](#local-6989586621679053300),[u5](#local-6989586621679053305)) [i5](#local-6989586621679053310)
data Array i e
= Array
{-# UNPACK #-} !Int
(Array# [e](#local-6989586621679053235))
data STArray s i e
= STArray
{-# UNPACK #-} !Int
(MutableArray# [s](#local-6989586621679053231) [e](#local-6989586621679053233))
type role Array nominal representational type role STArray nominal nominal representational
instance Eq (STArray s i e) where STArray _ _ _ arr1# == STArray _ _ _ arr2# = isTrue# (sameMutableArray# arr1# arr2#)
{-# NOINLINE arrEleBottom #-} arrEleBottom :: a arrEleBottom = errorWithoutStackTrace "(Array.!): undefined array element"
{-# INLINE array #-} array :: Ix i => (i,i)
-> [([i](#local-6989586621679053590), [e](#local-6989586621679053591))]
-> [Array](GHC.Arr.html#Array) [i](#local-6989586621679053590) [e](#local-6989586621679053591)
array (l,u) ies = let n = safeRangeSize (l,u) in unsafeArray' (l,u) n [(safeIndex (l,u) n i, e) | (i, e) <- ies]
{-# INLINE unsafeArray #-} unsafeArray :: Ix i => (i,i) -> [(Int, e)] -> Array i e unsafeArray b ies = unsafeArray' b (rangeSize b) ies
{-# INLINE unsafeArray' #-} unsafeArray' :: (i,i) -> Int -> [(Int, e)] -> Array i e unsafeArray' (l,u) n@(I# n#) ies = runST (ST $ [s1#](#local-6989586621679053611) -> case newArray# n# arrEleBottom s1# of (# s2#, marr# #) -> foldr (fill marr#) (done l u n marr#) ies s2#)
{-# INLINE fill #-} fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
fill marr# (I# i#, e) next = [s1#](#local-6989586621679053618) -> case writeArray# marr# i# e s1# of s2# -> next s2#
{-# INLINE done #-} done :: i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
done l u n@(I# _) marr# = [s1#](#local-6989586621679053624) -> case unsafeFreezeArray# marr# s1# of (# s2#, arr# #) -> (# s2#, Array l u n arr# #)
{-# INLINE listArray #-} listArray :: Ix i => (i,i) -> [e] -> Array i e listArray (l,u) es = runST (ST $ [s1#](#local-6989586621679053630) -> case safeRangeSize (l,u) of { n@(I# n#) -> case newArray# n# arrEleBottom s1# of { (# s2#, marr# #) -> let go y r = \ i# s3# -> case writeArray# marr# i# y s3# of s4# -> if (isTrue# (i# ==# n# -# 1#)) then s4# else r (i# +# 1#) s4# in done l u n marr# ( if n == 0 then s2# else foldr go (_ s# -> s#) es 0# s2#)}})
{-# INLINE (!) #-} (!) :: Ix i => Array i e -> i -> e (!) arr@(Array l u n _) i = unsafeAt arr $ safeIndex (l,u) n i
{-# INLINE (!#) #-} (!#) :: Ix i => Array i e -> i -> (# e #) (!#) arr@(Array l u n _) i = unsafeAt# arr $ safeIndex (l,u) n i
{-# INLINE safeRangeSize #-} safeRangeSize :: Ix i => (i, i) -> Int safeRangeSize (l,u) = let r = rangeSize (l, u) in if r < 0 then negRange else r
negRange :: Int
negRange = errorWithoutStackTrace "Negative range size"
{-# INLINE[1] safeIndex #-}
safeIndex :: Ix i => (i, i) -> Int -> i -> Int safeIndex (l,u) n@(I# _) i | (0 <= i') && (i' < n) = i' | otherwise = badSafeIndex i' n where i' = index (l,u) i
{-# RULES "safeIndex/I" safeIndex = lessSafeIndex :: (Int,Int) -> Int -> Int -> Int "safeIndex/(I,I)" safeIndex = lessSafeIndex :: ((Int,Int),(Int,Int)) -> Int -> (Int,Int) -> Int "safeIndex/(I,I,I)" safeIndex = lessSafeIndex :: ((Int,Int,Int),(Int,Int,Int)) -> Int -> (Int,Int,Int) -> Int #-}
lessSafeIndex :: Ix i => (i, i) -> Int -> i -> Int
lessSafeIndex (l,u) _ i = index (l,u) i
badSafeIndex :: Int -> Int -> Int badSafeIndex i' n = errorWithoutStackTrace ("Error in array index; " ++ show i' ++ " not in range [0.." ++ show n ++ ")")
{-# INLINE unsafeAt #-} unsafeAt :: Array i e -> Int -> e unsafeAt (Array _ _ _ arr#) (I# i#) = case indexArray# arr# i# of (# e #) -> e
unsafeAt# :: Array i e -> Int -> (# e #) unsafeAt# (Array _ _ _ arr#) (I# i#) = indexArray# arr# i#
unsafeAtA :: Applicative f => Array i e -> Int -> f e unsafeAtA ary i = case unsafeAt# ary i of (# e #) -> pure e
{-# INLINE bounds #-} bounds :: Array i e -> (i,i) bounds (Array l u _ _) = (l,u)
{-# INLINE numElements #-} numElements :: Array i e -> Int numElements (Array _ _ n _) = n
{-# INLINE indices #-} indices :: Ix i => Array i e -> [i] indices (Array l u _ _) = range (l,u)
{-# INLINE elems #-} elems :: Array i e -> [e] elems arr@(Array _ _ n _) = [e | i <- [0 .. n - 1], e <- unsafeAtA arr i]
{-# INLINABLE foldrElems #-} foldrElems :: (a -> b -> b) -> b -> Array i a -> b foldrElems f b0 = \ arr@(Array _ _ n _) -> let go i | i == n = b0 | (# e #) <- unsafeAt# arr i = f e (go (i+1)) in go 0
{-# INLINABLE foldlElems #-} foldlElems :: (b -> a -> b) -> b -> Array i a -> b foldlElems f b0 = \ arr@(Array _ _ n _) -> let go i | i == (-1) = b0 | (# e #) <- unsafeAt# arr i = f (go (i-1)) e in go (n-1)
{-# INLINABLE foldrElems' #-} foldrElems' :: (a -> b -> b) -> b -> Array i a -> b foldrElems' f b0 = \ arr@(Array _ _ n _) -> let go i a | i == (-1) = a | (# e #) <- unsafeAt# arr i = go (i-1) (f e $! a) in go (n-1) b0
{-# INLINABLE foldlElems' #-}
foldlElems' :: (b -> a -> b) -> b -> Array i a -> b
foldlElems' f b0 = \ arr@(Array _ _ n _) ->
let
go i a | i == n = a
| (# e #) <- unsafeAt# arr i
= go (i+1) (a seq
f a e)
in go 0 b0
{-# INLINABLE foldl1Elems #-} foldl1Elems :: (a -> a -> a) -> Array i a -> a foldl1Elems f = \ arr@(Array _ _ n _) -> let go i | i == 0 = unsafeAt arr 0 | (# e #) <- unsafeAt# arr i = f (go (i-1)) e in if n == 0 then errorWithoutStackTrace "foldl1: empty Array" else go (n-1)
{-# INLINABLE foldr1Elems #-} foldr1Elems :: (a -> a -> a) -> Array i a -> a foldr1Elems f = \ arr@(Array _ _ n _) -> let go i | i == n-1 = unsafeAt arr i | (# e #) <- unsafeAt# arr i = f e (go (i + 1)) in if n == 0 then errorWithoutStackTrace "foldr1: empty Array" else go 0
{-# INLINE assocs #-} assocs :: Ix i => Array i e -> [(i, e)] assocs arr@(Array l u _ _) = [(i, e) | i <- range (l,u), let !(# e #) = arr !# i]
{-# INLINE accumArray #-}
accumArray :: Ix i
=> (e -> a -> e)
-> e
-> (i,i)
-> [(i, a)]
-> Array i e
accumArray f initial (l,u) ies =
let n = safeRangeSize (l,u)
in unsafeAccumArray' f initial (l,u) n
[(safeIndex (l,u) n i, e) | (i, e) <- ies]
{-# INLINE unsafeAccumArray #-} unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i,i) -> [(Int, a)] -> Array i e unsafeAccumArray f initial b ies = unsafeAccumArray' f initial b (rangeSize b) ies
{-# INLINE unsafeAccumArray' #-} unsafeAccumArray' :: (e -> a -> e) -> e -> (i,i) -> Int -> [(Int, a)] -> Array i e unsafeAccumArray' f initial (l,u) n@(I# n#) ies = runST (ST $ [s1#](#local-6989586621679053748) -> case newArray# n# initial s1# of { (# s2#, marr# #) -> foldr (adjust' f marr#) (done l u n marr#) ies s2# })
{-# INLINE adjust #-} adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
adjust f marr# (I# i#, new) next = [s1#](#local-6989586621679053756) -> case readArray# marr# i# s1# of (# s2#, old #) -> case writeArray# marr# i# (f old new) s2# of s3# -> next s3#
{-# INLINE adjust' #-}
adjust' :: (e -> a -> e)
-> MutableArray# s e
-> (Int, a)
-> STRep s b -> STRep s b
adjust' f marr# (I# i#, new) next
= [s1#](#local-6989586621679053765) -> case readArray# marr# i# s1# of
(# s2#, old #) ->
let = f old new
in next (writeArray# marr# i# combined s2#)
{-# INLINE (//) #-} (//) :: Ix i => Array i e -> [(i, e)] -> Array i e arr@(Array l u n _) // ies = unsafeReplace arr [(safeIndex (l,u) n i, e) | (i, e) <- ies]
{-# INLINE unsafeReplace #-} unsafeReplace :: Array i e -> [(Int, e)] -> Array i e unsafeReplace arr ies = runST (do STArray l u n marr# <- thawSTArray arr ST (foldr (fill marr#) (done l u n marr#) ies))
{-# INLINE accum #-} accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e accum f arr@(Array l u n _) ies = unsafeAccum f arr [(safeIndex (l,u) n i, e) | (i, e) <- ies]
{-# INLINE unsafeAccum #-} unsafeAccum :: (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e unsafeAccum f arr ies = runST (do STArray l u n marr# <- thawSTArray arr ST (foldr (adjust' f marr#) (done l u n marr#) ies))
{-# INLINE [1] amap #-}
amap :: (a -> b) -> Array i a -> Array i b
amap f arr@(Array l u n@(I# n#) _) = runST (ST $ [s1#](#local-6989586621679053803) ->
case newArray# n# arrEleBottom s1# of
(# s2#, marr# #) ->
let go i s#
| i == n = done l u n marr# s#
| (# e #) <- unsafeAt# arr i
= fill marr# (i, f e) (go (i+1)) s#
in go 0 s2# )
{-# RULES "amap/coerce" amap coerce = coerce -- See Note [amap] #-}
{-# RULES "amap/amap" forall f g a . amap f (amap g a) = amap (f . g) a #-}
{-# INLINE ixmap #-} ixmap :: (Ix i, Ix j) => (i,i) -> (i -> j) -> Array j e -> Array i e ixmap (l,u) f arr = array (l,u) [(i, arr ! f i) | i <- range (l,u)]
{-# INLINE eqArray #-} eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool eqArray arr1@(Array l1 u1 n1 _) arr2@(Array l2 u2 n2 _) = if n1 == 0 then n2 == 0 else l1 == l2 && u1 == u2 && and [unsafeAt arr1 i == unsafeAt arr2 i | i <- [0 .. n1 - 1]]
{-# INLINE [1] cmpArray #-} cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering cmpArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
{-# INLINE cmpIntArray #-}
cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering
cmpIntArray arr1@(Array l1 u1 n1 _) arr2@(Array l2 u2 n2 _) =
if n1 == 0 then
if n2 == 0 then EQ else LT
else if n2 == 0 then GT
else case compare l1 l2 of
EQ -> foldr cmp (compare u1 u2) [0 .. (n1 min
n2) - 1]
other -> other
where
cmp i rest = case compare (unsafeAt arr1 i) (unsafeAt arr2 i) of
EQ -> rest
other -> other
{-# RULES "cmpArray/Int" cmpArray = cmpIntArray #-}
instance Functor (Array i) where fmap = amap
instance (Ix i, Eq e) => Eq (Array i e) where (==) = eqArray
instance (Ix i, Ord e) => Ord (Array i e) where compare = cmpArray
instance (Ix a, Show a, Show b) => Show (Array a b) where showsPrec p a = showParen (p > appPrec) $ showString "array " . showsPrec appPrec1 (bounds a) . showChar ' ' . showsPrec appPrec1 (assocs a)
{-# INLINE newSTArray #-} newSTArray :: Ix i => (i,i) -> e -> ST s (STArray s i e) newSTArray (l,u) initial = ST $ [s1#](#local-6989586621679053842) -> case safeRangeSize (l,u) of { n@(I# n#) -> case newArray# n# initial s1# of { (# s2#, marr# #) -> (# s2#, STArray l u n marr# #) }}
{-# INLINE boundsSTArray #-} boundsSTArray :: STArray s i e -> (i,i) boundsSTArray (STArray l u _ _) = (l,u)
{-# INLINE numElementsSTArray #-} numElementsSTArray :: STArray s i e -> Int numElementsSTArray (STArray _ _ n _) = n
{-# INLINE readSTArray #-} readSTArray :: Ix i => STArray s i e -> i -> ST s e readSTArray marr@(STArray l u n _) i = unsafeReadSTArray marr (safeIndex (l,u) n i)
{-# INLINE unsafeReadSTArray #-} unsafeReadSTArray :: STArray s i e -> Int -> ST s e unsafeReadSTArray (STArray _ _ _ marr#) (I# i#) = ST $ [s1#](#local-6989586621679053857) -> readArray# marr# i# s1#
{-# INLINE writeSTArray #-} writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s () writeSTArray marr@(STArray l u n _) i e = unsafeWriteSTArray marr (safeIndex (l,u) n i) e
{-# INLINE unsafeWriteSTArray #-} unsafeWriteSTArray :: STArray s i e -> Int -> e -> ST s () unsafeWriteSTArray (STArray _ _ _ marr#) (I# i#) e = ST $ [s1#](#local-6989586621679053867) -> case writeArray# marr# i# e s1# of s2# -> (# s2#, () #)
freezeSTArray :: STArray s i e -> ST s (Array i e) freezeSTArray (STArray l u n@(I# n#) marr#) = ST $ [s1#](#local-6989586621679053874) -> case newArray# n# arrEleBottom s1# of { (# s2#, marr'# #) -> let copy i# s3# | isTrue# (i# ==# n#) = s3# | otherwise = case readArray# marr# i# s3# of { (# s4#, e #) -> case writeArray# marr'# i# e s4# of { s5# -> copy (i# +# 1#) s5# }} in case copy 0# s2# of { s3# -> case unsafeFreezeArray# marr'# s3# of { (# s4#, arr# #) -> (# s4#, Array l u n arr# #) }}}
{-# INLINE unsafeFreezeSTArray #-} unsafeFreezeSTArray :: STArray s i e -> ST s (Array i e) unsafeFreezeSTArray (STArray l u n marr#) = ST $ [s1#](#local-6989586621679053890) -> case unsafeFreezeArray# marr# s1# of { (# s2#, arr# #) -> (# s2#, Array l u n arr# #) }
thawSTArray :: Array i e -> ST s (STArray s i e) thawSTArray (Array l u n@(I# n#) arr#) = ST $ [s1#](#local-6989586621679053898) -> case newArray# n# arrEleBottom s1# of { (# s2#, marr# #) -> let copy i# s3# | isTrue# (i# ==# n#) = s3# | otherwise = case indexArray# arr# i# of { (# e #) -> case writeArray# marr# i# e s3# of { s4# -> copy (i# +# 1#) s4# }} in case copy 0# s2# of { s3# -> (# s3#, STArray l u n marr# #) }}
{-# INLINE unsafeThawSTArray #-} unsafeThawSTArray :: Array i e -> ST s (STArray s i e) unsafeThawSTArray (Array l u n arr#) = ST $ [s1#](#local-6989586621679053911) -> case unsafeThawArray# arr# s1# of { (# s2#, marr# #) -> (# s2#, STArray l u n marr# #) }