module Biobase.Types.Index.Type where

import           Control.Applicative ((<$>))
import           Control.DeepSeq
import           Data.Aeson
import           Data.Binary
import           Data.Data (Data)
import           Data.Hashable (Hashable)
import           Data.Proxy
import           Data.Serialize (Serialize)
import           Data.Typeable (Typeable)
import           Data.Vector.Fusion.Stream.Monadic (Step(..), flatten)
import           Data.Vector.Unboxed.Deriving
import           GHC.Generics
import           GHC.TypeLits
import qualified Data.Ix as Ix
import qualified Data.Vector.Fusion.Stream.Monadic as SM
import           Test.QuickCheck
import           Text.Printf

import           Data.PrimitiveArray.Index.Class hiding (Index)
import qualified Data.PrimitiveArray.Index.Class as PA



-- | A linear @Int@-based index type.

newtype Index (t :: Nat) = Index { Index t -> Int
getIndex :: Int }
  deriving (Int -> Index t -> ShowS
[Index t] -> ShowS
Index t -> String
(Int -> Index t -> ShowS)
-> (Index t -> String) -> ([Index t] -> ShowS) -> Show (Index t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (t :: Nat). Int -> Index t -> ShowS
forall (t :: Nat). [Index t] -> ShowS
forall (t :: Nat). Index t -> String
showList :: [Index t] -> ShowS
$cshowList :: forall (t :: Nat). [Index t] -> ShowS
show :: Index t -> String
$cshow :: forall (t :: Nat). Index t -> String
showsPrec :: Int -> Index t -> ShowS
$cshowsPrec :: forall (t :: Nat). Int -> Index t -> ShowS
Show,ReadPrec [Index t]
ReadPrec (Index t)
Int -> ReadS (Index t)
ReadS [Index t]
(Int -> ReadS (Index t))
-> ReadS [Index t]
-> ReadPrec (Index t)
-> ReadPrec [Index t]
-> Read (Index t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (t :: Nat). ReadPrec [Index t]
forall (t :: Nat). ReadPrec (Index t)
forall (t :: Nat). Int -> ReadS (Index t)
forall (t :: Nat). ReadS [Index t]
readListPrec :: ReadPrec [Index t]
$creadListPrec :: forall (t :: Nat). ReadPrec [Index t]
readPrec :: ReadPrec (Index t)
$creadPrec :: forall (t :: Nat). ReadPrec (Index t)
readList :: ReadS [Index t]
$creadList :: forall (t :: Nat). ReadS [Index t]
readsPrec :: Int -> ReadS (Index t)
$creadsPrec :: forall (t :: Nat). Int -> ReadS (Index t)
Read,Index t -> Index t -> Bool
(Index t -> Index t -> Bool)
-> (Index t -> Index t -> Bool) -> Eq (Index t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (t :: Nat). Index t -> Index t -> Bool
/= :: Index t -> Index t -> Bool
$c/= :: forall (t :: Nat). Index t -> Index t -> Bool
== :: Index t -> Index t -> Bool
$c== :: forall (t :: Nat). Index t -> Index t -> Bool
Eq,Eq (Index t)
Eq (Index t)
-> (Index t -> Index t -> Ordering)
-> (Index t -> Index t -> Bool)
-> (Index t -> Index t -> Bool)
-> (Index t -> Index t -> Bool)
-> (Index t -> Index t -> Bool)
-> (Index t -> Index t -> Index t)
-> (Index t -> Index t -> Index t)
-> Ord (Index t)
Index t -> Index t -> Bool
Index t -> Index t -> Ordering
Index t -> Index t -> Index 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 (t :: Nat). Eq (Index t)
forall (t :: Nat). Index t -> Index t -> Bool
forall (t :: Nat). Index t -> Index t -> Ordering
forall (t :: Nat). Index t -> Index t -> Index t
min :: Index t -> Index t -> Index t
$cmin :: forall (t :: Nat). Index t -> Index t -> Index t
max :: Index t -> Index t -> Index t
$cmax :: forall (t :: Nat). Index t -> Index t -> Index t
>= :: Index t -> Index t -> Bool
$c>= :: forall (t :: Nat). Index t -> Index t -> Bool
> :: Index t -> Index t -> Bool
$c> :: forall (t :: Nat). Index t -> Index t -> Bool
<= :: Index t -> Index t -> Bool
$c<= :: forall (t :: Nat). Index t -> Index t -> Bool
< :: Index t -> Index t -> Bool
$c< :: forall (t :: Nat). Index t -> Index t -> Bool
compare :: Index t -> Index t -> Ordering
$ccompare :: forall (t :: Nat). Index t -> Index t -> Ordering
$cp1Ord :: forall (t :: Nat). Eq (Index t)
Ord,(forall x. Index t -> Rep (Index t) x)
-> (forall x. Rep (Index t) x -> Index t) -> Generic (Index t)
forall x. Rep (Index t) x -> Index t
forall x. Index t -> Rep (Index t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (t :: Nat) x. Rep (Index t) x -> Index t
forall (t :: Nat) x. Index t -> Rep (Index t) x
$cto :: forall (t :: Nat) x. Rep (Index t) x -> Index t
$cfrom :: forall (t :: Nat) x. Index t -> Rep (Index t) x
Generic,Ord (Index t)
Ord (Index t)
-> ((Index t, Index t) -> [Index t])
-> ((Index t, Index t) -> Index t -> Int)
-> ((Index t, Index t) -> Index t -> Int)
-> ((Index t, Index t) -> Index t -> Bool)
-> ((Index t, Index t) -> Int)
-> ((Index t, Index t) -> Int)
-> Ix (Index t)
(Index t, Index t) -> Int
(Index t, Index t) -> [Index t]
(Index t, Index t) -> Index t -> Bool
(Index t, Index t) -> Index t -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
forall (t :: Nat). Ord (Index t)
forall (t :: Nat). (Index t, Index t) -> Int
forall (t :: Nat). (Index t, Index t) -> [Index t]
forall (t :: Nat). (Index t, Index t) -> Index t -> Bool
forall (t :: Nat). (Index t, Index t) -> Index t -> Int
unsafeRangeSize :: (Index t, Index t) -> Int
$cunsafeRangeSize :: forall (t :: Nat). (Index t, Index t) -> Int
rangeSize :: (Index t, Index t) -> Int
$crangeSize :: forall (t :: Nat). (Index t, Index t) -> Int
inRange :: (Index t, Index t) -> Index t -> Bool
$cinRange :: forall (t :: Nat). (Index t, Index t) -> Index t -> Bool
unsafeIndex :: (Index t, Index t) -> Index t -> Int
$cunsafeIndex :: forall (t :: Nat). (Index t, Index t) -> Index t -> Int
index :: (Index t, Index t) -> Index t -> Int
$cindex :: forall (t :: Nat). (Index t, Index t) -> Index t -> Int
range :: (Index t, Index t) -> [Index t]
$crange :: forall (t :: Nat). (Index t, Index t) -> [Index t]
$cp1Ix :: forall (t :: Nat). Ord (Index t)
Ix.Ix,Typeable (Index t)
DataType
Constr
Typeable (Index t)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Index t -> c (Index t))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Index t))
-> (Index t -> Constr)
-> (Index t -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Index t)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index t)))
-> ((forall b. Data b => b -> b) -> Index t -> Index t)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Index t -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Index t -> r)
-> (forall u. (forall d. Data d => d -> u) -> Index t -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Index t -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Index t -> m (Index t))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Index t -> m (Index t))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Index t -> m (Index t))
-> Data (Index t)
Index t -> DataType
Index t -> Constr
(forall b. Data b => b -> b) -> Index t -> Index t
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Index t -> c (Index t)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Index t)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Index t -> u
forall u. (forall d. Data d => d -> u) -> Index t -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
forall (t :: Nat). KnownNat t => Typeable (Index t)
forall (t :: Nat). KnownNat t => Index t -> DataType
forall (t :: Nat). KnownNat t => Index t -> Constr
forall (t :: Nat).
KnownNat t =>
(forall b. Data b => b -> b) -> Index t -> Index t
forall (t :: Nat) u.
KnownNat t =>
Int -> (forall d. Data d => d -> u) -> Index t -> u
forall (t :: Nat) u.
KnownNat t =>
(forall d. Data d => d -> u) -> Index t -> [u]
forall (t :: Nat) r r'.
KnownNat t =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
forall (t :: Nat) r r'.
KnownNat t =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
forall (t :: Nat) (m :: * -> *).
(KnownNat t, Monad m) =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
forall (t :: Nat) (m :: * -> *).
(KnownNat t, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
forall (t :: Nat) (c :: * -> *).
KnownNat t =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Index t)
forall (t :: Nat) (c :: * -> *).
KnownNat t =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Index t -> c (Index t)
forall (t :: Nat) (t :: * -> *) (c :: * -> *).
(KnownNat t, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Index t))
forall (t :: Nat) (t :: * -> * -> *) (c :: * -> *).
(KnownNat t, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index t))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Index t)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Index t -> c (Index t)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Index t))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index t))
$cIndex :: Constr
$tIndex :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Index t -> m (Index t)
$cgmapMo :: forall (t :: Nat) (m :: * -> *).
(KnownNat t, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
gmapMp :: (forall d. Data d => d -> m d) -> Index t -> m (Index t)
$cgmapMp :: forall (t :: Nat) (m :: * -> *).
(KnownNat t, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
gmapM :: (forall d. Data d => d -> m d) -> Index t -> m (Index t)
$cgmapM :: forall (t :: Nat) (m :: * -> *).
(KnownNat t, Monad m) =>
(forall d. Data d => d -> m d) -> Index t -> m (Index t)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Index t -> u
$cgmapQi :: forall (t :: Nat) u.
KnownNat t =>
Int -> (forall d. Data d => d -> u) -> Index t -> u
gmapQ :: (forall d. Data d => d -> u) -> Index t -> [u]
$cgmapQ :: forall (t :: Nat) u.
KnownNat t =>
(forall d. Data d => d -> u) -> Index t -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
$cgmapQr :: forall (t :: Nat) r r'.
KnownNat t =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
$cgmapQl :: forall (t :: Nat) r r'.
KnownNat t =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Index t -> r
gmapT :: (forall b. Data b => b -> b) -> Index t -> Index t
$cgmapT :: forall (t :: Nat).
KnownNat t =>
(forall b. Data b => b -> b) -> Index t -> Index t
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index t))
$cdataCast2 :: forall (t :: Nat) (t :: * -> * -> *) (c :: * -> *).
(KnownNat t, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index t))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Index t))
$cdataCast1 :: forall (t :: Nat) (t :: * -> *) (c :: * -> *).
(KnownNat t, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Index t))
dataTypeOf :: Index t -> DataType
$cdataTypeOf :: forall (t :: Nat). KnownNat t => Index t -> DataType
toConstr :: Index t -> Constr
$ctoConstr :: forall (t :: Nat). KnownNat t => Index t -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Index t)
$cgunfold :: forall (t :: Nat) (c :: * -> *).
KnownNat t =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Index t)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Index t -> c (Index t)
$cgfoldl :: forall (t :: Nat) (c :: * -> *).
KnownNat t =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Index t -> c (Index t)
$cp1Data :: forall (t :: Nat). KnownNat t => Typeable (Index t)
Data,Typeable)

