-- | A linear 0-based int-index with a phantom type.

module Data.PrimitiveArray.Index.PhantomInt where

import Control.DeepSeq (NFData(..))
import Data.Aeson (FromJSON,FromJSONKey,ToJSON,ToJSONKey)
import Data.Binary (Binary)
import Data.Data
import Data.Hashable (Hashable)
import Data.Ix(Ix)
import Data.Serialize (Serialize)
import Data.Typeable
import Data.Vector.Fusion.Stream.Monadic (map,Step(..),flatten)
import Data.Vector.Unboxed.Deriving
import GHC.Generics (Generic)
import Prelude hiding (map)

import Data.PrimitiveArray.Index.Class
import Data.PrimitiveArray.Index.IOC



-- | A 'PInt' behaves exactly like an @Int@, but has an attached phantom
-- type @p@. In particular, the @Index@ and @IndexStream@ instances are the
-- same as for raw @Int@s.

newtype PInt (ioc  k) (p  k) = PInt { PInt ioc p -> Int
getPInt :: Int }
  deriving stock (ReadPrec [PInt ioc p]
ReadPrec (PInt ioc p)
Int -> ReadS (PInt ioc p)
ReadS [PInt ioc p]
(Int -> ReadS (PInt ioc p))
-> ReadS [PInt ioc p]
-> ReadPrec (PInt ioc p)
-> ReadPrec [PInt ioc p]
-> Read (PInt ioc p)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (ioc :: k) (p :: k). ReadPrec [PInt ioc p]
forall k (ioc :: k) (p :: k). ReadPrec (PInt ioc p)
forall k (ioc :: k) (p :: k). Int -> ReadS (PInt ioc p)
forall k (ioc :: k) (p :: k). ReadS [PInt ioc p]
readListPrec :: ReadPrec [PInt ioc p]
$creadListPrec :: forall k (ioc :: k) (p :: k). ReadPrec [PInt ioc p]
readPrec :: ReadPrec (PInt ioc p)
$creadPrec :: forall k (ioc :: k) (p :: k). ReadPrec (PInt ioc p)
readList :: ReadS [PInt ioc p]
$creadList :: forall k (ioc :: k) (p :: k). ReadS [PInt ioc p]
readsPrec :: Int -> ReadS (PInt ioc p)
$creadsPrec :: forall k (ioc :: k) (p :: k). Int -> ReadS (PInt ioc p)
Read,Int -> PInt ioc p -> ShowS
[PInt ioc p] -> ShowS
PInt ioc p -> String
(Int -> PInt ioc p -> ShowS)
-> (PInt ioc p -> String)
-> ([PInt ioc p] -> ShowS)
-> Show (PInt ioc p)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (ioc :: k) (p :: k). Int -> PInt ioc p -> ShowS
forall k (ioc :: k) (p :: k). [PInt ioc p] -> ShowS
forall k (ioc :: k) (p :: k). PInt ioc p -> String
showList :: [PInt ioc p] -> ShowS
$cshowList :: forall k (ioc :: k) (p :: k). [PInt ioc p] -> ShowS
show :: PInt ioc p -> String
$cshow :: forall k (ioc :: k) (p :: k). PInt ioc p -> String
showsPrec :: Int -> PInt ioc p -> ShowS
$cshowsPrec :: forall k (ioc :: k) (p :: k). Int -> PInt ioc p -> ShowS
Show,PInt ioc p -> PInt ioc p -> Bool
(PInt ioc p -> PInt ioc p -> Bool)
-> (PInt ioc p -> PInt ioc p -> Bool) -> Eq (PInt ioc p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
/= :: PInt ioc p -> PInt ioc p -> Bool
$c/= :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
== :: PInt ioc p -> PInt ioc p -> Bool
$c== :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
Eq,Eq (PInt ioc p)
Eq (PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> Ordering)
-> (PInt ioc p -> PInt ioc p -> Bool)
-> (PInt ioc p -> PInt ioc p -> Bool)
-> (PInt ioc p -> PInt ioc p -> Bool)
-> (PInt ioc p -> PInt ioc p -> Bool)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> Ord (PInt ioc p)
PInt ioc p -> PInt ioc p -> Bool
PInt ioc p -> PInt ioc p -> Ordering
PInt ioc p -> PInt ioc p -> PInt ioc p
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 (ioc :: k) (p :: k). Eq (PInt ioc p)
forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Ordering
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
min :: PInt ioc p -> PInt ioc p -> PInt ioc p
$cmin :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
max :: PInt ioc p -> PInt ioc p -> PInt ioc p
$cmax :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
>= :: PInt ioc p -> PInt ioc p -> Bool
$c>= :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
> :: PInt ioc p -> PInt ioc p -> Bool
$c> :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
<= :: PInt ioc p -> PInt ioc p -> Bool
$c<= :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
< :: PInt ioc p -> PInt ioc p -> Bool
$c< :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Bool
compare :: PInt ioc p -> PInt ioc p -> Ordering
$ccompare :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p -> Ordering
$cp1Ord :: forall k (ioc :: k) (p :: k). Eq (PInt ioc p)
Ord,(forall x. PInt ioc p -> Rep (PInt ioc p) x)
-> (forall x. Rep (PInt ioc p) x -> PInt ioc p)
-> Generic (PInt ioc p)
forall x. Rep (PInt ioc p) x -> PInt ioc p
forall x. PInt ioc p -> Rep (PInt ioc p) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (ioc :: k) (p :: k) x. Rep (PInt ioc p) x -> PInt ioc p
forall k (ioc :: k) (p :: k) x. PInt ioc p -> Rep (PInt ioc p) x
$cto :: forall k (ioc :: k) (p :: k) x. Rep (PInt ioc p) x -> PInt ioc p
$cfrom :: forall k (ioc :: k) (p :: k) x. PInt ioc p -> Rep (PInt ioc p) x
Generic,Typeable (PInt ioc p)
DataType
Constr
Typeable (PInt ioc p)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (PInt ioc p))
-> (PInt ioc p -> Constr)
-> (PInt ioc p -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (PInt ioc p)))
-> ((forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r)
-> (forall u. (forall d. Data d => d -> u) -> PInt ioc p -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p))
-> Data (PInt ioc p)
PInt ioc p -> DataType
PInt ioc p -> Constr
(forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PInt ioc p)
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) -> PInt ioc p -> u
forall u. (forall d. Data d => d -> u) -> PInt ioc p -> [u]
forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
Typeable (PInt ioc p)
forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
PInt ioc p -> DataType
forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
PInt ioc p -> Constr
forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
(forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p
forall k (ioc :: k) (p :: k) u.
(Typeable ioc, Typeable p, Typeable k) =>
Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u
forall k (ioc :: k) (p :: k) u.
(Typeable ioc, Typeable p, Typeable k) =>
(forall d. Data d => d -> u) -> PInt ioc p -> [u]
forall k (ioc :: k) (p :: k) r r'.
(Typeable ioc, Typeable p, Typeable k) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
forall k (ioc :: k) (p :: k) r r'.
(Typeable ioc, Typeable p, Typeable k) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
forall k (ioc :: k) (p :: k) (m :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Monad m) =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
forall k (ioc :: k) (p :: k) (m :: * -> *).
(Typeable ioc, Typeable p, Typeable k, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
forall k (ioc :: k) (p :: k) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PInt ioc p)
forall k (ioc :: k) (p :: k) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p)
forall k (ioc :: k) (p :: k) (t :: * -> *) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p))
forall k (ioc :: k) (p :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PInt ioc p))
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PInt ioc p)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PInt ioc p))
$cPInt :: Constr
$tPInt :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
$cgmapMo :: forall k (ioc :: k) (p :: k) (m :: * -> *).
(Typeable ioc, Typeable p, Typeable k, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
gmapMp :: (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
$cgmapMp :: forall k (ioc :: k) (p :: k) (m :: * -> *).
(Typeable ioc, Typeable p, Typeable k, MonadPlus m) =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
gmapM :: (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
$cgmapM :: forall k (ioc :: k) (p :: k) (m :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Monad m) =>
(forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p)
gmapQi :: Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u
$cgmapQi :: forall k (ioc :: k) (p :: k) u.
(Typeable ioc, Typeable p, Typeable k) =>
Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u
gmapQ :: (forall d. Data d => d -> u) -> PInt ioc p -> [u]
$cgmapQ :: forall k (ioc :: k) (p :: k) u.
(Typeable ioc, Typeable p, Typeable k) =>
(forall d. Data d => d -> u) -> PInt ioc p -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
$cgmapQr :: forall k (ioc :: k) (p :: k) r r'.
(Typeable ioc, Typeable p, Typeable k) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
$cgmapQl :: forall k (ioc :: k) (p :: k) r r'.
(Typeable ioc, Typeable p, Typeable k) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r
gmapT :: (forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p
$cgmapT :: forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
(forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PInt ioc p))
$cdataCast2 :: forall k (ioc :: k) (p :: k) (t :: * -> * -> *) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PInt ioc p))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p))
$cdataCast1 :: forall k (ioc :: k) (p :: k) (t :: * -> *) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p))
dataTypeOf :: PInt ioc p -> DataType
$cdataTypeOf :: forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
PInt ioc p -> DataType
toConstr :: PInt ioc p -> Constr
$ctoConstr :: forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
PInt ioc p -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PInt ioc p)
$cgunfold :: forall k (ioc :: k) (p :: k) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PInt ioc p)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p)
$cgfoldl :: forall k (ioc :: k) (p :: k) (c :: * -> *).
(Typeable ioc, Typeable p, Typeable k) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p)
$cp1Data :: forall k (ioc :: k) (p :: k).
(Typeable ioc, Typeable p, Typeable k) =>
Typeable (PInt ioc p)
Data,Typeable,Ord (PInt ioc p)
Ord (PInt ioc p)
-> ((PInt ioc p, PInt ioc p) -> [PInt ioc p])
-> ((PInt ioc p, PInt ioc p) -> PInt ioc p -> Int)
-> ((PInt ioc p, PInt ioc p) -> PInt ioc p -> Int)
-> ((PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool)
-> ((PInt ioc p, PInt ioc p) -> Int)
-> ((PInt ioc p, PInt ioc p) -> Int)
-> Ix (PInt ioc p)
(PInt ioc p, PInt ioc p) -> Int
(PInt ioc p, PInt ioc p) -> [PInt ioc p]
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool
(PInt ioc p, PInt ioc p) -> PInt ioc p -> 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 k (ioc :: k) (p :: k). Ord (PInt ioc p)
forall k (ioc :: k) (p :: k). (PInt ioc p, PInt ioc p) -> Int
forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> [PInt ioc p]
forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool
forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Int
unsafeRangeSize :: (PInt ioc p, PInt ioc p) -> Int
$cunsafeRangeSize :: forall k (ioc :: k) (p :: k). (PInt ioc p, PInt ioc p) -> Int
rangeSize :: (PInt ioc p, PInt ioc p) -> Int
$crangeSize :: forall k (ioc :: k) (p :: k). (PInt ioc p, PInt ioc p) -> Int
inRange :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool
$cinRange :: forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool
unsafeIndex :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int
$cunsafeIndex :: forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Int
index :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int
$cindex :: forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> PInt ioc p -> Int
range :: (PInt ioc p, PInt ioc p) -> [PInt ioc p]
$crange :: forall k (ioc :: k) (p :: k).
(PInt ioc p, PInt ioc p) -> [PInt ioc p]
$cp1Ix :: forall k (ioc :: k) (p :: k). Ord (PInt ioc p)
Ix)
  deriving newtype (Num (PInt ioc p)
Ord (PInt ioc p)
Num (PInt ioc p)
-> Ord (PInt ioc p)
-> (PInt ioc p -> Rational)
-> Real (PInt ioc p)
PInt ioc p -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
forall k (ioc :: k) (p :: k). Num (PInt ioc p)
forall k (ioc :: k) (p :: k). Ord (PInt ioc p)
forall k (ioc :: k) (p :: k). PInt ioc p -> Rational
toRational :: PInt ioc p -> Rational
$ctoRational :: forall k (ioc :: k) (p :: k). PInt ioc p -> Rational
$cp2Real :: forall k (ioc :: k) (p :: k). Ord (PInt ioc p)
$cp1Real :: forall k (ioc :: k) (p :: k). Num (PInt ioc p)
Real,Integer -> PInt ioc p
PInt ioc p -> PInt ioc p
PInt ioc p -> PInt ioc p -> PInt ioc p
(PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p)
-> (Integer -> PInt ioc p)
-> Num (PInt ioc p)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall k (ioc :: k) (p :: k). Integer -> PInt ioc p
forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
fromInteger :: Integer -> PInt ioc p
$cfromInteger :: forall k (ioc :: k) (p :: k). Integer -> PInt ioc p
signum :: PInt ioc p -> PInt ioc p
$csignum :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
abs :: PInt ioc p -> PInt ioc p
$cabs :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
negate :: PInt ioc p -> PInt ioc p
$cnegate :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
* :: PInt ioc p -> PInt ioc p -> PInt ioc p
$c* :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
- :: PInt ioc p -> PInt ioc p -> PInt ioc p
$c- :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
+ :: PInt ioc p -> PInt ioc p -> PInt ioc p
$c+ :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
Num,Int -> PInt ioc p
PInt ioc p -> Int
PInt ioc p -> [PInt ioc p]
PInt ioc p -> PInt ioc p
PInt ioc p -> PInt ioc p -> [PInt ioc p]
PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p]
(PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p)
-> (Int -> PInt ioc p)
-> (PInt ioc p -> Int)
-> (PInt ioc p -> [PInt ioc p])
-> (PInt ioc p -> PInt ioc p -> [PInt ioc p])
-> (PInt ioc p -> PInt ioc p -> [PInt ioc p])
-> (PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p])
-> Enum (PInt ioc p)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
forall k (ioc :: k) (p :: k). PInt ioc p -> Int
forall k (ioc :: k) (p :: k). PInt ioc p -> [PInt ioc p]
forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> [PInt ioc p]
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p]
enumFromThenTo :: PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p]
$cenumFromThenTo :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p]
enumFromTo :: PInt ioc p -> PInt ioc p -> [PInt ioc p]
$cenumFromTo :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> [PInt ioc p]
enumFromThen :: PInt ioc p -> PInt ioc p -> [PInt ioc p]
$cenumFromThen :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> [PInt ioc p]
enumFrom :: PInt ioc p -> [PInt ioc p]
$cenumFrom :: forall k (ioc :: k) (p :: k). PInt ioc p -> [PInt ioc p]
fromEnum :: PInt ioc p -> Int
$cfromEnum :: forall k (ioc :: k) (p :: k). PInt ioc p -> Int
toEnum :: Int -> PInt ioc p
$ctoEnum :: forall k (ioc :: k) (p :: k). Int -> PInt ioc p
pred :: PInt ioc p -> PInt ioc p
$cpred :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
succ :: PInt ioc p -> PInt ioc p
$csucc :: forall k (ioc :: k) (p :: k). PInt ioc p -> PInt ioc p
Enum,Enum (PInt ioc p)
Real (PInt ioc p)
Real (PInt ioc p)
-> Enum (PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> PInt ioc p)
-> (PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p))
-> (PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p))
-> (PInt ioc p -> Integer)
-> Integral (PInt ioc p)
PInt ioc p -> Integer
PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
PInt ioc p -> PInt ioc p -> PInt ioc p
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
forall k (ioc :: k) (p :: k). Enum (PInt ioc p)
forall k (ioc :: k) (p :: k). Real (PInt ioc p)
forall k (ioc :: k) (p :: k). PInt ioc p -> Integer
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
toInteger :: PInt ioc p -> Integer
$ctoInteger :: forall k (ioc :: k) (p :: k). PInt ioc p -> Integer
divMod :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
$cdivMod :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
quotRem :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
$cquotRem :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p)
mod :: PInt ioc p -> PInt ioc p -> PInt ioc p
$cmod :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
div :: PInt ioc p -> PInt ioc p -> PInt ioc p
$cdiv :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
rem :: PInt ioc p -> PInt ioc p -> PInt ioc p
$crem :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
quot :: PInt ioc p -> PInt ioc p -> PInt ioc p
$cquot :: forall k (ioc :: k) (p :: k).
PInt ioc p -> PInt ioc p -> PInt ioc p
$cp2Integral :: forall k (ioc :: k) (p :: k). Enum (PInt ioc p)
$cp1Integral :: forall k (ioc :: k) (p :: k). Real (PInt ioc p)
Integral)

