{-# Language MagicHash #-}
module Data.PrimitiveArray.Index.Point where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Data.Aeson
import Data.Binary
import Data.Bits
import Data.Bits.Extras (Ranked)
import Data.Hashable (Hashable)
import Data.Serialize
import Data.Vector.Unboxed.Deriving
import Data.Vector.Unboxed (Unbox(..))
import GHC.Exts
import GHC.Generics (Generic)
import qualified Data.Vector.Fusion.Stream.Monadic as SM
import qualified Data.Vector.Unboxed as VU
import Test.QuickCheck as TQ
import Test.SmallCheck.Series as TS
import Data.PrimitiveArray.Index.Class
import Data.PrimitiveArray.Index.IOC
newtype PointL t = PointL {PointL t -> Int
fromPointL :: Int}
deriving stock (PointL t -> PointL t -> Bool
(PointL t -> PointL t -> Bool)
-> (PointL t -> PointL t -> Bool) -> Eq (PointL t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (t :: k). PointL t -> PointL t -> Bool
/= :: PointL t -> PointL t -> Bool
$c/= :: forall k (t :: k). PointL t -> PointL t -> Bool
== :: PointL t -> PointL t -> Bool
$c== :: forall k (t :: k). PointL t -> PointL t -> Bool
Eq,Eq (PointL t)
Eq (PointL t)
-> (PointL t -> PointL t -> Ordering)
-> (PointL t -> PointL t -> Bool)
-> (PointL t -> PointL t -> Bool)
-> (PointL t -> PointL t -> Bool)
-> (PointL t -> PointL t -> Bool)
-> (PointL t -> PointL t -> PointL t)
-> (PointL t -> PointL t -> PointL t)
-> Ord (PointL t)
PointL t -> PointL t -> Bool
PointL t -> PointL t -> Ordering
PointL t -> PointL t -> PointL t
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k (t :: k). Eq (PointL t)
forall k (t :: k). PointL t -> PointL t -> Bool
forall k (t :: k). PointL t -> PointL t -> Ordering
forall k (t :: k). PointL t -> PointL t -> PointL t
min :: PointL t -> PointL t -> PointL t
$cmin :: forall k (t :: k). PointL t -> PointL t -> PointL t
max :: PointL t -> PointL t -> PointL t
$cmax :: forall k (t :: k). PointL t -> PointL t -> PointL t
>= :: PointL t -> PointL t -> Bool
$c>= :: forall k (t :: k). PointL t -> PointL t -> Bool
> :: PointL t -> PointL t -> Bool
$c> :: forall k (t :: k). PointL t -> PointL t -> Bool
<= :: PointL t -> PointL t -> Bool
$c<= :: forall k (t :: k). PointL t -> PointL t -> Bool
< :: PointL t -> PointL t -> Bool
$c< :: forall k (t :: k). PointL t -> PointL t -> Bool
compare :: PointL t -> PointL t -> Ordering
$ccompare :: forall k (t :: k). PointL t -> PointL t -> Ordering
$cp1Ord :: forall k (t :: k). Eq (PointL t)
Ord,ReadPrec [PointL t]
ReadPrec (PointL t)
Int -> ReadS (PointL t)
ReadS [PointL t]
(Int -> ReadS (PointL t))
-> ReadS [PointL t]
-> ReadPrec (PointL t)
-> ReadPrec [PointL t]
-> Read (PointL t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (t :: k). ReadPrec [PointL t]
forall k (t :: k). ReadPrec (PointL t)
forall k (t :: k). Int -> ReadS (PointL t)
forall k (t :: k). ReadS [PointL t]
readListPrec :: ReadPrec [PointL t]
$creadListPrec :: forall k (t :: k). ReadPrec [PointL t]
readPrec :: ReadPrec (PointL t)
$creadPrec :: forall k (t :: k). ReadPrec (PointL t)
readList :: ReadS [PointL t]
$creadList :: forall k (t :: k). ReadS [PointL t]
readsPrec :: Int -> ReadS (PointL t)
$creadsPrec :: forall k (t :: k). Int -> ReadS (PointL t)
Read,Int -> PointL t -> ShowS
[PointL t] -> ShowS
PointL t -> String
(Int -> PointL t -> ShowS)
-> (PointL t -> String) -> ([PointL t] -> ShowS) -> Show (PointL t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (t :: k). Int -> PointL t -> ShowS
forall k (t :: k). [PointL t] -> ShowS
forall k (t :: k). PointL t -> String
showList :: [PointL t] -> ShowS
$cshowList :: forall k (t :: k). [PointL t] -> ShowS
show :: PointL t -> String
$cshow :: forall k (t :: k). PointL t -> String
showsPrec :: Int -> PointL t -> ShowS
$cshowsPrec :: forall k (t :: k). Int -> PointL t -> ShowS
Show,(forall x. PointL t -> Rep (PointL t) x)
-> (forall x. Rep (PointL t) x -> PointL t) -> Generic (PointL t)
forall x. Rep (PointL t) x -> PointL t
forall x. PointL t -> Rep (PointL t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (t :: k) x. Rep (PointL t) x -> PointL t
forall k (t :: k) x. PointL t -> Rep (PointL t) x
$cto :: forall k (t :: k) x. Rep (PointL t) x -> PointL t
$cfrom :: forall k (t :: k) x. PointL t -> Rep (PointL t) x
Generic)
deriving newtype (Integer -> PointL t
PointL t -> PointL t
PointL t -> PointL t -> PointL t
(PointL t -> PointL t -> PointL t)
-> (PointL t -> PointL t -> PointL t)
-> (PointL t -> PointL t -> PointL t)
-> (PointL t -> PointL t)
-> (PointL t -> PointL t)
-> (PointL t -> PointL t)
-> (Integer -> PointL t)
-> Num (PointL t)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall k (t :: k). Integer -> PointL t
forall k (t :: k). PointL t -> PointL t
forall k (t :: k). PointL t -> PointL t -> PointL t
fromInteger :: Integer -> PointL t
$cfromInteger :: forall k (t :: k). Integer -> PointL t
signum :: PointL t -> PointL t
$csignum :: forall k (t :: k). PointL t -> PointL t
abs :: PointL t -> PointL t
$cabs :: forall k (t :: k). PointL t -> PointL t
negate :: PointL t -> PointL t
$cnegate :: forall k (t :: k). PointL t -> PointL t
* :: PointL t -> PointL t -> PointL t
$c* :: forall k (t :: k). PointL t -> PointL t -> PointL t
- :: PointL t -> PointL t -> PointL t
$c- :: forall k (t :: k). PointL t -> PointL t -> PointL t
+ :: PointL t -> PointL t -> PointL t
$c+ :: forall k (t :: k). PointL t -> PointL t -> PointL t
Num)
pointLI :: Int -> PointL I
pointLI :: Int -> PointL I
pointLI = Int -> PointL I
forall k (t :: k). Int -> PointL t
PointL
{-# Inline pointLI #-}
pointLO :: Int -> PointL O
pointLO :: Int -> PointL O
pointLO = Int -> PointL O
forall k (t :: k). Int -> PointL t
PointL
{-# Inline pointLO #-}
pointLC :: Int -> PointL C
pointLC :: Int -> PointL C
pointLC = Int -> PointL C
forall k (t :: k). Int -> PointL t
PointL
{-# Inline pointLC #-}
derivingUnbox "PointL"
[t| forall t . PointL t -> Int |]
[| \ (PointL i) -> i |]
[| \ i -> PointL i |]
instance Binary (PointL t)
instance Serialize (PointL t)
instance FromJSON (PointL t)
instance FromJSONKey (PointL t)
instance ToJSON (PointL t)
instance ToJSONKey (PointL t)
instance Hashable (PointL t)
instance NFData (PointL t) where
rnf :: PointL t -> ()
rnf (PointL Int
l) = Int -> ()
forall a. NFData a => a -> ()
rnf Int
l
{-# Inline rnf #-}
instance Index (PointL t) where
newtype LimitType (PointL t) = LtPointL Int
linearIndex :: LimitType (PointL t) -> PointL t -> Int
linearIndex LimitType (PointL t)
_ (PointL Int
z) = Int
z
{-# INLINE linearIndex #-}
fromLinearIndex :: LimitType (PointL t) -> Int -> PointL t
fromLinearIndex (LtPointL h) Int
k = (Int -> PointL t
forall k (t :: k). Int -> PointL t
PointL Int
k)
{-# Inline fromLinearIndex #-}
size :: LimitType (PointL t) -> Int
size (LtPointL h) = Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
{-# INLINE size #-}
inBounds :: LimitType (PointL t) -> PointL t -> Bool
inBounds (LtPointL h) (PointL Int
x) = Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
x Bool -> Bool -> Bool
&& Int
xInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
h
{-# INLINE inBounds #-}
zeroBound :: PointL t
zeroBound = Int -> PointL t
forall k (t :: k). Int -> PointL t
PointL Int
0
{-# Inline [0] zeroBound #-}
zeroBound' :: LimitType (PointL t)
zeroBound' = Int -> LimitType (PointL t)
forall k (t :: k). Int -> LimitType (PointL t)
LtPointL Int
0
{-# Inline [0] zeroBound' #-}
totalSize :: LimitType (PointL t) -> [Integer]
totalSize (LtPointL h) = [Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1]
{-# Inline [0] totalSize #-}
showBound :: LimitType (PointL t) -> [String]
showBound (LtPointL h) = [String
"LtPointL " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
h]
showIndex :: PointL t -> [String]
showIndex (PointL Int
i) = [String
"PointL " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i]
deriving instance Eq (LimitType (PointL t))
deriving instance Generic (LimitType (PointL t))
deriving instance Read (LimitType (PointL t))
deriving instance Show (LimitType (PointL t))
instance IndexStream z => IndexStream (z:.PointL I) where
streamUp :: LimitType (z :. PointL I)
-> LimitType (z :. PointL I) -> Stream m (z :. PointL I)
streamUp (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL I)))
-> Stream m z
-> Stream m (z :. PointL I)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamUpMk Int
lf) ((Int -> PointL I) -> Int -> SP z -> m (Step (SP z) (z :. PointL I))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> PointL I
forall k (t :: k). Int -> PointL t
PointL Int
ht) (Stream m z -> Stream m (z :. PointL I))
-> Stream m z -> Stream m (z :. PointL I)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
streamDown :: LimitType (z :. PointL I)
-> LimitType (z :. PointL I) -> Stream m (z :. PointL I)
streamDown (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL I)))
-> Stream m z
-> Stream m (z :. PointL I)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamDownMk Int
ht) ((Int -> PointL I) -> Int -> SP z -> m (Step (SP z) (z :. PointL I))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> PointL I
forall k (t :: k). Int -> PointL t
PointL Int
lf) (Stream m z -> Stream m (z :. PointL I))
-> Stream m z -> Stream m (z :. PointL I)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline [0] streamUp #-}
{-# Inline [0] streamDown #-}
instance IndexStream z => IndexStream (z:.PointL O) where
streamUp :: LimitType (z :. PointL O)
-> LimitType (z :. PointL O) -> Stream m (z :. PointL O)
streamUp (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL O)))
-> Stream m z
-> Stream m (z :. PointL O)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamDownMk Int
ht) ((Int -> PointL O) -> Int -> SP z -> m (Step (SP z) (z :. PointL O))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> PointL O
forall k (t :: k). Int -> PointL t
PointL Int
lf) (Stream m z -> Stream m (z :. PointL O))
-> Stream m z -> Stream m (z :. PointL O)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
streamDown :: LimitType (z :. PointL O)
-> LimitType (z :. PointL O) -> Stream m (z :. PointL O)
streamDown (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL O)))
-> Stream m z
-> Stream m (z :. PointL O)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamUpMk Int
lf) ((Int -> PointL O) -> Int -> SP z -> m (Step (SP z) (z :. PointL O))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> PointL O
forall k (t :: k). Int -> PointL t
PointL Int
ht) (Stream m z -> Stream m (z :. PointL O))
-> Stream m z -> Stream m (z :. PointL O)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline [0] streamUp #-}
{-# Inline [0] streamDown #-}
instance IndexStream z => IndexStream (z:.PointL C) where
streamUp :: LimitType (z :. PointL C)
-> LimitType (z :. PointL C) -> Stream m (z :. PointL C)
streamUp (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL C)))
-> Stream m z
-> Stream m (z :. PointL C)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamUpMk Int
lf) ((Int -> PointL C) -> Int -> SP z -> m (Step (SP z) (z :. PointL C))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> PointL C
forall k (t :: k). Int -> PointL t
PointL Int
ht) (Stream m z -> Stream m (z :. PointL C))
-> Stream m z -> Stream m (z :. PointL C)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
streamDown :: LimitType (z :. PointL C)
-> LimitType (z :. PointL C) -> Stream m (z :. PointL C)
streamDown (ls:..LtPointL lf) (hs:..LtPointL ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointL C)))
-> Stream m z
-> Stream m (z :. PointL C)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamDownMk Int
ht) ((Int -> PointL C) -> Int -> SP z -> m (Step (SP z) (z :. PointL C))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> PointL C
forall k (t :: k). Int -> PointL t
PointL Int
lf) (Stream m z -> Stream m (z :. PointL C))
-> Stream m z -> Stream m (z :. PointL C)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline [0] streamUp #-}
{-# Inline [0] streamDown #-}
data SP z = SP !z !Int#
streamUpMk :: Int -> z -> m (SP z)
streamUpMk (I# Int#
lf) z
z = SP z -> m (SP z)
forall (m :: * -> *) a. Monad m => a -> m a
return (SP z -> m (SP z)) -> SP z -> m (SP z)
forall a b. (a -> b) -> a -> b
$ z -> Int# -> SP z
forall z. z -> Int# -> SP z
SP z
z Int#
lf
{-# Inline [0] streamUpMk #-}
streamUpStep :: (Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> b
wrapper (I# Int#
ht) (SP z
z Int#
k)
| Int#
1# <- Int#
k Int# -> Int# -> Int#
># Int#
ht = Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (SP z) (z :. b) -> m (Step (SP z) (z :. b)))
-> Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall a b. (a -> b) -> a -> b
$ Step (SP z) (z :. b)
forall s a. Step s a
SM.Done
| Bool
otherwise = Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (SP z) (z :. b) -> m (Step (SP z) (z :. b)))
-> Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall a b. (a -> b) -> a -> b
$ (z :. b) -> SP z -> Step (SP z) (z :. b)
forall a s. a -> s -> Step s a
SM.Yield (z
zz -> b -> z :. b
forall a b. a -> b -> a :. b
:.Int -> b
wrapper (Int# -> Int
I# Int#
k)) (z -> Int# -> SP z
forall z. z -> Int# -> SP z
SP z
z (Int#
k Int# -> Int# -> Int#
+# Int#
1#))
{-# Inline [0] streamUpStep #-}
streamDownMk :: Int -> z -> m (SP z)
streamDownMk (I# Int#
ht) z
z = SP z -> m (SP z)
forall (m :: * -> *) a. Monad m => a -> m a
return (SP z -> m (SP z)) -> SP z -> m (SP z)
forall a b. (a -> b) -> a -> b
$ z -> Int# -> SP z
forall z. z -> Int# -> SP z
SP z
z Int#
ht
{-# Inline [0] streamDownMk #-}
streamDownStep :: (Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> b
wrapper (I# Int#
lf) (SP z
z Int#
k)
| Int#
1# <- Int#
k Int# -> Int# -> Int#
<# Int#
lf = Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (SP z) (z :. b) -> m (Step (SP z) (z :. b)))
-> Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall a b. (a -> b) -> a -> b
$ Step (SP z) (z :. b)
forall s a. Step s a
SM.Done
| Bool
otherwise = Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (SP z) (z :. b) -> m (Step (SP z) (z :. b)))
-> Step (SP z) (z :. b) -> m (Step (SP z) (z :. b))
forall a b. (a -> b) -> a -> b
$ (z :. b) -> SP z -> Step (SP z) (z :. b)
forall a s. a -> s -> Step s a
SM.Yield (z
zz -> b -> z :. b
forall a b. a -> b -> a :. b
:.Int -> b
wrapper (Int# -> Int
I# Int#
k)) (z -> Int# -> SP z
forall z. z -> Int# -> SP z
SP z
z (Int#
k Int# -> Int# -> Int#
-# Int#
1#))
{-# Inline [0] streamDownStep #-}
instance IndexStream (Z:.PointL t) => IndexStream (PointL t) where
streamUp :: LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t)
streamUp LimitType (PointL t)
l LimitType (PointL t)
h = ((Z :. PointL t) -> PointL t)
-> Stream m (Z :. PointL t) -> Stream m (PointL t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.PointL t
i) -> PointL t
i) (Stream m (Z :. PointL t) -> Stream m (PointL t))
-> Stream m (Z :. PointL t) -> Stream m (PointL t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. PointL t)
-> LimitType (Z :. PointL t) -> Stream m (Z :. PointL t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp (LimitType Z
ZZLimitType Z -> LimitType (PointL t) -> LimitType (Z :. PointL t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointL t)
l) (LimitType Z
ZZLimitType Z -> LimitType (PointL t) -> LimitType (Z :. PointL t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointL t)
h)
{-# INLINE streamUp #-}
streamDown :: LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t)
streamDown LimitType (PointL t)
l LimitType (PointL t)
h = ((Z :. PointL t) -> PointL t)
-> Stream m (Z :. PointL t) -> Stream m (PointL t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.PointL t
i) -> PointL t
i) (Stream m (Z :. PointL t) -> Stream m (PointL t))
-> Stream m (Z :. PointL t) -> Stream m (PointL t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. PointL t)
-> LimitType (Z :. PointL t) -> Stream m (Z :. PointL t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown (LimitType Z
ZZLimitType Z -> LimitType (PointL t) -> LimitType (Z :. PointL t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointL t)
l) (LimitType Z
ZZLimitType Z -> LimitType (PointL t) -> LimitType (Z :. PointL t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointL t)
h)
{-# INLINE streamDown #-}
instance Arbitrary (PointL t) where
arbitrary :: Gen (PointL t)
arbitrary = do
Int
b <- (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
choose (Int
0,Int
100)
PointL t -> Gen (PointL t)
forall (m :: * -> *) a. Monad m => a -> m a
return (PointL t -> Gen (PointL t)) -> PointL t -> Gen (PointL t)
forall a b. (a -> b) -> a -> b
$ Int -> PointL t
forall k (t :: k). Int -> PointL t
PointL Int
b
shrink :: PointL t -> [PointL t]
shrink (PointL Int
j)
| Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
j = [Int -> PointL t
forall k (t :: k). Int -> PointL t
PointL (Int -> PointL t) -> Int -> PointL t
forall a b. (a -> b) -> a -> b
$ Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]
| Bool
otherwise = []
instance Monad m => Serial m (PointL t) where
series :: Series m (PointL t)
series = Int -> PointL t
forall k (t :: k). Int -> PointL t
PointL (Int -> PointL t)
-> (NonNegative Int -> Int) -> NonNegative Int -> PointL t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Int -> Int
forall a. NonNegative a -> a
TS.getNonNegative (NonNegative Int -> PointL t)
-> Series m (NonNegative Int) -> Series m (PointL t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Series m (NonNegative Int)
forall (m :: * -> *) a. Serial m a => Series m a
series
newtype PointR t = PointR {PointR t -> Int
fromPointR :: Int}
deriving stock (PointR t -> PointR t -> Bool
(PointR t -> PointR t -> Bool)
-> (PointR t -> PointR t -> Bool) -> Eq (PointR t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (t :: k). PointR t -> PointR t -> Bool
/= :: PointR t -> PointR t -> Bool
$c/= :: forall k (t :: k). PointR t -> PointR t -> Bool
== :: PointR t -> PointR t -> Bool
$c== :: forall k (t :: k). PointR t -> PointR t -> Bool
Eq,Eq (PointR t)
Eq (PointR t)
-> (PointR t -> PointR t -> Ordering)
-> (PointR t -> PointR t -> Bool)
-> (PointR t -> PointR t -> Bool)
-> (PointR t -> PointR t -> Bool)
-> (PointR t -> PointR t -> Bool)
-> (PointR t -> PointR t -> PointR t)
-> (PointR t -> PointR t -> PointR t)
-> Ord (PointR t)
PointR t -> PointR t -> Bool
PointR t -> PointR t -> Ordering
PointR t -> PointR t -> PointR t
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k (t :: k). Eq (PointR t)
forall k (t :: k). PointR t -> PointR t -> Bool
forall k (t :: k). PointR t -> PointR t -> Ordering
forall k (t :: k). PointR t -> PointR t -> PointR t
min :: PointR t -> PointR t -> PointR t
$cmin :: forall k (t :: k). PointR t -> PointR t -> PointR t
max :: PointR t -> PointR t -> PointR t
$cmax :: forall k (t :: k). PointR t -> PointR t -> PointR t
>= :: PointR t -> PointR t -> Bool
$c>= :: forall k (t :: k). PointR t -> PointR t -> Bool
> :: PointR t -> PointR t -> Bool
$c> :: forall k (t :: k). PointR t -> PointR t -> Bool
<= :: PointR t -> PointR t -> Bool
$c<= :: forall k (t :: k). PointR t -> PointR t -> Bool
< :: PointR t -> PointR t -> Bool
$c< :: forall k (t :: k). PointR t -> PointR t -> Bool
compare :: PointR t -> PointR t -> Ordering
$ccompare :: forall k (t :: k). PointR t -> PointR t -> Ordering
$cp1Ord :: forall k (t :: k). Eq (PointR t)
Ord,ReadPrec [PointR t]
ReadPrec (PointR t)
Int -> ReadS (PointR t)
ReadS [PointR t]
(Int -> ReadS (PointR t))
-> ReadS [PointR t]
-> ReadPrec (PointR t)
-> ReadPrec [PointR t]
-> Read (PointR t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (t :: k). ReadPrec [PointR t]
forall k (t :: k). ReadPrec (PointR t)
forall k (t :: k). Int -> ReadS (PointR t)
forall k (t :: k). ReadS [PointR t]
readListPrec :: ReadPrec [PointR t]
$creadListPrec :: forall k (t :: k). ReadPrec [PointR t]
readPrec :: ReadPrec (PointR t)
$creadPrec :: forall k (t :: k). ReadPrec (PointR t)
readList :: ReadS [PointR t]
$creadList :: forall k (t :: k). ReadS [PointR t]
readsPrec :: Int -> ReadS (PointR t)
$creadsPrec :: forall k (t :: k). Int -> ReadS (PointR t)
Read,Int -> PointR t -> ShowS
[PointR t] -> ShowS
PointR t -> String
(Int -> PointR t -> ShowS)
-> (PointR t -> String) -> ([PointR t] -> ShowS) -> Show (PointR t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (t :: k). Int -> PointR t -> ShowS
forall k (t :: k). [PointR t] -> ShowS
forall k (t :: k). PointR t -> String
showList :: [PointR t] -> ShowS
$cshowList :: forall k (t :: k). [PointR t] -> ShowS
show :: PointR t -> String
$cshow :: forall k (t :: k). PointR t -> String
showsPrec :: Int -> PointR t -> ShowS
$cshowsPrec :: forall k (t :: k). Int -> PointR t -> ShowS
Show,(forall x. PointR t -> Rep (PointR t) x)
-> (forall x. Rep (PointR t) x -> PointR t) -> Generic (PointR t)
forall x. Rep (PointR t) x -> PointR t
forall x. PointR t -> Rep (PointR t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (t :: k) x. Rep (PointR t) x -> PointR t
forall k (t :: k) x. PointR t -> Rep (PointR t) x
$cto :: forall k (t :: k) x. Rep (PointR t) x -> PointR t
$cfrom :: forall k (t :: k) x. PointR t -> Rep (PointR t) x
Generic)
deriving newtype (Integer -> PointR t
PointR t -> PointR t
PointR t -> PointR t -> PointR t
(PointR t -> PointR t -> PointR t)
-> (PointR t -> PointR t -> PointR t)
-> (PointR t -> PointR t -> PointR t)
-> (PointR t -> PointR t)
-> (PointR t -> PointR t)
-> (PointR t -> PointR t)
-> (Integer -> PointR t)
-> Num (PointR t)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall k (t :: k). Integer -> PointR t
forall k (t :: k). PointR t -> PointR t
forall k (t :: k). PointR t -> PointR t -> PointR t
fromInteger :: Integer -> PointR t
$cfromInteger :: forall k (t :: k). Integer -> PointR t
signum :: PointR t -> PointR t
$csignum :: forall k (t :: k). PointR t -> PointR t
abs :: PointR t -> PointR t
$cabs :: forall k (t :: k). PointR t -> PointR t
negate :: PointR t -> PointR t
$cnegate :: forall k (t :: k). PointR t -> PointR t
* :: PointR t -> PointR t -> PointR t
$c* :: forall k (t :: k). PointR t -> PointR t -> PointR t
- :: PointR t -> PointR t -> PointR t
$c- :: forall k (t :: k). PointR t -> PointR t -> PointR t
+ :: PointR t -> PointR t -> PointR t
$c+ :: forall k (t :: k). PointR t -> PointR t -> PointR t
Num)
derivingUnbox "PointR"
[t| forall t . PointR t -> Int |]
[| \ (PointR i) -> i |]
[| \ i -> PointR i |]
instance Binary (PointR t)
instance Serialize (PointR t)
instance FromJSON (PointR t)
instance FromJSONKey (PointR t)
instance ToJSON (PointR t)
instance ToJSONKey (PointR t)
instance Hashable (PointR t)
instance NFData (PointR t) where
rnf :: PointR t -> ()
rnf (PointR Int
l) = Int -> ()
forall a. NFData a => a -> ()
rnf Int
l
{-# Inline rnf #-}
instance Index (PointR t) where
newtype LimitType (PointR t) = LtPointR Int
linearIndex :: LimitType (PointR t) -> PointR t -> Int
linearIndex LimitType (PointR t)
_ (PointR Int
z) = Int
z
{-# INLINE linearIndex #-}
size :: LimitType (PointR t) -> Int
size (LtPointR h) = Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
{-# INLINE size #-}
inBounds :: LimitType (PointR t) -> PointR t -> Bool
inBounds (LtPointR h) (PointR Int
x) = Int
0Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
x Bool -> Bool -> Bool
&& Int
xInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
h
{-# INLINE inBounds #-}
zeroBound :: PointR t
zeroBound = Int -> PointR t
forall k (t :: k). Int -> PointR t
PointR Int
0
{-# Inline [0] zeroBound #-}
zeroBound' :: LimitType (PointR t)
zeroBound' = Int -> LimitType (PointR t)
forall k (t :: k). Int -> LimitType (PointR t)
LtPointR Int
0
{-# Inline [0] zeroBound' #-}
totalSize :: LimitType (PointR t) -> [Integer]
totalSize (LtPointR h) = [Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1]
{-# Inline [0] totalSize #-}
fromLinearIndex :: LimitType (PointR t) -> Int -> PointR t
fromLinearIndex LimitType (PointR t)
_ = Int -> PointR t
forall k (t :: k). Int -> PointR t
PointR
{-# Inline [0] fromLinearIndex #-}
showBound :: LimitType (PointR t) -> [String]
showBound (LtPointR b) = [String
"LtPointR " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
b]
showIndex :: PointR t -> [String]
showIndex (PointR Int
p) = [String
"PointR " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
p]
deriving instance Eq (LimitType (PointR t))
deriving instance Generic (LimitType (PointR t))
deriving instance Read (LimitType (PointR t))
deriving instance Show (LimitType (PointR t))
instance IndexStream z => IndexStream (z:.PointR I) where
streamUp :: LimitType (z :. PointR I)
-> LimitType (z :. PointR I) -> Stream m (z :. PointR I)
streamUp (ls:..LtPointR lf) (hs:..LtPointR ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointR I)))
-> Stream m z
-> Stream m (z :. PointR I)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamDownMk Int
ht) ((Int -> PointR I) -> Int -> SP z -> m (Step (SP z) (z :. PointR I))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> PointR I
forall k (t :: k). Int -> PointR t
PointR Int
lf) (Stream m z -> Stream m (z :. PointR I))
-> Stream m z -> Stream m (z :. PointR I)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
streamDown :: LimitType (z :. PointR I)
-> LimitType (z :. PointR I) -> Stream m (z :. PointR I)
streamDown (ls:..LtPointR lf) (hs:..LtPointR ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointR I)))
-> Stream m z
-> Stream m (z :. PointR I)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamUpMk Int
lf) ((Int -> PointR I) -> Int -> SP z -> m (Step (SP z) (z :. PointR I))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> PointR I
forall k (t :: k). Int -> PointR t
PointR Int
ht) (Stream m z -> Stream m (z :. PointR I))
-> Stream m z -> Stream m (z :. PointR I)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline [0] streamUp #-}
{-# Inline [0] streamDown #-}
instance IndexStream z => IndexStream (z:.PointR O) where
streamUp :: LimitType (z :. PointR O)
-> LimitType (z :. PointR O) -> Stream m (z :. PointR O)
streamUp (ls:..LtPointR lf) (hs:..LtPointR ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointR O)))
-> Stream m z
-> Stream m (z :. PointR O)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamUpMk Int
lf) ((Int -> PointR O) -> Int -> SP z -> m (Step (SP z) (z :. PointR O))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamUpStep Int -> PointR O
forall k (t :: k). Int -> PointR t
PointR Int
ht) (Stream m z -> Stream m (z :. PointR O))
-> Stream m z -> Stream m (z :. PointR O)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp LimitType z
ls LimitType z
hs
streamDown :: LimitType (z :. PointR O)
-> LimitType (z :. PointR O) -> Stream m (z :. PointR O)
streamDown (ls:..LtPointR lf) (hs:..LtPointR ht) = (z -> m (SP z))
-> (SP z -> m (Step (SP z) (z :. PointR O)))
-> Stream m z
-> Stream m (z :. PointR O)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
SM.flatten (Int -> z -> m (SP z)
forall (m :: * -> *) z. Monad m => Int -> z -> m (SP z)
streamDownMk Int
ht) ((Int -> PointR O) -> Int -> SP z -> m (Step (SP z) (z :. PointR O))
forall (m :: * -> *) b z.
Monad m =>
(Int -> b) -> Int -> SP z -> m (Step (SP z) (z :. b))
streamDownStep Int -> PointR O
forall k (t :: k). Int -> PointR t
PointR Int
lf) (Stream m z -> Stream m (z :. PointR O))
-> Stream m z -> Stream m (z :. PointR O)
forall a b. (a -> b) -> a -> b
$ LimitType z -> LimitType z -> Stream m z
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown LimitType z
ls LimitType z
hs
{-# Inline [0] streamUp #-}
{-# Inline [0] streamDown #-}
instance IndexStream (Z:.PointR t) => IndexStream (PointR t) where
streamUp :: LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t)
streamUp LimitType (PointR t)
l LimitType (PointR t)
h = ((Z :. PointR t) -> PointR t)
-> Stream m (Z :. PointR t) -> Stream m (PointR t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.PointR t
i) -> PointR t
i) (Stream m (Z :. PointR t) -> Stream m (PointR t))
-> Stream m (Z :. PointR t) -> Stream m (PointR t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. PointR t)
-> LimitType (Z :. PointR t) -> Stream m (Z :. PointR t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp (LimitType Z
ZZLimitType Z -> LimitType (PointR t) -> LimitType (Z :. PointR t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointR t)
l) (LimitType Z
ZZLimitType Z -> LimitType (PointR t) -> LimitType (Z :. PointR t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointR t)
h)
{-# INLINE streamUp #-}
streamDown :: LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t)
streamDown LimitType (PointR t)
l LimitType (PointR t)
h = ((Z :. PointR t) -> PointR t)
-> Stream m (Z :. PointR t) -> Stream m (PointR t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.PointR t
i) -> PointR t
i) (Stream m (Z :. PointR t) -> Stream m (PointR t))
-> Stream m (Z :. PointR t) -> Stream m (PointR t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. PointR t)
-> LimitType (Z :. PointR t) -> Stream m (Z :. PointR t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown (LimitType Z
ZZLimitType Z -> LimitType (PointR t) -> LimitType (Z :. PointR t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointR t)
l) (LimitType Z
ZZLimitType Z -> LimitType (PointR t) -> LimitType (Z :. PointR t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (PointR t)
h)
{-# INLINE streamDown #-}
arbMaxPointR :: Int
arbMaxPointR = Int
100
instance Arbitrary (PointR t) where
arbitrary :: Gen (PointR t)
arbitrary = do
Int
b <- (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
choose (Int
0,Int
arbMaxPointR)
PointR t -> Gen (PointR t)
forall (m :: * -> *) a. Monad m => a -> m a
return (PointR t -> Gen (PointR t)) -> PointR t -> Gen (PointR t)
forall a b. (a -> b) -> a -> b
$ Int -> PointR t
forall k (t :: k). Int -> PointR t
PointR Int
b
shrink :: PointR t -> [PointR t]
shrink (PointR Int
j)
| Int
jInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
arbMaxPointR = [Int -> PointR t
forall k (t :: k). Int -> PointR t
PointR (Int -> PointR t) -> Int -> PointR t
forall a b. (a -> b) -> a -> b
$ Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1]
| Bool
otherwise = []
instance SparseBucket (PointL I) where
{-# Inline manhattan #-}
manhattan :: LimitType (PointL I) -> PointL I -> Int
manhattan (LtPointL u) (PointL Int
i) = Int
i
{-# Inline manhattanMax #-}
manhattanMax :: LimitType (PointL I) -> Int
manhattanMax (LtPointL u) = Int
u
instance SparseBucket (PointL O) where
{-# Inline manhattan #-}
manhattan :: LimitType (PointL O) -> PointL O -> Int
manhattan (LtPointL u) (PointL Int
i) = Int
uInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i
{-# Inline manhattanMax #-}
manhattanMax :: LimitType (PointL O) -> Int
manhattanMax (LtPointL u) = Int
u