PrimitiveArray-0.9.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.PhantomInt

Description

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

Synopsis

Documentation

newtype PInt (ioc :: k) (p :: k) Source #

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 Ints.

Constructors

PInt 

Fields

Instances
Vector Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (PInt t p) -> m (Vector (PInt t p)) #

basicUnsafeThaw :: PrimMonad m => Vector (PInt t p) -> m (Mutable Vector (PrimState m) (PInt t p)) #

basicLength :: Vector (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t p) -> Vector (PInt t p) #

basicUnsafeIndexM :: Monad m => Vector (PInt t p) -> Int -> m (PInt t p) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (PInt t p) -> Vector (PInt t p) -> m () #

elemseq :: Vector (PInt t p) -> PInt t p -> b -> b #

MVector MVector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

basicLength :: MVector s (PInt t p) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t p) -> MVector s (PInt t p) #

basicOverlaps :: MVector s (PInt t p) -> MVector s (PInt t p) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t p)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (PInt t p) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> PInt t p -> m (MVector (PrimState m) (PInt t p)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (PInt t p) -> Int -> m (PInt t p) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (PInt t p) -> Int -> PInt t p -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (PInt t p) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (PInt t p) -> PInt t p -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (PInt t p) -> MVector (PrimState m) (PInt t p) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (PInt t p) -> MVector (PrimState m) (PInt t p) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (PInt t p) -> Int -> m (MVector (PrimState m) (PInt t p)) #

Eq (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

(/=) :: LimitType (PInt t p) -> LimitType (PInt t p) -> Bool #

Read (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Show (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> LimitType (PInt t p) -> ShowS #

show :: LimitType (PInt t p) -> String #

showList :: [LimitType (PInt t p)] -> ShowS #

Generic (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (LimitType (PInt t p)) :: Type -> Type #

Methods

from :: LimitType (PInt t p) -> Rep (LimitType (PInt t p)) x #

to :: Rep (LimitType (PInt t p)) x -> LimitType (PInt t p) #

IndexStream z => IndexStream (z :. PInt C p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: Monad m => LimitType (z :. PInt C p) -> LimitType (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

IndexStream z => IndexStream (z :. PInt O p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: Monad m => LimitType (z :. PInt O p) -> LimitType (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

IndexStream z => IndexStream (z :. PInt I p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => LimitType (z :. PInt I p) -> LimitType (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

Enum (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

succ :: PInt ioc p -> PInt ioc p #

pred :: PInt ioc p -> PInt ioc p #

toEnum :: Int -> PInt ioc p #

fromEnum :: PInt ioc p -> Int #

enumFrom :: PInt ioc p -> [PInt ioc p] #

enumFromThen :: PInt ioc p -> PInt ioc p -> [PInt ioc p] #

enumFromTo :: PInt ioc p -> PInt ioc p -> [PInt ioc p] #

enumFromThenTo :: PInt ioc p -> PInt ioc p -> PInt ioc p -> [PInt ioc p] #

Eq (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(==) :: PInt ioc p -> PInt ioc p -> Bool #

(/=) :: PInt ioc p -> PInt ioc p -> Bool #

Integral (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

quot :: PInt ioc p -> PInt ioc p -> PInt ioc p #

rem :: PInt ioc p -> PInt ioc p -> PInt ioc p #

div :: PInt ioc p -> PInt ioc p -> PInt ioc p #

mod :: PInt ioc p -> PInt ioc p -> PInt ioc p #

quotRem :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p) #

divMod :: PInt ioc p -> PInt ioc p -> (PInt ioc p, PInt ioc p) #

toInteger :: PInt ioc p -> Integer #

(Typeable ioc, Typeable p, Typeable k) => Data (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PInt ioc p -> c (PInt ioc p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PInt ioc p) #

toConstr :: PInt ioc p -> Constr #

dataTypeOf :: PInt ioc p -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PInt ioc p)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PInt ioc p)) #

gmapT :: (forall b. Data b => b -> b) -> PInt ioc p -> PInt ioc p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PInt ioc p -> r #

gmapQ :: (forall d. Data d => d -> u) -> PInt ioc p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PInt ioc p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PInt ioc p -> m (PInt ioc p) #

Num (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

(+) :: 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 #

negate :: PInt ioc p -> PInt ioc p #

abs :: PInt ioc p -> PInt ioc p #

signum :: PInt ioc p -> PInt ioc p #

fromInteger :: Integer -> PInt ioc p #

Ord (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

compare :: 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 #

max :: PInt ioc p -> PInt ioc p -> PInt ioc p #

min :: PInt ioc p -> PInt ioc p -> PInt ioc p #

Read (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

readsPrec :: Int -> ReadS (PInt ioc p) #

readList :: ReadS [PInt ioc p] #

readPrec :: ReadPrec (PInt ioc p) #

readListPrec :: ReadPrec [PInt ioc p] #

Real (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

toRational :: PInt ioc p -> Rational #

Show (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

showsPrec :: Int -> PInt ioc p -> ShowS #

show :: PInt ioc p -> String #

showList :: [PInt ioc p] -> ShowS #

Ix (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

range :: (PInt ioc p, PInt ioc p) -> [PInt ioc p] #

index :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int #

unsafeIndex :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Int

inRange :: (PInt ioc p, PInt ioc p) -> PInt ioc p -> Bool #

rangeSize :: (PInt ioc p, PInt ioc p) -> Int #

unsafeRangeSize :: (PInt ioc p, PInt ioc p) -> Int

Generic (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

type Rep (PInt ioc p) :: Type -> Type #

Methods

from :: PInt ioc p -> Rep (PInt ioc p) x #

to :: Rep (PInt ioc p) x -> PInt ioc p #

Hashable (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

hashWithSalt :: Int -> PInt t p -> Int #

hash :: PInt t p -> Int #

ToJSON (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

toJSON :: PInt t p -> Value #

toEncoding :: PInt t p -> Encoding #

toJSONList :: [PInt t p] -> Value #

toEncodingList :: [PInt t p] -> Encoding #

ToJSONKey (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

FromJSON (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

parseJSON :: Value -> Parser (PInt t p) #

parseJSONList :: Value -> Parser [PInt t p] #

FromJSONKey (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Binary (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

put :: PInt t p -> Put #

get :: Get (PInt t p) #

putList :: [PInt t p] -> Put #

Serialize (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

put :: Putter (PInt t p) #

get :: Get (PInt t p) #

NFData (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

rnf :: PInt t p -> () #

Unbox (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

IndexStream (Z :. PInt ioc p) => IndexStream (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Methods

streamUp :: Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

streamDown :: Monad m => LimitType (PInt ioc p) -> LimitType (PInt ioc p) -> Stream m (PInt ioc p) Source #

Index (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

Associated Types

data LimitType (PInt t p) :: Type Source #

data MVector s (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data MVector s (PInt t p) = MV_PInt (MVector s Int)
type Rep (LimitType (PInt t p)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (LimitType (PInt t p)) = D1 (MetaData "LimitType" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "LtPInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
type Rep (PInt ioc p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

type Rep (PInt ioc p) = D1 (MetaData "PInt" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PInt" PrefixI True) (S1 (MetaSel (Just "getPInt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data Vector (PInt t p) = V_PInt (Vector Int)
data LimitType (PInt t p) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.PhantomInt

data LimitType (PInt t p) = LtPInt Int

streamUpMk :: Monad m => b -> p -> a -> m (a, b) Source #

streamUpStep :: Monad m => p1 -> Int -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p2)) Source #

streamDownMk :: Monad m => p -> b -> a -> m (a, b) Source #

streamDownStep :: Monad m => Int -> p1 -> (a, Int) -> m (Step (a, Int) (a :. PInt ioc p2)) Source #