-- | Turn an 'Int' into an 'Index' safely.

index :: forall t . KnownNat t => Int -> Index t
index :: Int -> Index t
index Int
i = Index t -> (Index t -> Index t) -> Maybe (Index t) -> Index t
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Index t
forall a. HasCallStack => String -> a
error (String -> Index t) -> String -> Index t
forall a b. (a -> b) -> a -> b
$ String -> Int -> Integer -> String
forall r. PrintfType r => String -> r
printf String
"%d < Index %d\n" Int
i Integer
n) Index t -> Index t
forall a. a -> a
id (Maybe (Index t) -> Index t) -> Maybe (Index t) -> Index t
forall a b. (a -> b) -> a -> b
$ Int -> Maybe (Index t)
forall (t :: Nat). KnownNat t => Int -> Maybe (Index t)
maybeIndex Int
i
  where n :: Integer
n = Proxy t -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)
{-# Inline index #-}

-- | Produce 'Just' and 'Index' or 'Nothing'.

maybeIndex :: forall t . KnownNat t => Int -> Maybe (Index t)
maybeIndex :: Int -> Maybe (Index t)
maybeIndex Int
i
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n    = Index t -> Maybe (Index t)
forall a. a -> Maybe a
Just (Index t -> Maybe (Index t))
-> (Int -> Index t) -> Int -> Maybe (Index t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Index t
forall (t :: Nat). Int -> Index t
Index (Int -> Maybe (Index t)) -> Int -> Maybe (Index t)
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n
  | Bool
otherwise = Maybe (Index t)
forall a. Maybe a
Nothing
  where n :: Int
n = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy t -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy t
forall k (t :: k). Proxy t
Proxy :: Proxy t)
{-# Inline maybeIndex #-}

instance KnownNat t => Num (Index t) where
  Index Int
a + :: Index t -> Index t -> Index t
+ Index Int
b = String -> Index t
forall a. HasCallStack => String -> a
error (String -> Index t) -> String -> Index t
forall a b. (a -> b) -> a -> b
$ (String, Int, Int) -> String
forall a. Show a => a -> String
show (String
" Index.(+) not implemented, use (+.)",Int
a,Int
b) -- index $ a + b
  Index Int
a - :: Index t -> Index t -> Index t
- Index Int
b = String -> Index t
forall a. HasCallStack => String -> a
error (String -> Index t) -> String -> Index t
forall a b. (a -> b) -> a -> b
$ (String, Int, Int) -> String
forall a. Show a => a -> String
show (String
" Index.(-) not implemented, use (-.)",Int
a,Int
b) -- index $ a - b
  Index Int
a * :: Index t -> Index t -> Index t
* Index Int
b = String -> Index t
forall a. HasCallStack => String -> a
error (String -> Index t) -> String -> Index t
forall a b. (a -> b) -> a -> b
$ (String, Int, Int) -> String
forall a. Show a => a -> String
show (String
" Index.(*) not implemented", Int
a,Int
b) -- index $ a * b
  negate :: Index t -> Index t
negate = String -> Index t -> Index t
forall a. HasCallStack => String -> a
error String
"Indices are natural numbers"
  abs :: Index t -> Index t
abs = Index t -> Index t
forall a. a -> a
id
  signum :: Index t -> Index t
signum = Int -> Index t
forall (t :: Nat). KnownNat t => Int -> Index t
index (Int -> Index t) -> (Index t -> Int) -> Index t -> Index t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Num a => a -> a
signum (Int -> Int) -> (Index t -> Int) -> Index t -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index t -> Int
forall (t :: Nat). Index t -> Int
getIndex
  fromInteger :: Integer -> Index t
fromInteger = Int -> Index t
forall (t :: Nat). KnownNat t => Int -> Index t
index (Int -> Index t) -> (Integer -> Int) -> Integer -> Index t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
  {-# Inline fromInteger #-}

instance NFData (Index t) where
  rnf :: Index t -> ()
rnf = Int -> ()
forall a. NFData a => a -> ()
rnf (Int -> ()) -> (Index t -> Int) -> Index t -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index t -> Int
forall (t :: Nat). Index t -> Int
getIndex
  {-# Inline rnf #-}

instance Binary    (Index t)
instance Serialize (Index t)
instance ToJSON    (Index t)
instance FromJSON  (Index t)
instance Hashable  (Index t)

derivingUnbox "Index"
  [t| forall t . Index t -> Int |]  [| getIndex |]  [| Index |]

instance forall t . KnownNat t => PA.Index (Index t) where
  newtype LimitType (Index t) = LtIndex Int
  linearIndex :: LimitType (Index t) -> Index t -> Int
linearIndex (LtIndex k) (Index Int
z) = Int
z
  {-# INLINE linearIndex #-}
  size :: LimitType (Index t) -> Int
size (LtIndex h) = Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
  {-# INLINE size #-}
  inBounds :: LimitType (Index t) -> Index t -> Bool
inBounds (LtIndex h) (Index 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 :: Index t
zeroBound = Int -> Index t
forall (t :: Nat). Int -> Index t
Index Int
0
  {-# Inline zeroBound #-}
  zeroBound' :: LimitType (Index t)
zeroBound' = Int -> LimitType (Index t)
forall (t :: Nat). Int -> LimitType (Index t)
LtIndex Int
0
  {-# Inline zeroBound' #-}
  totalSize :: LimitType (Index t) -> [Integer]
totalSize (LtIndex k) = [Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k]
  {-# Inline totalSize #-}
  fromLinearIndex :: LimitType (Index t) -> Int -> Index t
fromLinearIndex LimitType (Index t)
_ = Int -> Index t
forall (t :: Nat). Int -> Index t
Index
  {-# Inline [0] fromLinearIndex #-}
  showBound :: LimitType (Index t) -> [String]
showBound (LtIndex k) = [String
"LtIndex " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
k]
  showIndex :: Index t -> [String]
showIndex (Index Int
k) = [String
"Index " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
k]

instance (KnownNat t, IndexStream z)  IndexStream (z:.Index t) where
  streamUp :: LimitType (z :. Index t)
-> LimitType (z :. Index t) -> Stream m (z :. Index t)
streamUp (ls:..LtIndex lf) (hs:..LtIndex ht) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. Index t)))
-> Stream m z
-> Stream m (z :. Index t)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten z -> m (z, Int)
mk (z, Int) -> m (Step (z, Int) (z :. Index t))
step (Stream m z -> Stream m (z :. Index t))
-> Stream m z -> Stream m (z :. Index t)
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
    where mk :: z -> m (z, Int)
mk z
z = (z, Int) -> m (z, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (z
z,Int
lf)
          step :: (z, Int) -> m (Step (z, Int) (z :. Index t))
step (z
z,Int
k)
            | Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
ht    = Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t)))
-> Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall a b. (a -> b) -> a -> b
$ Step (z, Int) (z :. Index t)
forall s a. Step s a
Done
            | Bool
otherwise = Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t)))
-> Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall a b. (a -> b) -> a -> b
$ (z :. Index t) -> (z, Int) -> Step (z, Int) (z :. Index t)
forall a s. a -> s -> Step s a
Yield (z
zz -> Index t -> z :. Index t
forall a b. a -> b -> a :. b
:.Int -> Index t
forall (t :: Nat). Int -> Index t
Index Int
k) (z
z,Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
          {-# Inline [0] mk   #-}
          {-# Inline [0] step #-}
  {-# Inline streamUp #-}
  streamDown :: LimitType (z :. Index t)
-> LimitType (z :. Index t) -> Stream m (z :. Index t)
streamDown (ls:..LtIndex lf) (hs:..LtIndex ht) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. Index t)))
-> Stream m z
-> Stream m (z :. Index t)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten z -> m (z, Int)
mk (z, Int) -> m (Step (z, Int) (z :. Index t))
step (Stream m z -> Stream m (z :. Index t))
-> Stream m z -> Stream m (z :. Index t)
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
    where mk :: z -> m (z, Int)
mk z
z = (z, Int) -> m (z, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (z
z,Int
ht)
          step :: (z, Int) -> m (Step (z, Int) (z :. Index t))
step (z
z,Int
k)
            | Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lf    = Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t)))
-> Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall a b. (a -> b) -> a -> b
$ Step (z, Int) (z :. Index t)
forall s a. Step s a
Done
            | Bool
otherwise = Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t)))
-> Step (z, Int) (z :. Index t) -> m (Step (z, Int) (z :. Index t))
forall a b. (a -> b) -> a -> b
$ (z :. Index t) -> (z, Int) -> Step (z, Int) (z :. Index t)
forall a s. a -> s -> Step s a
Yield (z
zz -> Index t -> z :. Index t
forall a b. a -> b -> a :. b
:.Int -> Index t
forall (t :: Nat). Int -> Index t
Index Int
k) (z
z,Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
          {-# Inline [0] mk   #-}
          {-# Inline [0] step #-}
  {-# Inline streamDown #-}

instance (KnownNat t)  IndexStream (Index t) where
  streamUp :: LimitType (Index t) -> LimitType (Index t) -> Stream m (Index t)
streamUp LimitType (Index t)
l LimitType (Index t)
h = ((Z :. Index t) -> Index t)
-> Stream m (Z :. Index t) -> Stream m (Index t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.Index t
i) -> Index t
i) (Stream m (Z :. Index t) -> Stream m (Index t))
-> Stream m (Z :. Index t) -> Stream m (Index t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. Index t)
-> LimitType (Z :. Index t) -> Stream m (Z :. Index t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamUp (LimitType Z
ZZLimitType Z -> LimitType (Index t) -> LimitType (Z :. Index t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Index t)
l) (LimitType Z
ZZLimitType Z -> LimitType (Index t) -> LimitType (Z :. Index t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Index t)
h)
  {-# INLINE streamUp #-}
  streamDown :: LimitType (Index t) -> LimitType (Index t) -> Stream m (Index t)
streamDown LimitType (Index t)
l LimitType (Index t)
h = ((Z :. Index t) -> Index t)
-> Stream m (Z :. Index t) -> Stream m (Index t)
forall (m :: * -> *) a b.
Monad m =>
(a -> b) -> Stream m a -> Stream m b
SM.map (\(Z
Z:.Index t
i) -> Index t
i) (Stream m (Z :. Index t) -> Stream m (Index t))
-> Stream m (Z :. Index t) -> Stream m (Index t)
forall a b. (a -> b) -> a -> b
$ LimitType (Z :. Index t)
-> LimitType (Z :. Index t) -> Stream m (Z :. Index t)
forall i (m :: * -> *).
(IndexStream i, Monad m) =>
LimitType i -> LimitType i -> Stream m i
streamDown (LimitType Z
ZZLimitType Z -> LimitType (Index t) -> LimitType (Z :. Index t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Index t)
l) (LimitType Z
ZZLimitType Z -> LimitType (Index t) -> LimitType (Z :. Index t)
forall zs z. LimitType zs -> LimitType z -> LimitType (zs :. z)
:..LimitType (Index t)
h)
  {-# INLINE streamDown #-}

instance Arbitrary (Index t) where
  arbitrary :: Gen (Index t)
arbitrary = Int -> Index t
forall (t :: Nat). Int -> Index t
Index (Int -> Index t) -> Gen Int -> Gen (Index t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
  shrink :: Index t -> [Index t]
shrink (Index Int
j) = (Int -> Index t) -> [Int] -> [Index t]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Index t
forall (t :: Nat). Int -> Index t
Index ([Int] -> [Index t]) -> [Int] -> [Index t]
forall a b. (a -> b) -> a -> b
$ Int -> [Int]
forall a. Arbitrary a => a -> [a]
shrink Int
j