pIntI :: Int -> PInt I p
pIntI :: Int -> PInt I p
pIntI = Int -> PInt I p
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
PInt
{-# Inline pIntI #-}

pIntO :: Int -> PInt O p
pIntO :: Int -> PInt O p
pIntO = Int -> PInt O p
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
PInt
{-# Inline pIntO #-}

pIntC :: Int -> PInt C p
pIntC :: Int -> PInt C p
pIntC = Int -> PInt C p
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
PInt
{-# Inline pIntC #-}

derivingUnbox "PInt"
  [t| forall t p . PInt t p -> Int |]  [| getPInt |]  [| PInt |]

instance Binary       (PInt t p)
instance Serialize    (PInt t p)
instance FromJSON     (PInt t p)
instance FromJSONKey  (PInt t p)
instance ToJSON       (PInt t p)
instance ToJSONKey    (PInt t p)
instance Hashable     (PInt t p)
instance NFData       (PInt t p)

instance Index (PInt t p) where
  newtype LimitType (PInt t p) = LtPInt Int
  linearIndex :: LimitType (PInt t p) -> PInt t p -> Int
linearIndex LimitType (PInt t p)
_ (PInt Int
k) = Int
k
  {-# Inline linearIndex #-}
  size :: LimitType (PInt t p) -> Int
size (LtPInt h) = Int
hInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1
  {-# Inline size #-}
  inBounds :: LimitType (PInt t p) -> PInt t p -> Bool
inBounds (LtPInt h) (PInt Int
k) = Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
k Bool -> Bool -> Bool
&& Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
h
  {-# Inline inBounds #-}
  fromLinearIndex :: LimitType (PInt t p) -> Int -> PInt t p
fromLinearIndex = String -> LimitType (PInt t p) -> Int -> PInt t p
forall a. HasCallStack => String -> a
error String
"implement me"
  zeroBound :: PInt t p
zeroBound = String -> PInt t p
forall a. HasCallStack => String -> a
error String
"implement me"
  zeroBound' :: LimitType (PInt t p)
zeroBound' = String -> LimitType (PInt t p)
forall a. HasCallStack => String -> a
error String
"implement me"
  totalSize :: LimitType (PInt t p) -> [Integer]
totalSize = String -> LimitType (PInt t p) -> [Integer]
forall a. HasCallStack => String -> a
error String
"implement me"
  showBound :: LimitType (PInt t p) -> [String]
showBound = String -> LimitType (PInt t p) -> [String]
forall a. HasCallStack => String -> a
error String
"implement me"
  showIndex :: PInt t p -> [String]
showIndex = String -> PInt t p -> [String]
forall a. HasCallStack => String -> a
error String
"implement me"

deriving instance Show    (LimitType (PInt t p))
deriving instance Read    (LimitType (PInt t p))
deriving instance Eq      (LimitType (PInt t p))
deriving instance Generic (LimitType (PInt t p))

instance IndexStream z => IndexStream (z:.PInt I p) where
  streamUp :: LimitType (z :. PInt I p)
-> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p)
streamUp   (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt I p)))
-> Stream m z
-> Stream m (z :. PInt I p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) b p a. Monad m => b -> p -> a -> m (a, b)
streamUpMk   Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt I p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
p -> Int -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamUpStep   Int
l Int
h) (Stream m z -> Stream m (z :. PInt I p))
-> Stream m z -> Stream m (z :. PInt I p)
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 :. PInt I p)
-> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p)
streamDown (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt I p)))
-> Stream m z
-> Stream m (z :. PInt I p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) p b a. Monad m => p -> b -> a -> m (a, b)
streamDownMk Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt I p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
Int -> p -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamDownStep Int
l Int
h) (Stream m z -> Stream m (z :. PInt I p))
-> Stream m z -> Stream m (z :. PInt I p)
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 streamUp   #-}
  {-# Inline streamDown #-}

instance IndexStream z => IndexStream (z:.PInt O p) where
  streamUp :: LimitType (z :. PInt O p)
-> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p)
streamUp   (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt O p)))
-> Stream m z
-> Stream m (z :. PInt O p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) p b a. Monad m => p -> b -> a -> m (a, b)
streamDownMk Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt O p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
Int -> p -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamDownStep Int
l Int
h) (Stream m z -> Stream m (z :. PInt O p))
-> Stream m z -> Stream m (z :. PInt O p)
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 :. PInt O p)
-> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p)
streamDown (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt O p)))
-> Stream m z
-> Stream m (z :. PInt O p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) b p a. Monad m => b -> p -> a -> m (a, b)
streamUpMk   Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt O p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
p -> Int -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamUpStep   Int
l Int
h) (Stream m z -> Stream m (z :. PInt O p))
-> Stream m z -> Stream m (z :. PInt O p)
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 streamUp   #-}
  {-# Inline streamDown #-}

instance IndexStream z => IndexStream (z:.PInt C p) where
  streamUp :: LimitType (z :. PInt C p)
-> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p)
streamUp   (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt C p)))
-> Stream m z
-> Stream m (z :. PInt C p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) b p a. Monad m => b -> p -> a -> m (a, b)
streamUpMk   Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt C p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
p -> Int -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamUpStep   Int
l Int
h) (Stream m z -> Stream m (z :. PInt C p))
-> Stream m z -> Stream m (z :. PInt C p)
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 :. PInt C p)
-> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p)
streamDown (ls:..LtPInt l) (hs:..LtPInt h) = (z -> m (z, Int))
-> ((z, Int) -> m (Step (z, Int) (z :. PInt C p)))
-> Stream m z
-> Stream m (z :. PInt C p)
forall (m :: * -> *) a s b.
Monad m =>
(a -> m s) -> (s -> m (Step s b)) -> Stream m a -> Stream m b
flatten (Int -> Int -> z -> m (z, Int)
forall (m :: * -> *) p b a. Monad m => p -> b -> a -> m (a, b)
streamDownMk Int
l Int
h) (Int -> Int -> (z, Int) -> m (Step (z, Int) (z :. PInt C p))
forall k (m :: * -> *) p a (ioc :: k) (p :: k).
Monad m =>
Int -> p -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamDownStep Int
l Int
h) (Stream m z -> Stream m (z :. PInt C p))
-> Stream m z -> Stream m (z :. PInt C p)
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 streamUp   #-}
  {-# Inline streamDown #-}

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

streamUpMk :: b -> p -> a -> m (a, b)
streamUpMk b
l p
h a
z = (a, b) -> m (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
z,b
l)
{-# Inline [0] streamUpMk #-}

streamUpStep :: p -> Int -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamUpStep p
l Int
h (a
z,Int
k)
  | Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
h     = Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (a, Int) (a :. PInt ioc p)
 -> m (Step (a, Int) (a :. PInt ioc p)))
-> Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall a b. (a -> b) -> a -> b
$ Step (a, Int) (a :. PInt ioc p)
forall s a. Step s a
Done
  | Bool
otherwise = Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (a, Int) (a :. PInt ioc p)
 -> m (Step (a, Int) (a :. PInt ioc p)))
-> Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall a b. (a -> b) -> a -> b
$ (a :. PInt ioc p) -> (a, Int) -> Step (a, Int) (a :. PInt ioc p)
forall a s. a -> s -> Step s a
Yield (a
za -> PInt ioc p -> a :. PInt ioc p
forall a b. a -> b -> a :. b
:.Int -> PInt ioc p
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
PInt Int
k) (a
z,Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# Inline [0] streamUpStep #-}

streamDownMk :: p -> b -> a -> m (a, b)
streamDownMk p
l b
h a
z = (a, b) -> m (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
z,b
h)
{-# Inline [0] streamDownMk #-}

streamDownStep :: Int -> p -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p))
streamDownStep Int
l p
h (a
z,Int
k)
  | Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l     = Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (a, Int) (a :. PInt ioc p)
 -> m (Step (a, Int) (a :. PInt ioc p)))
-> Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall a b. (a -> b) -> a -> b
$ Step (a, Int) (a :. PInt ioc p)
forall s a. Step s a
Done
  | Bool
otherwise = Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (a, Int) (a :. PInt ioc p)
 -> m (Step (a, Int) (a :. PInt ioc p)))
-> Step (a, Int) (a :. PInt ioc p)
-> m (Step (a, Int) (a :. PInt ioc p))
forall a b. (a -> b) -> a -> b
$ (a :. PInt ioc p) -> (a, Int) -> Step (a, Int) (a :. PInt ioc p)
forall a s. a -> s -> Step s a
Yield (a
za -> PInt ioc p -> a :. PInt ioc p
forall a b. a -> b -> a :. b
:.Int -> PInt ioc p
forall k (ioc :: k) (p :: k). Int -> PInt ioc p
PInt Int
k) (a
z,Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
{-# Inline [0] streamDownStep #-}