numerical-0.0.0.0: core package for Numerical Haskell project

Safe HaskellNone
LanguageHaskell2010

Numerical.Array.Shape

Contents

Synopsis

Shape

data Shape (rank :: Nat) a where Source #

Constructors

Nil :: Shape Z a 
(:*) :: !a -> !(Shape r a) -> Shape (S r) a infixr 3 
Instances
(Unbox a, Unbox (Shape (S n) a)) => Vector Vector (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Shape (S (S n)) a) -> m (Vector (Shape (S (S n)) a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Shape (S (S n)) a) -> m (Mutable Vector (PrimState m) (Shape (S (S n)) a)) #

basicLength :: Vector (Shape (S (S n)) a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Shape (S (S n)) a) -> Vector (Shape (S (S n)) a) #

basicUnsafeIndexM :: Monad m => Vector (Shape (S (S n)) a) -> Int -> m (Shape (S (S n)) a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Shape (S (S n)) a) -> Vector (Shape (S (S n)) a) -> m () #

elemseq :: Vector (Shape (S (S n)) a) -> Shape (S (S n)) a -> b -> b #

Unbox a => Vector Vector (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Shape (S Z) a) -> m (Vector (Shape (S Z) a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Shape (S Z) a) -> m (Mutable Vector (PrimState m) (Shape (S Z) a)) #

basicLength :: Vector (Shape (S Z) a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Shape (S Z) a) -> Vector (Shape (S Z) a) #

basicUnsafeIndexM :: Monad m => Vector (Shape (S Z) a) -> Int -> m (Shape (S Z) a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Shape (S Z) a) -> Vector (Shape (S Z) a) -> m () #

elemseq :: Vector (Shape (S Z) a) -> Shape (S Z) a -> b -> b #

Unbox a => Vector Vector (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

(Unbox a, Unbox (Shape (S n) a)) => MVector MVector (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

basicLength :: MVector s (Shape (S (S n)) a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Shape (S (S n)) a) -> MVector s (Shape (S (S n)) a) #

basicOverlaps :: MVector s (Shape (S (S n)) a) -> MVector s (Shape (S (S n)) a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Shape (S (S n)) a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Shape (S (S n)) a -> m (MVector (PrimState m) (Shape (S (S n)) a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> Int -> m (Shape (S (S n)) a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> Int -> Shape (S (S n)) a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> Shape (S (S n)) a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> MVector (PrimState m) (Shape (S (S n)) a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> MVector (PrimState m) (Shape (S (S n)) a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Shape (S (S n)) a) -> Int -> m (MVector (PrimState m) (Shape (S (S n)) a)) #

Unbox a => MVector MVector (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

basicLength :: MVector s (Shape (S Z) a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Shape (S Z) a) -> MVector s (Shape (S Z) a) #

basicOverlaps :: MVector s (Shape (S Z) a) -> MVector s (Shape (S Z) a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Shape (S Z) a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Shape (S Z) a -> m (MVector (PrimState m) (Shape (S Z) a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> Int -> m (Shape (S Z) a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> Int -> Shape (S Z) a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> Shape (S Z) a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> MVector (PrimState m) (Shape (S Z) a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> MVector (PrimState m) (Shape (S Z) a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Shape (S Z) a) -> Int -> m (MVector (PrimState m) (Shape (S Z) a)) #

Unbox a => MVector MVector (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

basicLength :: MVector s (Shape Z a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Shape Z a) -> MVector s (Shape Z a) #

basicOverlaps :: MVector s (Shape Z a) -> MVector s (Shape Z a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Shape Z a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Shape Z a -> m (MVector (PrimState m) (Shape Z a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> Int -> m (Shape Z a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> Int -> Shape Z a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> Shape Z a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> MVector (PrimState m) (Shape Z a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> MVector (PrimState m) (Shape Z a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Shape Z a) -> Int -> m (MVector (PrimState m) (Shape Z a)) #

Functor (Shape r) => Functor (Shape (S r)) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

fmap :: (a -> b) -> Shape (S r) a -> Shape (S r) b #

(<$) :: a -> Shape (S r) b -> Shape (S r) a #

Functor (Shape Z) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

fmap :: (a -> b) -> Shape Z a -> Shape Z b #

(<$) :: a -> Shape Z b -> Shape Z a #

Applicative (Shape r) => Applicative (Shape (S r)) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

pure :: a -> Shape (S r) a #

(<*>) :: Shape (S r) (a -> b) -> Shape (S r) a -> Shape (S r) b #

liftA2 :: (a -> b -> c) -> Shape (S r) a -> Shape (S r) b -> Shape (S r) c #

(*>) :: Shape (S r) a -> Shape (S r) b -> Shape (S r) b #

(<*) :: Shape (S r) a -> Shape (S r) b -> Shape (S r) a #

Applicative (Shape Z) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

pure :: a -> Shape Z a #

(<*>) :: Shape Z (a -> b) -> Shape Z a -> Shape Z b #

liftA2 :: (a -> b -> c) -> Shape Z a -> Shape Z b -> Shape Z c #

(*>) :: Shape Z a -> Shape Z b -> Shape Z b #

(<*) :: Shape Z a -> Shape Z b -> Shape Z a #

Foldable (Shape (S r)) => Foldable (Shape (S (S r))) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

fold :: Monoid m => Shape (S (S r)) m -> m #

foldMap :: Monoid m => (a -> m) -> Shape (S (S r)) a -> m #

foldr :: (a -> b -> b) -> b -> Shape (S (S r)) a -> b #

foldr' :: (a -> b -> b) -> b -> Shape (S (S r)) a -> b #

foldl :: (b -> a -> b) -> b -> Shape (S (S r)) a -> b #

foldl' :: (b -> a -> b) -> b -> Shape (S (S r)) a -> b #

foldr1 :: (a -> a -> a) -> Shape (S (S r)) a -> a #

foldl1 :: (a -> a -> a) -> Shape (S (S r)) a -> a #

toList :: Shape (S (S r)) a -> [a] #

null :: Shape (S (S r)) a -> Bool #

length :: Shape (S (S r)) a -> Int #

elem :: Eq a => a -> Shape (S (S r)) a -> Bool #

maximum :: Ord a => Shape (S (S r)) a -> a #

minimum :: Ord a => Shape (S (S r)) a -> a #

sum :: Num a => Shape (S (S r)) a -> a #

product :: Num a => Shape (S (S r)) a -> a #

Foldable (Shape (S Z)) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

fold :: Monoid m => Shape (S Z) m -> m #

foldMap :: Monoid m => (a -> m) -> Shape (S Z) a -> m #

foldr :: (a -> b -> b) -> b -> Shape (S Z) a -> b #

foldr' :: (a -> b -> b) -> b -> Shape (S Z) a -> b #

foldl :: (b -> a -> b) -> b -> Shape (S Z) a -> b #

foldl' :: (b -> a -> b) -> b -> Shape (S Z) a -> b #

foldr1 :: (a -> a -> a) -> Shape (S Z) a -> a #

foldl1 :: (a -> a -> a) -> Shape (S Z) a -> a #

toList :: Shape (S Z) a -> [a] #

null :: Shape (S Z) a -> Bool #

length :: Shape (S Z) a -> Int #

elem :: Eq a => a -> Shape (S Z) a -> Bool #

maximum :: Ord a => Shape (S Z) a -> a #

minimum :: Ord a => Shape (S Z) a -> a #

sum :: Num a => Shape (S Z) a -> a #

product :: Num a => Shape (S Z) a -> a #

Foldable (Shape Z) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

fold :: Monoid m => Shape Z m -> m #

foldMap :: Monoid m => (a -> m) -> Shape Z a -> m #

foldr :: (a -> b -> b) -> b -> Shape Z a -> b #

foldr' :: (a -> b -> b) -> b -> Shape Z a -> b #

foldl :: (b -> a -> b) -> b -> Shape Z a -> b #

foldl' :: (b -> a -> b) -> b -> Shape Z a -> b #

foldr1 :: (a -> a -> a) -> Shape Z a -> a #

foldl1 :: (a -> a -> a) -> Shape Z a -> a #

toList :: Shape Z a -> [a] #

null :: Shape Z a -> Bool #

length :: Shape Z a -> Int #

elem :: Eq a => a -> Shape Z a -> Bool #

maximum :: Ord a => Shape Z a -> a #

minimum :: Ord a => Shape Z a -> a #

sum :: Num a => Shape Z a -> a #

product :: Num a => Shape Z a -> a #

Traversable (Shape (S n)) => Traversable (Shape (S (S n))) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

traverse :: Applicative f => (a -> f b) -> Shape (S (S n)) a -> f (Shape (S (S n)) b) #

sequenceA :: Applicative f => Shape (S (S n)) (f a) -> f (Shape (S (S n)) a) #

mapM :: Monad m => (a -> m b) -> Shape (S (S n)) a -> m (Shape (S (S n)) b) #

sequence :: Monad m => Shape (S (S n)) (m a) -> m (Shape (S (S n)) a) #

Traversable (Shape (S Z)) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

traverse :: Applicative f => (a -> f b) -> Shape (S Z) a -> f (Shape (S Z) b) #

sequenceA :: Applicative f => Shape (S Z) (f a) -> f (Shape (S Z) a) #

mapM :: Monad m => (a -> m b) -> Shape (S Z) a -> m (Shape (S Z) b) #

sequence :: Monad m => Shape (S Z) (m a) -> m (Shape (S Z) a) #

Traversable (Shape Z) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

traverse :: Applicative f => (a -> f b) -> Shape Z a -> f (Shape Z b) #

sequenceA :: Applicative f => Shape Z (f a) -> f (Shape Z a) #

mapM :: Monad m => (a -> m b) -> Shape Z a -> m (Shape Z b) #

sequence :: Monad m => Shape Z (m a) -> m (Shape Z a) #

(Eq a, Eq (Shape s a)) => Eq (Shape (S s) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

(==) :: Shape (S s) a -> Shape (S s) a -> Bool #

(/=) :: Shape (S s) a -> Shape (S s) a -> Bool #

Eq (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

(==) :: Shape Z a -> Shape Z a -> Bool #

(/=) :: Shape Z a -> Shape Z a -> Bool #

(Data a, Data (Shape n a), Typeable (S n)) => Data (Shape (S n) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Shape (S n) a -> c (Shape (S n) a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Shape (S n) a) #

toConstr :: Shape (S n) a -> Constr #

dataTypeOf :: Shape (S n) a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Shape (S n) a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Shape (S n) a)) #

gmapT :: (forall b. Data b => b -> b) -> Shape (S n) a -> Shape (S n) a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Shape (S n) a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Shape (S n) a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Shape (S n) a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Shape (S n) a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Shape (S n) a -> m (Shape (S n) a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Shape (S n) a -> m (Shape (S n) a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Shape (S n) a -> m (Shape (S n) a) #

(Data a, Typeable Z) => Data (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Shape Z a -> c (Shape Z a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Shape Z a) #

toConstr :: Shape Z a -> Constr #

dataTypeOf :: Shape Z a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Shape Z a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Shape Z a)) #

gmapT :: (forall b. Data b => b -> b) -> Shape Z a -> Shape Z a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Shape Z a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Shape Z a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Shape Z a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Shape Z a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Shape Z a -> m (Shape Z a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Shape Z a -> m (Shape Z a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Shape Z a -> m (Shape Z a) #

(Show a, Show (Shape s a)) => Show (Shape (S s) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

showsPrec :: Int -> Shape (S s) a -> ShowS #

show :: Shape (S s) a -> String #

showList :: [Shape (S s) a] -> ShowS #

Show (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

showsPrec :: Int -> Shape Z a -> ShowS #

show :: Shape Z a -> String #

showList :: [Shape Z a] -> ShowS #

(Semigroup a, Applicative (Shape n)) => Semigroup (Shape n a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

(<>) :: Shape n a -> Shape n a -> Shape n a #

sconcat :: NonEmpty (Shape n a) -> Shape n a #

stimes :: Integral b => b -> Shape n a -> Shape n a #

(Monoid a, Applicative (Shape n)) => Monoid (Shape n a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

mempty :: Shape n a #

mappend :: Shape n a -> Shape n a -> Shape n a #

mconcat :: [Shape n a] -> Shape n a #

(Storable a, Storable (Shape (S n) a)) => Storable (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

sizeOf :: Shape (S (S n)) a -> Int #

alignment :: Shape (S (S n)) a -> Int #

peekElemOff :: Ptr (Shape (S (S n)) a) -> Int -> IO (Shape (S (S n)) a) #

pokeElemOff :: Ptr (Shape (S (S n)) a) -> Int -> Shape (S (S n)) a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Shape (S (S n)) a) #

pokeByteOff :: Ptr b -> Int -> Shape (S (S n)) a -> IO () #

peek :: Ptr (Shape (S (S n)) a) -> IO (Shape (S (S n)) a) #

poke :: Ptr (Shape (S (S n)) a) -> Shape (S (S n)) a -> IO () #

Storable a => Storable (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

sizeOf :: Shape (S Z) a -> Int #

alignment :: Shape (S Z) a -> Int #

peekElemOff :: Ptr (Shape (S Z) a) -> Int -> IO (Shape (S Z) a) #

pokeElemOff :: Ptr (Shape (S Z) a) -> Int -> Shape (S Z) a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Shape (S Z) a) #

pokeByteOff :: Ptr b -> Int -> Shape (S Z) a -> IO () #

peek :: Ptr (Shape (S Z) a) -> IO (Shape (S Z) a) #

poke :: Ptr (Shape (S Z) a) -> Shape (S Z) a -> IO () #

Storable a => Storable (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

sizeOf :: Shape Z a -> Int #

alignment :: Shape Z a -> Int #

peekElemOff :: Ptr (Shape Z a) -> Int -> IO (Shape Z a) #

pokeElemOff :: Ptr (Shape Z a) -> Int -> Shape Z a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Shape Z a) #

pokeByteOff :: Ptr b -> Int -> Shape Z a -> IO () #

peek :: Ptr (Shape Z a) -> IO (Shape Z a) #

poke :: Ptr (Shape Z a) -> Shape Z a -> IO () #

(Unbox a, Unbox (Shape (S n) a)) => Unbox (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Unbox a => Unbox (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

Unbox a => Unbox (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

data MVector s (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

data MVector s (Shape (S (S n)) a) = MV_ShapeSSN (MVector s (a, Shape (S n) a))
data MVector s (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

data MVector s (Shape (S Z) a) = MV_ShapeSZ (MVector s a)
data MVector s (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

data MVector s (Shape Z a) = MV_ShapeZ Int
data Vector (Shape (S (S n)) a) Source # 
Instance details

Defined in Numerical.Array.Shape

data Vector (Shape (S (S n)) a) = V_ShapeSSN (Vector (a, Shape (S n) a))
data Vector (Shape (S Z) a) Source # 
Instance details

Defined in Numerical.Array.Shape

data Vector (Shape (S Z) a) = V_ShapeSZ (Vector a)
data Vector (Shape Z a) Source # 
Instance details

Defined in Numerical.Array.Shape

Shape Utilities

foldl :: forall a b r. Foldable (Shape r) => (b -> a -> b) -> b -> Shape r a -> b Source #

foldr :: forall a b r. Foldable (Shape r) => (a -> b -> b) -> b -> Shape r a -> b Source #

foldl' :: forall a b r. Foldable (Shape r) => (b -> a -> b) -> b -> Shape r a -> b Source #

foldl1 :: forall b r. Foldable (Shape (S r)) => (b -> b -> b) -> Shape (S r) b -> b Source #

foldr1 :: forall b r. Foldable (Shape (S r)) => (b -> b -> b) -> Shape (S r) b -> b Source #

map :: forall a b r. Applicative (Shape r) => (a -> b) -> Shape r a -> Shape r b Source #

map2 :: forall a b c r. Applicative (Shape r) => (a -> b -> c) -> Shape r a -> Shape r b -> Shape r c Source #

data Nat Source #

Constructors

S !Nat 
Z 
Instances
Eq Nat Source # 
Instance details

Defined in Numerical.Nat

Methods

(==) :: Nat -> Nat -> Bool #

(/=) :: Nat -> Nat -> Bool #

Data Nat Source # 
Instance details

Defined in Numerical.Nat

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Nat -> c Nat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Nat #

toConstr :: Nat -> Constr #

dataTypeOf :: Nat -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Nat -> Nat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r #

gmapQ :: (forall d. Data d => d -> u) -> Nat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Nat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

Read Nat Source # 
Instance details

Defined in Numerical.Nat

Show Nat Source # 
Instance details

Defined in Numerical.Nat

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

data SNat :: Nat -> * where Source #

Constructors

SZero :: SNat Z 
SSucc :: SNat n -> SNat (S n) 

weaklyDominates :: (Ord a, Applicative (Shape n), Foldable (Shape n)) => Shape n a -> Shape n a -> Bool Source #

weaklyDominates is the <= operator lifted onto a sized vector to induce a partial order relation

strictlyDominates :: (Ord a, Applicative (Shape n), Foldable (Shape n)) => Shape n a -> Shape n a -> Bool Source #

strictlyDominates is the < operator lifted onto a sized vector to induce a partial order relation

shapeToList :: Shape n a -> [a] Source #

type Index rank = Shape rank Int Source #

backwards :: (Traversable t, Applicative f) => ((a -> Backwards f b) -> t a -> Backwards f (t b)) -> (a -> f b) -> t a -> f (t b) Source #

Unboxed Vector Morphism

class Unbox (Shape n a) => UnBoxedShapeMorphism n a where Source #

Methods

unShapeMVector :: MVector s (Shape n a) -> (Int, Shape n (MVector s a)) Source #

reShapeMVector :: (Int, Shape n (MVector s a)) -> MVector s (Shape n a) Source #

Instances
Unbox a => UnBoxedShapeMorphism Z a Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

unShapeMVector :: MVector s (Shape Z a) -> (Int, Shape Z (MVector s a)) Source #

reShapeMVector :: (Int, Shape Z (MVector s a)) -> MVector s (Shape Z a) Source #

(Unbox a, UnBoxedShapeMorphism (S n) a) => UnBoxedShapeMorphism (S (S n)) a Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

unShapeMVector :: MVector s (Shape (S (S n)) a) -> (Int, Shape (S (S n)) (MVector s a)) Source #

reShapeMVector :: (Int, Shape (S (S n)) (MVector s a)) -> MVector s (Shape (S (S n)) a) Source #

Unbox a => UnBoxedShapeMorphism (S Z) a Source # 
Instance details

Defined in Numerical.Array.Shape

Methods

unShapeMVector :: MVector s (Shape (S Z) a) -> (Int, Shape (S Z) (MVector s a)) Source #

reShapeMVector :: (Int, Shape (S Z) (MVector s a)) -> MVector s (Shape (S Z) a) Source #

traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) #

Map each element of a structure to an action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see traverse_.