{-# LANGUAGE Trustworthy, OverloadedLists, ConstraintKinds, TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-}
{-# LANGUAGE TypeFamilies, UndecidableInstances, DefaultSignatures, CPP #-}
module SDP.Index
(
module SDP.Nullable,
module SDP.Shape,
(:|:), SubIndex, takeDim, dropDim, joinDim, splitDim,
Index (..),
InBounds (..), offsetIntegral, defaultBoundsUnsign
)
where
import Prelude ( (++) )
import SDP.SafePrelude
import SDP.Nullable
import SDP.Shape
import Data.Tuple
import Data.Char ( ord )
import GHC.Types
import Foreign.C.Types
import Control.Exception.SDP
default ()
data InBounds = ER
| UR
| IN
| OR
deriving ( InBounds -> InBounds -> Bool
(InBounds -> InBounds -> Bool)
-> (InBounds -> InBounds -> Bool) -> Eq InBounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InBounds -> InBounds -> Bool
$c/= :: InBounds -> InBounds -> Bool
== :: InBounds -> InBounds -> Bool
$c== :: InBounds -> InBounds -> Bool
Eq, Int -> InBounds -> ShowS
[InBounds] -> ShowS
InBounds -> String
(Int -> InBounds -> ShowS)
-> (InBounds -> String) -> ([InBounds] -> ShowS) -> Show InBounds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InBounds] -> ShowS
$cshowList :: [InBounds] -> ShowS
show :: InBounds -> String
$cshow :: InBounds -> String
showsPrec :: Int -> InBounds -> ShowS
$cshowsPrec :: Int -> InBounds -> ShowS
Show, ReadPrec [InBounds]
ReadPrec InBounds
Int -> ReadS InBounds
ReadS [InBounds]
(Int -> ReadS InBounds)
-> ReadS [InBounds]
-> ReadPrec InBounds
-> ReadPrec [InBounds]
-> Read InBounds
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InBounds]
$creadListPrec :: ReadPrec [InBounds]
readPrec :: ReadPrec InBounds
$creadPrec :: ReadPrec InBounds
readList :: ReadS [InBounds]
$creadList :: ReadS [InBounds]
readsPrec :: Int -> ReadS InBounds
$creadsPrec :: Int -> ReadS InBounds
Read, Int -> InBounds
InBounds -> Int
InBounds -> [InBounds]
InBounds -> InBounds
InBounds -> InBounds -> [InBounds]
InBounds -> InBounds -> InBounds -> [InBounds]
(InBounds -> InBounds)
-> (InBounds -> InBounds)
-> (Int -> InBounds)
-> (InBounds -> Int)
-> (InBounds -> [InBounds])
-> (InBounds -> InBounds -> [InBounds])
-> (InBounds -> InBounds -> [InBounds])
-> (InBounds -> InBounds -> InBounds -> [InBounds])
-> Enum InBounds
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: InBounds -> InBounds -> InBounds -> [InBounds]
$cenumFromThenTo :: InBounds -> InBounds -> InBounds -> [InBounds]
enumFromTo :: InBounds -> InBounds -> [InBounds]
$cenumFromTo :: InBounds -> InBounds -> [InBounds]
enumFromThen :: InBounds -> InBounds -> [InBounds]
$cenumFromThen :: InBounds -> InBounds -> [InBounds]
enumFrom :: InBounds -> [InBounds]
$cenumFrom :: InBounds -> [InBounds]
fromEnum :: InBounds -> Int
$cfromEnum :: InBounds -> Int
toEnum :: Int -> InBounds
$ctoEnum :: Int -> InBounds
pred :: InBounds -> InBounds
$cpred :: InBounds -> InBounds
succ :: InBounds -> InBounds
$csucc :: InBounds -> InBounds
Enum )
type family i :|: j
where
i :|: E = i
i :|: j = DimInit i :|: DimInit j
type SubIndex = Sub
class (Index i, Index j, Index (i :|: j)) => Sub i j
where
dropDim :: i -> j -> i :|: j
joinDim :: j -> i :|: j -> i
takeDim :: i -> j
instance {-# OVERLAPS #-} (Index i, E ~~ (i :|: i)) => Sub i i
where
dropDim :: i -> i -> i :|: i
dropDim = \ i
_ i
_ -> E
i :|: i
E
joinDim :: i -> (i :|: i) -> i
joinDim = i -> (i :|: i) -> i
forall a b. a -> b -> a
const
takeDim :: i -> i
takeDim = i -> i
forall a. a -> a
id
instance
(
ij ~~ (i :|: j), DimInit ij ~~ (DimInit i :|: j), DimLast ij ~~ DimLast i,
Index i, Index j, Index ij, Sub (DimInit i) j
) => Sub i j
where
dropDim :: i -> j -> i :|: j
dropDim i
i' j
j' = let (DimInit i
is, DimLast i
i) = i -> (DimInit i, DimLast i)
forall i. Shape i => i -> (DimInit i, DimLast i)
unconsDim i
i' in DimInit ij -> DimLast ij -> ij
forall i. Shape i => DimInit i -> DimLast i -> i
consDim (DimInit i -> j -> DimInit i :|: j
forall i j. Sub i j => i -> j -> i :|: j
dropDim DimInit i
is j
j') DimLast ij
DimLast i
i
joinDim :: j -> (i :|: j) -> i
joinDim j
j' i :|: j
ij = let (DimInit i :|: j
is, DimLast i
i) = ij -> (DimInit ij, DimLast ij)
forall i. Shape i => i -> (DimInit i, DimLast i)
unconsDim ij
i :|: j
ij in DimInit i -> DimLast i -> i
forall i. Shape i => DimInit i -> DimLast i -> i
consDim (j -> (DimInit i :|: j) -> DimInit i
forall i j. Sub i j => j -> (i :|: j) -> i
joinDim j
j' DimInit i :|: j
is) DimLast i
i
takeDim :: i -> j
takeDim = DimInit i -> j
forall i j. Sub i j => i -> j
takeDim (DimInit i -> j) -> (i -> DimInit i) -> i -> j
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> DimInit i
forall i. Shape i => i -> DimInit i
initDim
splitDim :: (SubIndex i j) => i -> (i :|: j, j)
splitDim :: i -> (i :|: j, j)
splitDim i
i = let j :: j
j = i -> j
forall i j. Sub i j => i -> j
takeDim i
i in (i -> j -> i :|: j
forall i j. Sub i j => i -> j -> i :|: j
dropDim i
i j
j, j
j)
class (Ord i, Shape i, Shape (DimLast i), Shape (DimInit i), Shape (GIndex i)) => Index i
where
{-# INLINE size #-}
size :: (i, i) -> Int
default size :: (Enum i) => (i, i) -> Int
size bnds :: (i, i)
bnds@(i
l, i
u) = (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i, i)
bnds Bool -> Int -> Int -> Int
forall a. Bool -> a -> a -> a
? Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ i
u i -> i -> Int
forall i. Enum i => i -> i -> Int
-. i
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
{-# INLINE sizes #-}
sizes :: (i, i) -> [Int]
default sizes :: (Index (GIndex i)) => (i, i) -> [Int]
sizes = (GIndex i, GIndex i) -> [Int]
forall i. Index i => (i, i) -> [Int]
sizes ((GIndex i, GIndex i) -> [Int])
-> ((i, i) -> (GIndex i, GIndex i)) -> (i, i) -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> (GIndex i, GIndex i)
forall i. Shape i => (i, i) -> (GIndex i, GIndex i)
toGBounds
{-# INLINE safeElem #-}
safeElem :: (i, i) -> i -> i
safeElem (i
l, i
u) = i -> i -> i
forall a. Ord a => a -> a -> a
min i
u (i -> i) -> (i -> i) -> i -> i
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> i -> i
forall a. Ord a => a -> a -> a
max i
l
{-# INLINE ordBounds #-}
ordBounds :: (i, i) -> (i, i)
ordBounds = \ (i, i)
bs -> (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i, i)
bs Bool -> (i, i) -> (i, i) -> (i, i)
forall a. Bool -> a -> a -> a
? (i, i) -> (i, i)
forall a b. (a, b) -> (b, a)
swap (i, i)
bs ((i, i) -> (i, i)) -> (i, i) -> (i, i)
forall a b. (a -> b) -> a -> b
$ (i, i)
bs
defLimit :: i -> Integer
default defLimit :: (Integral i, Bounded i) => i -> Integer
defLimit i
i = i -> Integer
forall a. Integral a => a -> Integer
toInteger (i
forall a. Bounded a => a
maxBound i -> i -> i
forall a. a -> a -> a
`asTypeOf` i
i) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
{-# INLINE defaultBounds #-}
defaultBounds :: Int -> (i, i)
defaultBounds Int
n = (Int -> i
forall i. Index i => Int -> i
unsafeIndex Int
0, Int -> i
forall i. Index i => Int -> i
unsafeIndex (Int -> i) -> Int -> i
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE unsafeIndex #-}
unsafeIndex :: Int -> i
default unsafeIndex :: (Enum i) => Int -> i
unsafeIndex = Int -> i
forall a. Enum a => Int -> a
toEnum
{-# INLINE isEmpty #-}
isEmpty :: (i, i) -> Bool
isEmpty = (i -> i -> Bool) -> (i, i) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry i -> i -> Bool
forall a. Ord a => a -> a -> Bool
(>)
inBounds :: (i, i) -> i -> InBounds
inBounds (i
l, i
u) i
i | i
l i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u = InBounds
ER | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u = InBounds
OR | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
< i
l = InBounds
UR | Bool
True = InBounds
IN
{-# INLINE isOverflow #-}
isOverflow :: (i, i) -> i -> Bool
isOverflow (i
l, i
u) i
i = i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u Bool -> Bool -> Bool
|| i
l i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u
{-# INLINE isUnderflow #-}
isUnderflow :: (i, i) -> i -> Bool
isUnderflow (i
l, i
u) i
i = i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
< i
l Bool -> Bool -> Bool
|| i
l i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u
{-# INLINE inRange #-}
inRange :: (i, i) -> i -> Bool
inRange (i
l, i
u) i
i = i
l i -> i -> Bool
forall a. Ord a => a -> a -> Bool
<= i
i Bool -> Bool -> Bool
&& i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
<= i
u
prev :: (i, i) -> i -> i
default prev :: (Enum i) => (i, i) -> i -> i
prev (i
l, i
u) i
i | (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i
l, i
u) = i
forall a. a
e | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
<= i
l = i
l | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
u = i
u | Bool
True = i -> i
forall a. Enum a => a -> a
pred i
i
where
e :: a
e = String -> a
forall a. String -> a
emptyEx String
"prev {default}"
default next :: (Enum i) => (i, i) -> i -> i
next :: (i, i) -> i -> i
next (i
l, i
u) i
i | (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i
l, i
u) = i
forall a. a
e | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
>= i
u = i
u | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
< i
l = i
l | Bool
True = i -> i
forall a. Enum a => a -> a
succ i
i
where
e :: a
e = String -> a
forall a. String -> a
emptyEx String
"next {default}"
{-# INLINE offset #-}
offset :: (i, i) -> i -> Int
default offset :: (Enum i) => (i, i) -> i -> Int
offset bnds :: (i, i)
bnds@(i
l, i
_) i
i = (i, i) -> i -> Int -> String -> Int
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (i, i)
bnds i
i (i
i i -> i -> Int
forall i. Enum i => i -> i -> Int
-. i
l) String
"offset {default}"
{-# INLINE index #-}
index :: (i, i) -> Int -> i
default index :: (Enum i) => (i, i) -> Int -> i
index bnds :: (i, i)
bnds@(i
l, i
_) Int
n =
let res :: i
res = Int -> i
forall a. Enum a => Int -> a
toEnum (Int -> i) -> Int -> i
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ i -> Int
forall a. Enum a => a -> Int
fromEnum i
l
in (Int, Int) -> Int -> i -> String -> i
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (Int
0, (i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i, i)
bnds Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
n i
res String
"index {default}"
{-# INLINE range #-}
range :: (i, i) -> [i]
default range :: (Enum i) => (i, i) -> [i]
range = (i -> i -> [i]) -> (i, i) -> [i]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry i -> i -> [i]
forall a. Enum a => a -> a -> [a]
enumFromTo
subshape :: (Sub i j, Index (i :|: j)) => (i, i) -> i :|: j -> (j, j)
subshape (i
l, i
u) i :|: j
ij = (i :|: j, i :|: j) -> (i :|: j) -> (j, j) -> String -> (j, j)
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (i :|: j
l', i :|: j
u') i :|: j
ij (j
lj, j
uj) String
"subshape {default}"
where
(i :|: j
l', j
lj) = i -> (i :|: j, j)
forall i j. SubIndex i j => i -> (i :|: j, j)
splitDim i
l
(i :|: j
u', j
uj) = i -> (i :|: j, j)
forall i j. SubIndex i j => i -> (i :|: j, j)
splitDim i
u
slice :: (Sub i j, ij ~ (i :|: j), Index j) => (i, i) -> ij -> ((ij, ij), (j, j))
slice (i
l, i
u) ij
ij = (ij, ij)
-> ij -> ((ij, ij), (j, j)) -> String -> ((ij, ij), (j, j))
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (ij
ls, ij
us) ij
ij ((ij
ls, ij
us), (j
lj, j
uj)) String
"slice {default}"
where
(ij
ls, j
lj) = i -> (i :|: j, j)
forall i j. SubIndex i j => i -> (i :|: j, j)
splitDim i
l
(ij
us, j
uj) = i -> (i :|: j, j)
forall i j. SubIndex i j => i -> (i :|: j, j)
splitDim i
u
instance (Index i) => Estimate (i, i)
where
<==> :: Compare (i, i)
(<==>) = (Int -> Int -> Ordering) -> ((i, i) -> Int) -> Compare (i, i)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Ordering
forall o. Ord o => Compare o
(<=>) (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.<=. :: (i, i) -> (i, i) -> Bool
(.<=.) = (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> (i, i) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(<=) (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.>=. :: (i, i) -> (i, i) -> Bool
(.>=.) = (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> (i, i) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.>. :: (i, i) -> (i, i) -> Bool
(.>.) = (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> (i, i) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>) (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.<. :: (i, i) -> (i, i) -> Bool
(.<.) = (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> (i, i) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(<) (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
<.=> :: (i, i) -> Int -> Ordering
(<.=>) = Int -> Int -> Ordering
forall o. Ord o => Compare o
(<=>) (Int -> Int -> Ordering)
-> ((i, i) -> Int) -> (i, i) -> Int -> Ordering
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.> :: (i, i) -> Int -> Bool
(.>) = Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>) (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.< :: (i, i) -> Int -> Bool
(.<) = Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(<) (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.>= :: (i, i) -> Int -> Bool
(.>=) = Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
.<= :: (i, i) -> Int -> Bool
(.<=) = Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(<=) (Int -> Int -> Bool) -> ((i, i) -> Int) -> (i, i) -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i, i) -> Int
forall i. Index i => (i, i) -> Int
size
instance (Index i) => Nullable (i, i)
where
isNull :: (i, i) -> Bool
isNull = (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty
lzero :: (i, i)
lzero = Int -> (i, i)
forall i. Index i => Int -> (i, i)
defaultBounds Int
0
instance Index E
where
unsafeIndex :: Int -> E
unsafeIndex = E -> Int -> E
forall a b. a -> b -> a
const (String -> E
forall a. String -> a
emptyEx String
"unsafeIndex {E}")
defLimit :: E -> Integer
defLimit = Integer -> E -> Integer
forall a b. a -> b -> a
const (-Integer
1)
size :: (E, E) -> Int
size = Int -> (E, E) -> Int
forall a b. a -> b -> a
const Int
0
sizes :: (E, E) -> [Int]
sizes = [Int] -> (E, E) -> [Int]
forall a b. a -> b -> a
const []
range :: (E, E) -> [E]
range = [E] -> (E, E) -> [E]
forall a b. a -> b -> a
const []
next :: (E, E) -> E -> E
next (E, E)
_ E
_ = E
E
prev :: (E, E) -> E -> E
prev (E, E)
_ E
_ = E
E
offset :: (E, E) -> E -> Int
offset (E, E)
_ E
_ = String -> Int
forall a. String -> a
emptyEx String
"offset {E}"
index :: (E, E) -> Int -> E
index (E, E)
_ Int
_ = String -> E
forall a. String -> a
emptyEx String
"index {E}"
inBounds :: (E, E) -> E -> InBounds
inBounds (E, E)
_ E
_ = InBounds
ER
inRange :: (E, E) -> E -> Bool
inRange (E, E)
_ E
_ = Bool
False
isEmpty :: (E, E) -> Bool
isEmpty (E, E)
_ = Bool
True
isOverflow :: (E, E) -> E -> Bool
isOverflow (E, E)
_ E
_ = Bool
True
isUnderflow :: (E, E) -> E -> Bool
isUnderflow (E, E)
_ E
_ = Bool
True
instance Index ()
where
size :: ((), ()) -> Int
size = Int -> ((), ()) -> Int
forall a b. a -> b -> a
const Int
1
sizes :: ((), ()) -> [Int]
sizes = [Int] -> ((), ()) -> [Int]
forall a b. a -> b -> a
const [Item [Int]
1]
range :: ((), ()) -> [()]
range = [()] -> ((), ()) -> [()]
forall a b. a -> b -> a
const [()]
defLimit :: () -> Integer
defLimit = Integer -> () -> Integer
forall a b. a -> b -> a
const Integer
0
next :: ((), ()) -> () -> ()
next ((), ())
_ ()
_ = ()
prev :: ((), ()) -> () -> ()
prev ((), ())
_ ()
_ = ()
inBounds :: ((), ()) -> () -> InBounds
inBounds ((), ())
_ ()
_ = InBounds
IN
isEmpty :: ((), ()) -> Bool
isEmpty ((), ())
_ = Bool
False
inRange :: ((), ()) -> () -> Bool
inRange ((), ())
_ ()
_ = Bool
True
isOverflow :: ((), ()) -> () -> Bool
isOverflow ((), ())
_ ()
_ = Bool
False
isUnderflow :: ((), ()) -> () -> Bool
isUnderflow ((), ())
_ ()
_ = Bool
False
defaultBounds :: Int -> ((), ())
defaultBounds = ((), ()) -> Int -> ((), ())
forall a b. a -> b -> a
const ((), ())
index :: ((), ()) -> Int -> ()
index = (Int -> ()) -> ((), ()) -> Int -> ()
forall a b. a -> b -> a
const Int -> ()
forall i. Index i => Int -> i
unsafeIndex
offset :: ((), ()) -> () -> Int
offset ((), ())
_ ()
_ = Int
0
unsafeIndex :: Int -> ()
unsafeIndex Int
0 = ()
unsafeIndex Int
_ = String -> ()
forall a. String -> a
emptyEx String
"unsafeIndex ()"
instance Index Char
where
defaultBounds :: Int -> (Char, Char)
defaultBounds = Int -> (Char, Char)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
defLimit :: Char -> Integer
defLimit = Integer -> Char -> Integer
forall a b. a -> b -> a
const (Integer -> Char -> Integer) -> Integer -> Char -> Integer
forall a b. (a -> b) -> a -> b
$ Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Char -> Int
ord Char
forall a. Bounded a => a
maxBound)
instance Index Integer
where
defLimit :: Integer -> Integer
defLimit = String -> Integer -> Integer
forall a. HasCallStack => String -> a
error String
"in SDP.Index.defLimit: Integer has no upper bound"
offset :: (Integer, Integer) -> Integer -> Int
offset = (Integer, Integer) -> Integer -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Int where offset :: (Int, Int) -> Int -> Int
offset = (Int, Int) -> Int -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Int8 where offset :: (Int8, Int8) -> Int8 -> Int
offset = (Int8, Int8) -> Int8 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Int16 where offset :: (Int16, Int16) -> Int16 -> Int
offset = (Int16, Int16) -> Int16 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Int32 where offset :: (Int32, Int32) -> Int32 -> Int
offset = (Int32, Int32) -> Int32 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Int64 where offset :: (Int64, Int64) -> Int64 -> Int
offset = (Int64, Int64) -> Int64 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index Word where offset :: (Word, Word) -> Word -> Int
offset = (Word, Word) -> Word -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (Word, Word)
defaultBounds = Int -> (Word, Word)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index Word8 where offset :: (Word8, Word8) -> Word8 -> Int
offset = (Word8, Word8) -> Word8 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (Word8, Word8)
defaultBounds = Int -> (Word8, Word8)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index Word16 where offset :: (Word16, Word16) -> Word16 -> Int
offset = (Word16, Word16) -> Word16 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (Word16, Word16)
defaultBounds = Int -> (Word16, Word16)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index Word32 where offset :: (Word32, Word32) -> Word32 -> Int
offset = (Word32, Word32) -> Word32 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (Word32, Word32)
defaultBounds = Int -> (Word32, Word32)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index Word64 where offset :: (Word64, Word64) -> Word64 -> Int
offset = (Word64, Word64) -> Word64 -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (Word64, Word64)
defaultBounds = Int -> (Word64, Word64)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CChar where offset :: (CChar, CChar) -> CChar -> Int
offset = (CChar, CChar) -> CChar -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CSChar where offset :: (CSChar, CSChar) -> CSChar -> Int
offset = (CSChar, CSChar) -> CSChar -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CWchar where offset :: (CWchar, CWchar) -> CWchar -> Int
offset = (CWchar, CWchar) -> CWchar -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CShort where offset :: (CShort, CShort) -> CShort -> Int
offset = (CShort, CShort) -> CShort -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CInt where offset :: (CInt, CInt) -> CInt -> Int
offset = (CInt, CInt) -> CInt -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CLong where offset :: (CLong, CLong) -> CLong -> Int
offset = (CLong, CLong) -> CLong -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CLLong where offset :: (CLLong, CLLong) -> CLLong -> Int
offset = (CLLong, CLLong) -> CLLong -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CIntPtr where offset :: (CIntPtr, CIntPtr) -> CIntPtr -> Int
offset = (CIntPtr, CIntPtr) -> CIntPtr -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CIntMax where offset :: (CIntMax, CIntMax) -> CIntMax -> Int
offset = (CIntMax, CIntMax) -> CIntMax -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CPtrdiff where offset :: (CPtrdiff, CPtrdiff) -> CPtrdiff -> Int
offset = (CPtrdiff, CPtrdiff) -> CPtrdiff -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CSigAtomic where offset :: (CSigAtomic, CSigAtomic) -> CSigAtomic -> Int
offset = (CSigAtomic, CSigAtomic) -> CSigAtomic -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral
instance Index CSize where offset :: (CSize, CSize) -> CSize -> Int
offset = (CSize, CSize) -> CSize -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CSize, CSize)
defaultBounds = Int -> (CSize, CSize)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CBool where offset :: (CBool, CBool) -> CBool -> Int
offset = (CBool, CBool) -> CBool -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CBool, CBool)
defaultBounds = Int -> (CBool, CBool)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CUChar where offset :: (CUChar, CUChar) -> CUChar -> Int
offset = (CUChar, CUChar) -> CUChar -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CUChar, CUChar)
defaultBounds = Int -> (CUChar, CUChar)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CUShort where offset :: (CUShort, CUShort) -> CUShort -> Int
offset = (CUShort, CUShort) -> CUShort -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CUShort, CUShort)
defaultBounds = Int -> (CUShort, CUShort)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CUInt where offset :: (CUInt, CUInt) -> CUInt -> Int
offset = (CUInt, CUInt) -> CUInt -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CUInt, CUInt)
defaultBounds = Int -> (CUInt, CUInt)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CULong where offset :: (CULong, CULong) -> CULong -> Int
offset = (CULong, CULong) -> CULong -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CULong, CULong)
defaultBounds = Int -> (CULong, CULong)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CULLong where offset :: (CULLong, CULLong) -> CULLong -> Int
offset = (CULLong, CULLong) -> CULLong -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CULLong, CULLong)
defaultBounds = Int -> (CULLong, CULLong)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CUIntPtr where offset :: (CUIntPtr, CUIntPtr) -> CUIntPtr -> Int
offset = (CUIntPtr, CUIntPtr) -> CUIntPtr -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CUIntPtr, CUIntPtr)
defaultBounds = Int -> (CUIntPtr, CUIntPtr)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance Index CUIntMax where offset :: (CUIntMax, CUIntMax) -> CUIntMax -> Int
offset = (CUIntMax, CUIntMax) -> CUIntMax -> Int
forall i. (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral; defaultBounds :: Int -> (CUIntMax, CUIntMax)
defaultBounds = Int -> (CUIntMax, CUIntMax)
forall i. (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign
instance (Index i) => Index (E :& i)
where
defLimit :: (E :& i) -> Integer
defLimit = (Integer -> (E :& i) -> Integer
forall a b. a -> b -> a
const (Integer -> (E :& i) -> Integer)
-> (i -> Integer) -> i -> (E :& i) -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Integer
forall i. Index i => i -> Integer
defLimit :: (Index i) => i -> (E :& i) -> Integer) i
forall a. HasCallStack => a
undefined
size :: (E :& i, E :& i) -> Int
size = \ ([Item (E :& i)
l], [Item (E :& i)
u]) -> (i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i
Item (E :& i)
l, i
Item (E :& i)
u)
sizes :: (E :& i, E :& i) -> [Int]
sizes = \ ([Item (E :& i)
l], [Item (E :& i)
u]) -> [(i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i
Item (E :& i)
l, i
Item (E :& i)
u)]
range :: (E :& i, E :& i) -> [E :& i]
range = \ ([Item (E :& i)
l], [Item (E :& i)
u]) -> [ [i
Item (E :& i)
i] | i
i <- (i, i) -> [i]
forall i. Index i => (i, i) -> [i]
range (i
Item (E :& i)
l, i
Item (E :& i)
u) ]
next :: (E :& i, E :& i) -> (E :& i) -> E :& i
next = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> [(i, i) -> i -> i
forall i. Index i => (i, i) -> i -> i
next (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i]
prev :: (E :& i, E :& i) -> (E :& i) -> E :& i
prev = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> [(i, i) -> i -> i
forall i. Index i => (i, i) -> i -> i
prev (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i]
inRange :: (E :& i, E :& i) -> (E :& i) -> Bool
inRange = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
inRange (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i
isOverflow :: (E :& i, E :& i) -> (E :& i) -> Bool
isOverflow = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
isOverflow (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i
isUnderflow :: (E :& i, E :& i) -> (E :& i) -> Bool
isUnderflow = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
isUnderflow (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i
safeElem :: (E :& i, E :& i) -> (E :& i) -> E :& i
safeElem = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> [(i, i) -> i -> i
forall i. Index i => (i, i) -> i -> i
safeElem (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i]
isEmpty :: (E :& i, E :& i) -> Bool
isEmpty = \ ([Item (E :& i)
l], [Item (E :& i)
u]) -> (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i
Item (E :& i)
l, i
Item (E :& i)
u)
ordBounds :: (E :& i, E :& i) -> (E :& i, E :& i)
ordBounds = \ ([Item (E :& i)
l], [Item (E :& i)
u]) -> let (i
l', i
u') = (i, i) -> (i, i)
forall i. Index i => (i, i) -> (i, i)
ordBounds (i
Item (E :& i)
l, i
Item (E :& i)
u) in ([i
Item (E :& i)
l'], [i
Item (E :& i)
u'])
offset :: (E :& i, E :& i) -> (E :& i) -> Int
offset = \ ([Item (E :& i)
l], [Item (E :& i)
u]) [Item (E :& i)
i] -> (i, i) -> i -> Int
forall i. Index i => (i, i) -> i -> Int
offset (i
Item (E :& i)
l, i
Item (E :& i)
u) i
Item (E :& i)
i
index :: (E :& i, E :& i) -> Int -> E :& i
index = \ ([Item (E :& i)
l], [Item (E :& i)
u]) Int
n -> [(i, i) -> Int -> i
forall i. Index i => (i, i) -> Int -> i
index (i
Item (E :& i)
l, i
Item (E :& i)
u) Int
n]
defaultBounds :: Int -> (E :& i, E :& i)
defaultBounds = (i -> E :& i) -> (i, i) -> (E :& i, E :& i)
forall a b. (a -> b) -> (a, a) -> (b, b)
both (E
E E -> i -> E :& i
forall tail head. tail -> head -> tail :& head
:&) ((i, i) -> (E :& i, E :& i))
-> (Int -> (i, i)) -> Int -> (E :& i, E :& i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (i, i)
forall i. Index i => Int -> (i, i)
defaultBounds
unsafeIndex :: Int -> E :& i
unsafeIndex = \ Int
n -> [Int -> i
forall i. Index i => Int -> i
unsafeIndex Int
n]
instance (Index i, Enum i, Bounded i, Index (i' :& i)) => Index (i' :& i :& i)
where
defLimit :: ((i' :& i) :& i) -> Integer
defLimit (i' :& i) :& i
i = i -> Int -> ((i' :& i) :& i) -> Integer
forall i i'. Index i => i -> Int -> (i' :& i) -> Integer
lim (String -> i
forall a. HasCallStack => String -> a
error String
"in defLimit {i' :& i :& i}") (((i' :& i) :& i) -> Int
forall i. Shape i => i -> Int
rank (i' :& i) :& i
i) (i' :& i) :& i
i
where
lim :: (Index i) => i -> Int -> (i' :& i) -> Integer
lim :: i -> Int -> (i' :& i) -> Integer
lim = Integer -> (i' :& i) -> Integer
forall a b. a -> b -> a
const (Integer -> (i' :& i) -> Integer)
-> (i -> Int -> Integer) -> i -> Int -> (i' :& i) -> Integer
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
(^) (Integer -> Int -> Integer)
-> (i -> Integer) -> i -> Int -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Integer
forall i. Index i => i -> Integer
defLimit
size :: ((i' :& i) :& i, (i' :& i) :& i) -> Int
size (i' :& i
ls :& i
l, i' :& i
us :& i
u) = (i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i
l, i
u) Int -> Int -> Int
forall a. Num a => a -> a -> a
* (i' :& i, i' :& i) -> Int
forall i. Index i => (i, i) -> Int
size (i' :& i
ls, i' :& i
us)
sizes :: ((i' :& i) :& i, (i' :& i) :& i) -> [Int]
sizes (i' :& i
ls :& i
l, i' :& i
us :& i
u) = (i' :& i, i' :& i) -> [Int]
forall i. Index i => (i, i) -> [Int]
sizes (i' :& i
ls, i' :& i
us) [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ (i, i) -> [Int]
forall i. Index i => (i, i) -> [Int]
sizes (i
l, i
u)
range :: ((i' :& i) :& i, (i' :& i) :& i) -> [(i' :& i) :& i]
range (i' :& i
ls :& i
l, i' :& i
us :& i
u) = ((i' :& i) -> i -> (i' :& i) :& i)
-> [i' :& i] -> [i] -> [(i' :& i) :& i]
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
(:&) ((i' :& i, i' :& i) -> [i' :& i]
forall i. Index i => (i, i) -> [i]
range (i' :& i
ls, i' :& i
us)) ((i, i) -> [i]
forall i. Index i => (i, i) -> [i]
range (i
l, i
u))
prev :: ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> (i' :& i) :& i
prev bs :: ((i' :& i) :& i, (i' :& i) :& i)
bs@(i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i) :& i
ix
| ((i' :& i) :& i, (i' :& i) :& i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty ((i' :& i) :& i, (i' :& i) :& i)
bs = String -> (i' :& i) :& i
forall a. String -> a
emptyEx String
"prev {i' :& i :& i}"
| i
i i -> i -> Bool
forall a. Eq a => a -> a -> Bool
/= i
l = i' :& i
is (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i -> i
forall a. Enum a => a -> a
pred i
i
| i' :& i
is (i' :& i) -> (i' :& i) -> Bool
forall a. Eq a => a -> a -> Bool
/= i' :& i
ls = (i' :& i, i' :& i) -> (i' :& i) -> i' :& i
forall i. Index i => (i, i) -> i -> i
prev (i' :& i
ls, i' :& i
us) i' :& i
is (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
u
| Bool
True = i' :& i
ls (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
l
where
(i' :& i
is :& i
i) = ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> (i' :& i) :& i
forall i. Index i => (i, i) -> i -> i
safeElem ((i' :& i) :& i, (i' :& i) :& i)
bs (i' :& i) :& i
ix
next :: ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> (i' :& i) :& i
next bs :: ((i' :& i) :& i, (i' :& i) :& i)
bs@(i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i) :& i
ix
| ((i' :& i) :& i, (i' :& i) :& i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty ((i' :& i) :& i, (i' :& i) :& i)
bs = String -> (i' :& i) :& i
forall a. String -> a
emptyEx String
"next {i' :& i :& i}"
| i
i i -> i -> Bool
forall a. Eq a => a -> a -> Bool
/= i
u = i' :& i
is (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i -> i
forall a. Enum a => a -> a
succ i
i
| i' :& i
is (i' :& i) -> (i' :& i) -> Bool
forall a. Eq a => a -> a -> Bool
/= i' :& i
us = (i' :& i, i' :& i) -> (i' :& i) -> i' :& i
forall i. Index i => (i, i) -> i -> i
prev (i' :& i
ls, i' :& i
us) i' :& i
is (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
u
| Bool
True = i' :& i
ls (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
l
where
(i' :& i
is :& i
i) = ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> (i' :& i) :& i
forall i. Index i => (i, i) -> i -> i
safeElem ((i' :& i) :& i, (i' :& i) :& i)
bs (i' :& i) :& i
ix
inBounds :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> InBounds
inBounds ((i' :& i) :& i, (i' :& i) :& i)
bs (i' :& i) :& i
i
| ((i' :& i) :& i, (i' :& i) :& i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty ((i' :& i) :& i, (i' :& i) :& i)
bs = InBounds
ER
| ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool
forall i. Index i => (i, i) -> i -> Bool
isUnderflow ((i' :& i) :& i, (i' :& i) :& i)
bs (i' :& i) :& i
i = InBounds
UR
| ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool
forall i. Index i => (i, i) -> i -> Bool
isOverflow ((i' :& i) :& i, (i' :& i) :& i)
bs (i' :& i) :& i
i = InBounds
OR
| Bool
True = InBounds
IN
inRange :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool
inRange (i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i
is :& i
i) = (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
inRange (i
l, i
u) i
i Bool -> Bool -> Bool
&& (i' :& i, i' :& i) -> (i' :& i) -> Bool
forall i. Index i => (i, i) -> i -> Bool
inRange (i' :& i
ls, i' :& i
us) i' :& i
is
isOverflow :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool
isOverflow (i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i
is :& i
i) = (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
isOverflow (i
l, i
u) i
i Bool -> Bool -> Bool
|| (i' :& i, i' :& i) -> (i' :& i) -> Bool
forall i. Index i => (i, i) -> i -> Bool
isOverflow (i' :& i
ls, i' :& i
us) i' :& i
is
isUnderflow :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool
isUnderflow (i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i
is :& i
i) = (i, i) -> i -> Bool
forall i. Index i => (i, i) -> i -> Bool
isUnderflow (i
l, i
u) i
i Bool -> Bool -> Bool
|| (i' :& i, i' :& i) -> (i' :& i) -> Bool
forall i. Index i => (i, i) -> i -> Bool
isUnderflow (i' :& i
ls, i' :& i
us) i' :& i
is
safeElem :: ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> (i' :& i) :& i
safeElem (i' :& i
ls :& i
l, i' :& i
us :& i
u) (i' :& i
is :& i
i) = (i' :& i, i' :& i) -> (i' :& i) -> i' :& i
forall i. Index i => (i, i) -> i -> i
safeElem (i' :& i
ls, i' :& i
us) i' :& i
is (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& (i, i) -> i -> i
forall i. Index i => (i, i) -> i -> i
safeElem (i
l, i
u) i
i
isEmpty :: ((i' :& i) :& i, (i' :& i) :& i) -> Bool
isEmpty (i' :& i
ls :& i
l, i' :& i
us :& i
u) = (i, i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i
l, i
u) Bool -> Bool -> Bool
|| (i' :& i, i' :& i) -> Bool
forall i. Index i => (i, i) -> Bool
isEmpty (i' :& i
ls, i' :& i
us)
ordBounds :: ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i, (i' :& i) :& i)
ordBounds (i' :& i
ls :& i
l, i' :& i
us :& i
u) = (i' :& i
ls' (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
l', i' :& i
us' (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
u')
where
(i' :& i
ls', i' :& i
us') = (i' :& i, i' :& i) -> (i' :& i, i' :& i)
forall i. Index i => (i, i) -> (i, i)
ordBounds (i' :& i
ls, i' :& i
us)
(i
l', i
u') = (i, i) -> (i, i)
forall i. Index i => (i, i) -> (i, i)
ordBounds (i
l, i
u)
index :: ((i' :& i) :& i, (i' :& i) :& i) -> Int -> (i' :& i) :& i
index bnds :: ((i' :& i) :& i, (i' :& i) :& i)
bnds@(i' :& i
ls :& i
l, i' :& i
us :& i
u) Int
c = (Int, Int) -> Int -> ((i' :& i) :& i) -> String -> (i' :& i) :& i
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (Int
0, ((i' :& i) :& i, (i' :& i) :& i) -> Int
forall i. Index i => (i, i) -> Int
size ((i' :& i) :& i, (i' :& i) :& i)
bnds Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
c (i' :& i) :& i
res String
err
where
(Int
cs, Int
i) = Int
c Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` (i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i
l, i
u)
res :: (i' :& i) :& i
res = (i' :& i, i' :& i) -> Int -> i' :& i
forall i. Index i => (i, i) -> Int -> i
index (i' :& i
ls, i' :& i
us) Int
cs (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& Int -> i
forall i. Index i => Int -> i
unsafeIndex Int
i
err :: String
err = String
"index {i' :& i :& i}"
offset :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Int
offset ((i' :& i) :& i, (i' :& i) :& i)
bnds ix :: (i' :& i) :& i
ix@(i' :& i
is :& i
i) = ((i' :& i) :& i, (i' :& i) :& i)
-> ((i' :& i) :& i) -> Int -> String -> Int
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds ((i' :& i) :& i, (i' :& i) :& i)
bnds (i' :& i) :& i
ix Int
res String
"offset {i' :& i :& i}"
where
res :: Int
res = (i' :& i, i' :& i) -> (i' :& i) -> Int
forall i. Index i => (i, i) -> i -> Int
offset (i' :& i
ls, i' :& i
us) i' :& i
is Int -> Int -> Int
forall a. Num a => a -> a -> a
* (i, i) -> Int
forall i. Index i => (i, i) -> Int
size (i
l, i
u) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (i, i) -> i -> Int
forall i. Index i => (i, i) -> i -> Int
offset (i
l, i
u) i
i
(i' :& i
ls :& i
l, i' :& i
us :& i
u) = ((i' :& i) :& i, (i' :& i) :& i)
bnds
unsafeIndex :: Int -> (i' :& i) :& i
unsafeIndex Int
c = Int -> i' :& i
forall i. Index i => Int -> i
unsafeIndex Int
d (i' :& i) -> i -> (i' :& i) :& i
forall tail head. tail -> head -> tail :& head
:& i
i
where
(Int
d, Int
m) = Int -> Integer
forall i. Index i => i -> Integer
defLimit Int
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
lim Bool -> (Int, Int) -> (Int, Int) -> (Int, Int)
forall a. Bool -> a -> a -> a
? (Int
0, Int
c) ((Int, Int) -> (Int, Int)) -> (Int, Int) -> (Int, Int)
forall a b. (a -> b) -> a -> b
$ Int
c Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
lim
i :: i
i = Int -> i
forall i. Index i => Int -> i
unsafeIndex Int
m
lim :: Integer
lim = i -> Integer
forall i. Index i => i -> Integer
defLimit i
i
#define INDEX_INSTANCE(Type) instance (Ord i, Index i, Enum i, Bounded i) => Index (Type i) where\
{\
size = size . toGBounds;\
sizes = sizes . toGBounds;\
isEmpty = isEmpty . toGBounds;\
defLimit = defLimit . toGIndex;\
unsafeIndex = fromGIndex . unsafeIndex;\
index = fromGIndex ... index . toGBounds;\
range = fmap fromGIndex . range . toGBounds;\
ordBounds = fromGBounds . ordBounds . toGBounds;\
offset = \ bs -> offset (toGBounds bs) . toGIndex;\
inRange = \ bs -> inRange (toGBounds bs) . toGIndex;\
isOverflow = \ bs -> isOverflow (toGBounds bs) . toGIndex;\
isUnderflow = \ bs -> isUnderflow (toGBounds bs) . toGIndex;\
next = \ bs -> fromGIndex . next (toGBounds bs) . toGIndex;\
prev = \ bs -> fromGIndex . prev (toGBounds bs) . toGIndex;\
safeElem = \ bs -> fromGIndex . safeElem (toGBounds bs) . toGIndex;\
}
INDEX_INSTANCE(T2)
INDEX_INSTANCE(T3)
INDEX_INSTANCE(T4)
INDEX_INSTANCE(T5)
INDEX_INSTANCE(T6)
INDEX_INSTANCE(T7)
INDEX_INSTANCE(T8)
INDEX_INSTANCE(T9)
INDEX_INSTANCE(T10)
INDEX_INSTANCE(T11)
INDEX_INSTANCE(T12)
INDEX_INSTANCE(T13)
INDEX_INSTANCE(T14)
INDEX_INSTANCE(T15)
#undef INDEX_INSTANCE
(-.) :: (Enum i) => i -> i -> Int
-. :: i -> i -> Int
(-.) = (Int -> Int -> Int) -> (i -> Int) -> i -> i -> Int
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on (-) i -> Int
forall a. Enum a => a -> Int
fromEnum
{-# INLINE offsetIntegral #-}
offsetIntegral :: (Index i, Integral i) => (i, i) -> i -> Int
offsetIntegral :: (i, i) -> i -> Int
offsetIntegral bnds :: (i, i)
bnds@(i
l, i
_) i
i = (i, i) -> i -> Int -> String -> Int
forall i res. Index i => (i, i) -> i -> res -> String -> res
checkBounds (i, i)
bnds i
i (i
i i -> i -> Int
forall i. Enum i => i -> i -> Int
-. i
l) String
"offset {default}"
{-# INLINE defaultBoundsUnsign #-}
defaultBoundsUnsign :: (Index i, Bounded i) => Int -> (i, i)
defaultBoundsUnsign :: Int -> (i, i)
defaultBoundsUnsign Int
n = Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 Bool -> (i, i) -> (i, i) -> (i, i)
forall a. Bool -> a -> a -> a
? Int -> Int -> (i, i)
ub Int
1 Int
0 ((i, i) -> (i, i)) -> (i, i) -> (i, i)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (i, i)
ub Int
0 (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) where ub :: Int -> Int -> (i, i)
ub = (i -> i -> (i, i)) -> (Int -> i) -> Int -> Int -> (i, i)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on (,) Int -> i
forall i. Index i => Int -> i
unsafeIndex
checkBounds :: (Index i) => (i, i) -> i -> res -> String -> res
checkBounds :: (i, i) -> i -> res -> String -> res
checkBounds (i, i)
bnds i
i res
res = case (i, i) -> i -> InBounds
forall i. Index i => (i, i) -> i -> InBounds
inBounds (i, i)
bnds i
i of
InBounds
ER -> IndexException -> res
forall a e. Exception e => e -> a
throw (IndexException -> res)
-> (String -> IndexException) -> String -> res
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IndexException
EmptyRange (String -> IndexException) -> ShowS -> String -> IndexException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"in SDP.Index."
InBounds
OR -> IndexException -> res
forall a e. Exception e => e -> a
throw (IndexException -> res)
-> (String -> IndexException) -> String -> res
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IndexException
IndexOverflow (String -> IndexException) -> ShowS -> String -> IndexException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"in SDP.Index."
InBounds
UR -> IndexException -> res
forall a e. Exception e => e -> a
throw (IndexException -> res)
-> (String -> IndexException) -> String -> res
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IndexException
IndexUnderflow (String -> IndexException) -> ShowS -> String -> IndexException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"in SDP.Index."
InBounds
IN -> res -> String -> res
forall a b. a -> b -> a
const res
res
emptyEx :: String -> a
emptyEx :: String -> a
emptyEx = IndexException -> a
forall a e. Exception e => e -> a
throw (IndexException -> a) -> (String -> IndexException) -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IndexException
EmptyRange (String -> IndexException) -> ShowS -> String -> IndexException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"in SDP.Index."