PrimitiveArray-0.7.1.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 t p 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 t0 p0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (PInt t0 p0) -> m (Vector (PInt t0 p0)) #

basicUnsafeThaw :: PrimMonad m => Vector (PInt t0 p0) -> m (Mutable Vector (PrimState m) (PInt t0 p0)) #

basicLength :: Vector (PInt t0 p0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (PInt t0 p0) -> Vector (PInt t0 p0) #

basicUnsafeIndexM :: Monad m => Vector (PInt t0 p0) -> Int -> m (PInt t0 p0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (PInt t0 p0) -> Vector (PInt t0 p0) -> m () #

elemseq :: Vector (PInt t0 p0) -> PInt t0 p0 -> b -> b #

MVector MVector (PInt t0 p0) Source # 

Methods

basicLength :: MVector s (PInt t0 p0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PInt t0 p0) -> MVector s (PInt t0 p0) #

basicOverlaps :: MVector s (PInt t0 p0) -> MVector s (PInt t0 p0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PInt t0 p0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> PInt t0 p0 -> m (MVector (PrimState m) (PInt t0 p0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> Int -> m (PInt t0 p0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> Int -> PInt t0 p0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> PInt t0 p0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> MVector (PrimState m) (PInt t0 p0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> MVector (PrimState m) (PInt t0 p0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (PInt t0 p0) -> Int -> m (MVector (PrimState m) (PInt t0 p0)) #

Enum (PInt t p) Source # 

Methods

succ :: PInt t p -> PInt t p #

pred :: PInt t p -> PInt t p #

toEnum :: Int -> PInt t p #

fromEnum :: PInt t p -> Int #

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

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

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

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

Eq (PInt t p) Source # 

Methods

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

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

Integral (PInt t p) Source # 

Methods

quot :: PInt t p -> PInt t p -> PInt t p #

rem :: PInt t p -> PInt t p -> PInt t p #

div :: PInt t p -> PInt t p -> PInt t p #

mod :: PInt t p -> PInt t p -> PInt t p #

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

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

toInteger :: PInt t p -> Integer #

(Data t, Data p) => Data (PInt t p) Source # 

Methods

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

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

toConstr :: PInt t p -> Constr #

dataTypeOf :: PInt t p -> DataType #

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

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

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

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

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

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

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

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

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

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

Num (PInt t p) Source # 

Methods

(+) :: PInt t p -> PInt t p -> PInt t p #

(-) :: PInt t p -> PInt t p -> PInt t p #

(*) :: PInt t p -> PInt t p -> PInt t p #

negate :: PInt t p -> PInt t p #

abs :: PInt t p -> PInt t p #

signum :: PInt t p -> PInt t p #

fromInteger :: Integer -> PInt t p #

Ord (PInt t p) Source # 

Methods

compare :: PInt t p -> PInt t p -> Ordering #

(<) :: PInt t p -> PInt t p -> Bool #

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

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

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

max :: PInt t p -> PInt t p -> PInt t p #

min :: PInt t p -> PInt t p -> PInt t p #

Read (PInt t p) Source # 

Methods

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

readList :: ReadS [PInt t p] #

readPrec :: ReadPrec (PInt t p) #

readListPrec :: ReadPrec [PInt t p] #

Real (PInt t p) Source # 

Methods

toRational :: PInt t p -> Rational #

Show (PInt t p) Source # 

Methods

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

show :: PInt t p -> String #

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

Ix (PInt t p) Source # 

Methods

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

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

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

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

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

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

Generic (PInt t p) Source # 

Associated Types

type Rep (PInt t p) :: * -> * #

Methods

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

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

Hashable (PInt t p) Source # 

Methods

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

hash :: PInt t p -> Int #

FromJSON (PInt t p) Source # 

Methods

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

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

ToJSON (PInt t p) Source # 

Methods

toJSON :: PInt t p -> Value #

toEncoding :: PInt t p -> Encoding #

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

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

Binary (PInt t p) Source # 

Methods

put :: PInt t p -> Put #

get :: Get (PInt t p) #

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

Serialize (PInt t p) Source # 

Methods

put :: Putter (PInt t p) #

get :: Get (PInt t p) #

NFData (PInt t p) Source # 

Methods

rnf :: PInt t p -> () #

Unbox (PInt t0 p0) Source # 
IndexStream z => IndexStream ((:.) z (PInt C p)) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

IndexStream (PInt C p) Source # 

Methods

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

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

IndexStream (PInt O p) Source # 

Methods

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

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

IndexStream (PInt I p) Source # 

Methods

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

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

Index (PInt t p) Source # 

Methods

linearIndex :: PInt t p -> PInt t p -> PInt t p -> Int Source #

smallestLinearIndex :: PInt t p -> Int Source #

largestLinearIndex :: PInt t p -> Int Source #

size :: PInt t p -> PInt t p -> Int Source #

inBounds :: PInt t p -> PInt t p -> PInt t p -> Bool Source #

data MVector s (PInt t0 p0) Source # 
data MVector s (PInt t0 p0) = MV_PInt (MVector s Int)
type Rep (PInt t p) Source # 
type Rep (PInt t p) = D1 (MetaData "PInt" "Data.PrimitiveArray.Index.PhantomInt" "PrimitiveArray-0.7.1.0-B4A9oZDNxHW51HjshiHgYe" True) (C1 (MetaCons "PInt" PrefixI True) (S1 (MetaSel (Just Symbol "getPInt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PInt t0 p0) Source # 
data Vector (PInt t0 p0) = V_PInt (Vector Int)

streamUpMk :: Monad m => t2 -> t -> t1 -> m (t1, t2) Source #

streamUpStep :: (Ord t2, Num t2, Monad m) => t -> t2 -> (t1, t2) -> m (Step (t1, t2) ((:.) t1 t2)) Source #

streamDownMk :: Monad m => t -> t2 -> t1 -> m (t1, t2) Source #

streamDownStep :: (Ord t2, Num t2, Monad m) => t2 -> t -> (t1, t2) -> m (Step (t1, t2) ((:.) t1 t2)) Source #