orthotope-0.1.6.0: Multidimensional arrays inspired by APL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Array.Internal.DynamicS

Synopsis

Documentation

newtype Array a Source #

Constructors

A 

Fields

Instances

Instances details
(Arbitrary a, Unbox a) => Arbitrary (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

arbitrary :: Gen (Array a) #

shrink :: Array a -> [Array a] #

(Data a, Storable a) => Data (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

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

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

toConstr :: Array a -> Constr #

dataTypeOf :: Array a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Associated Types

type Rep (Array a) :: Type -> Type #

Methods

from :: Array a -> Rep (Array a) x #

to :: Rep (Array a) x -> Array a #

(Read a, Unbox a) => Read (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

(Show a, Unbox a) => Show (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

NFData a => NFData (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

rnf :: Array a -> () #

Eq (Array Vector a) => Eq (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

Ord (Array Vector a) => Ord (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

(Pretty a, Storable a) => Pretty (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

(a ~ b, Unbox a) => Convert (Array a) (Array b) Source # 
Instance details

Defined in Data.Array.Convert

(a ~ b, Unbox a) => Convert (Array a) (Array b) Source # 
Instance details

Defined in Data.Array.Convert

a ~ b => Convert (Array a) (Array Vector b) Source # 
Instance details

Defined in Data.Array.Convert

(a ~ b, KnownNat n) => Convert (Array a) (Array n b) Source # 
Instance details

Defined in Data.Array.Convert

Methods

convert :: Array0 a -> Array n b Source #

convertE :: Array0 a -> Either String (Array n b) Source #

(a ~ b, Shape sh) => Convert (Array a) (Array sh b) Source # 
Instance details

Defined in Data.Array.Convert

Methods

convert :: Array0 a -> Array sh b Source #

convertE :: Array0 a -> Either String (Array sh b) Source #

(a ~ b, Shape sh) => Convert (Array sh a) (Array b) Source # 
Instance details

Defined in Data.Array.Convert

Methods

convert :: Array sh a -> Array0 b Source #

convertE :: Array sh a -> Either String (Array0 b) Source #

type Rep (Array a) Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

type Rep (Array a) = D1 ('MetaData "Array" "Data.Array.Internal.DynamicS" "orthotope-0.1.6.0-7Lf71PJ1JmQsaMK9uKKpP" 'True) (C1 ('MetaCons "A" 'PrefixI 'True) (S1 ('MetaSel ('Just "unA") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Array Vector a))))

class Vector v Source #

The Vector class is the interface to the underlying storage for the arrays. The operations map straight to operations for Vector.

Instances

Instances details
Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.Dynamic

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.DynamicU

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

Vector [] Source # 
Instance details

Defined in Data.Array.Internal

Associated Types

type VecElem [] :: Type -> Constraint Source #

Methods

vIndex :: VecElem [] a => [a] -> Int -> a Source #

vLength :: VecElem [] a => [a] -> Int Source #

vToList :: VecElem [] a => [a] -> [a] Source #

vFromList :: VecElem [] a => [a] -> [a] Source #

vSingleton :: VecElem [] a => a -> [a] Source #

vReplicate :: VecElem [] a => Int -> a -> [a] Source #

vMap :: (VecElem [] a, VecElem [] b) => (a -> b) -> [a] -> [b] Source #

vZipWith :: (VecElem [] a, VecElem [] b, VecElem [] c) => (a -> b -> c) -> [a] -> [b] -> [c] Source #

vZipWith3 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d) => (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

vZipWith4 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d, VecElem [] e) => (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] Source #

vZipWith5 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d, VecElem [] e, VecElem [] f) => (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] Source #

vAppend :: VecElem [] a => [a] -> [a] -> [a] Source #

vConcat :: VecElem [] a => [[a]] -> [a] Source #

vFold :: VecElem [] a => (a -> a -> a) -> a -> [a] -> a Source #

vSlice :: VecElem [] a => Int -> Int -> [a] -> [a] Source #

vSum :: (VecElem [] a, Num a) => [a] -> a Source #

vProduct :: (VecElem [] a, Num a) => [a] -> a Source #

vMaximum :: (VecElem [] a, Ord a) => [a] -> a Source #

vMinimum :: (VecElem [] a, Ord a) => [a] -> a Source #

vUpdate :: VecElem [] a => [a] -> [(Int, a)] -> [a] Source #

vGenerate :: VecElem [] a => Int -> (Int -> a) -> [a] Source #

vAll :: VecElem [] a => (a -> Bool) -> [a] -> Bool Source #

vAny :: VecElem [] a => (a -> Bool) -> [a] -> Bool Source #

type ShapeL = [Int] Source #

The shape of an array is a list of its dimensions.

class Storable a #

The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.

Memory addresses are represented as values of type Ptr a, for some a which is an instance of class Storable. The type argument to Ptr helps provide some valuable type safety in FFI code (you can't mix pointers of different types without an explicit cast), while helping the Haskell type system figure out which marshalling method is needed for a given pointer.

All marshalling between Haskell and a foreign language ultimately boils down to translating Haskell data structures into the binary representation of a corresponding data structure of the foreign language and vice versa. To code this marshalling in Haskell, it is necessary to manipulate primitive data types stored in unstructured memory blocks. The class Storable facilitates this manipulation on all types for which it is instantiated, which are the standard basic types of Haskell, the fixed size Int types (Int8, Int16, Int32, Int64), the fixed size Word types (Word8, Word16, Word32, Word64), StablePtr, all types from Foreign.C.Types, as well as Ptr.

Minimal complete definition

sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Instances

Instances details
Storable CBool 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CBool -> Int #

alignment :: CBool -> Int #

peekElemOff :: Ptr CBool -> Int -> IO CBool #

pokeElemOff :: Ptr CBool -> Int -> CBool -> IO () #

peekByteOff :: Ptr b -> Int -> IO CBool #

pokeByteOff :: Ptr b -> Int -> CBool -> IO () #

peek :: Ptr CBool -> IO CBool #

poke :: Ptr CBool -> CBool -> IO () #

Storable CChar 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Storable CClock 
Instance details

Defined in Foreign.C.Types

Storable CDouble 
Instance details

Defined in Foreign.C.Types

Storable CFloat 
Instance details

Defined in Foreign.C.Types

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Storable CIntMax 
Instance details

Defined in Foreign.C.Types

Storable CIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CLLong 
Instance details

Defined in Foreign.C.Types

Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Storable CPtrdiff 
Instance details

Defined in Foreign.C.Types

Storable CSChar 
Instance details

Defined in Foreign.C.Types

Storable CSUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CShort 
Instance details

Defined in Foreign.C.Types

Storable CSigAtomic 
Instance details

Defined in Foreign.C.Types

Storable CSize 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CSize -> Int #

alignment :: CSize -> Int #

peekElemOff :: Ptr CSize -> Int -> IO CSize #

pokeElemOff :: Ptr CSize -> Int -> CSize -> IO () #

peekByteOff :: Ptr b -> Int -> IO CSize #

pokeByteOff :: Ptr b -> Int -> CSize -> IO () #

peek :: Ptr CSize -> IO CSize #

poke :: Ptr CSize -> CSize -> IO () #

Storable CTime 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CTime -> Int #

alignment :: CTime -> Int #

peekElemOff :: Ptr CTime -> Int -> IO CTime #

pokeElemOff :: Ptr CTime -> Int -> CTime -> IO () #

peekByteOff :: Ptr b -> Int -> IO CTime #

pokeByteOff :: Ptr b -> Int -> CTime -> IO () #

peek :: Ptr CTime -> IO CTime #

poke :: Ptr CTime -> CTime -> IO () #

Storable CUChar 
Instance details

Defined in Foreign.C.Types

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Storable CUIntMax 
Instance details

Defined in Foreign.C.Types

Storable CUIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CULLong 
Instance details

Defined in Foreign.C.Types

Storable CULong 
Instance details

Defined in Foreign.C.Types

Storable CUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CUShort 
Instance details

Defined in Foreign.C.Types

Storable CWchar 
Instance details

Defined in Foreign.C.Types

Storable IntPtr 
Instance details

Defined in Foreign.Ptr

Storable WordPtr 
Instance details

Defined in Foreign.Ptr

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Storable IoSubSystem

Since: base-4.9.0.0

Instance details

Defined in GHC.RTS.Flags

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Storable ()

Since: base-4.9.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

peekElemOff :: Ptr () -> Int -> IO () #

pokeElemOff :: Ptr () -> Int -> () -> IO () #

peekByteOff :: Ptr b -> Int -> IO () #

pokeByteOff :: Ptr b -> Int -> () -> IO () #

peek :: Ptr () -> IO () #

poke :: Ptr () -> () -> IO () #

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Storable a => Storable (Complex a)

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

peekElemOff :: Ptr (Complex a) -> Int -> IO (Complex a) #

pokeElemOff :: Ptr (Complex a) -> Int -> Complex a -> IO () #

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

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

peek :: Ptr (Complex a) -> IO (Complex a) #

poke :: Ptr (Complex a) -> Complex a -> IO () #

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

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

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

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Storable a => Storable (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int #

alignment :: Down a -> Int #

peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) #

pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () #

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

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

peek :: Ptr (Down a) -> IO (Down a) #

poke :: Ptr (Down a) -> Down a -> IO () #

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

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

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

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

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

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

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

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

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

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

(Storable a, Integral a) => Storable (Ratio a)

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) #

pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () #

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

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

peek :: Ptr (Ratio a) -> IO (Ratio a) #

poke :: Ptr (Ratio a) -> Ratio a -> IO () #

Storable (StablePtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

peekElemOff :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) #

pokeElemOff :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () #

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

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

peek :: Ptr (StablePtr a) -> IO (StablePtr a) #

poke :: Ptr (StablePtr a) -> StablePtr a -> IO () #

Prim a => Storable (PrimStorable a) 
Instance details

Defined in Data.Primitive.Types

Storable g => Storable (StateGen g) 
Instance details

Defined in System.Random.Internal

Methods

sizeOf :: StateGen g -> Int #

alignment :: StateGen g -> Int #

peekElemOff :: Ptr (StateGen g) -> Int -> IO (StateGen g) #

pokeElemOff :: Ptr (StateGen g) -> Int -> StateGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StateGen g) #

pokeByteOff :: Ptr b -> Int -> StateGen g -> IO () #

peek :: Ptr (StateGen g) -> IO (StateGen g) #

poke :: Ptr (StateGen g) -> StateGen g -> IO () #

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) #

pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () #

peekByteOff :: Ptr b0 -> Int -> IO (Const a b) #

pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () #

peek :: Ptr (Const a b) -> IO (Const a b) #

poke :: Ptr (Const a b) -> Const a b -> IO () #

size :: Array a -> Int Source #

The number of elements in the array.

shapeL :: Array a -> ShapeL Source #

The shape of an array, i.e., a list of the sizes of its dimensions. In the linearization of the array the outermost (i.e. first list element) varies most slowly. O(1) time.

rank :: Array a -> Int Source #

The rank of an array, i.e., the number of dimensions it has. O(1) time.

toList :: (HasCallStack, Unbox a) => Array a -> [a] Source #

Convert to a list with the elements in the linearization order. O(n) time.

fromList :: (HasCallStack, Unbox a) => ShapeL -> [a] -> Array a Source #

Convert from a list with the elements given in the linearization order. Fails if the given shape does not have the same number of elements as the list. O(n) time.

toVector :: (HasCallStack, Unbox a) => Array a -> Vector a Source #

Convert to a vector with the elements in the linearization order. O(n) or O(1) time (the latter if the vector is already in the linearization order).

fromVector :: (HasCallStack, Unbox a) => ShapeL -> Vector a -> Array a Source #

Convert from a vector with the elements given in the linearization order. Fails if the given shape does not have the same number of elements as the list. O(1) time.

normalize :: Unbox a => Array a -> Array a Source #

Make sure the underlying vector is in the linearization order. This is semantically an identity function, but can have big performance implications. O(n) or O(1) time.

scalar :: Unbox a => a -> Array a Source #

Convert a value to a scalar (rank 0) array. O(1) time.

unScalar :: (HasCallStack, Unbox a) => Array a -> a Source #

Convert a scalar (rank 0) array to a value. O(1) time.

constant :: Unbox a => ShapeL -> a -> Array a Source #

Make an array with all elements having the same value. O(1) time

reshape :: (HasCallStack, Unbox a) => ShapeL -> Array a -> Array a Source #

Change the shape of an array. Fails if the arrays have different number of elements. O(n) or O(1) time.

stretch :: HasCallStack => ShapeL -> Array a -> Array a Source #

Change the size of dimensions with size 1. These dimension can be changed to any size. All other dimensions must remain the same. O(1) time.

stretchOuter :: HasCallStack => Int -> Array a -> Array a Source #

Change the size of the outermost dimension by replication.

transpose :: HasCallStack => [Int] -> Array a -> Array a Source #

Do an arbitrary array transposition. Fails if the transposition argument is not a permutation of the numbers [0..r-1], where r is the rank of the array. O(1) time.

index :: (HasCallStack, Unbox a) => Array a -> Int -> Array a Source #

Index into an array. Fails if the array has rank 0 or if the index is out of bounds. O(1) time.

pad :: (HasCallStack, Unbox a) => [(Int, Int)] -> a -> Array a -> Array a Source #

Pad each dimension on the low and high side with the given value. O(n) time.

mapA :: (Unbox a, Unbox b) => (a -> b) -> Array a -> Array b Source #

Map over the array elements. O(n) time.

zipWithA :: (HasCallStack, Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Array a -> Array b -> Array c Source #

Map over the array elements. O(n) time.

zipWith3A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Array a -> Array b -> Array c -> Array d Source #

Map over the array elements. O(n) time.

zipWith4A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => (a -> b -> c -> d -> e) -> Array a -> Array b -> Array c -> Array d -> Array e Source #

Map over the array elements. O(n) time.

zipWith5A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => (a -> b -> c -> d -> e -> f) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f Source #

Map over the array elements. O(n) time.

append :: (HasCallStack, Unbox a) => Array a -> Array a -> Array a Source #

Append two arrays along the outermost dimension. All dimensions, except the outermost, must be the same. O(n) time.

concatOuter :: (HasCallStack, Unbox a) => [Array a] -> Array a Source #

Concatenate a number of arrays into a single array. Fails if any, but the outer, dimensions differ. O(n) time.

ravel :: (HasCallStack, Unbox a) => Array (Array a) -> Array a Source #

Turn a rank-1 array of arrays into a single array by making the outer array into the outermost dimension of the result array. All the arrays must have the same shape. O(n) time.

unravel :: (HasCallStack, Unbox a) => Array a -> Array (Array a) Source #

Turn an array into a nested array, this is the inverse of ravel. I.e., ravel . unravel == id.

window :: HasCallStack => [Int] -> Array a -> Array a Source #

Make a window of the outermost dimensions. The rank increases with the length of the window list. E.g., if the shape of the array is [10,12,8] and the window size is [3,3] then the resulting array will have shape [8,10,3,3,8]. O(1) time.

stride :: HasCallStack => [Int] -> Array a -> Array a Source #

Stride the outermost dimensions. E.g., if the array shape is [10,12,8] and the strides are [2,2] then the resulting shape will be [5,6,8]. O(1) time.

rotate :: (HasCallStack, Unbox a) => Int -> Int -> Array a -> Array a Source #

Rotate the array k times along the d'th dimension. E.g., if the array shape is [2, 3, 2], d is 1, and k is 4, the resulting shape will be [2, 4, 3, 2].

slice :: HasCallStack => [(Int, Int)] -> Array a -> Array a Source #

Extract a slice of an array. The first argument is a list of (offset, length) pairs. The length of the slicing argument must not exceed the rank of the array. The extracted slice must fall within the array dimensions. E.g. slice [1,2] (fromList [4] [1,2,3,4]) == [2,3]. O(1) time.

rerank :: (HasCallStack, Unbox a, Unbox b) => Int -> (Array a -> Array b) -> Array a -> Array b Source #

Apply a function to the subarrays n levels down and make the results into an array with the same n outermost dimensions. The n must not exceed the rank of the array. O(n) time.

rerank2 :: (HasCallStack, Unbox a, Unbox b, Unbox c) => Int -> (Array a -> Array b -> Array c) -> Array a -> Array b -> Array c Source #

Apply a two-argument function to the subarrays n levels down and make the results into an array with the same n outermost dimensions. The n must not exceed the rank of the array. O(n) time.

rev :: [Int] -> Array a -> Array a Source #

Reverse the given dimensions, with the outermost being dimension 0. O(1) time.

reduce :: Unbox a => (a -> a -> a) -> a -> Array a -> Array a Source #

Reduce all elements of an array into a rank 0 array. To reduce parts use rerank and transpose together with reduce. O(n) time.

foldrA :: Unbox a => (a -> b -> b) -> b -> Array a -> b Source #

Constrained version of foldr for Arrays.

traverseA :: (Unbox a, Unbox b, Applicative f) => (a -> f b) -> Array a -> f (Array b) Source #

Constrained version of traverse for Arrays.

allSameA :: (Unbox a, Eq a) => Array a -> Bool Source #

Check if all elements of the array are equal.

sumA :: (Unbox a, Num a) => Array a -> a Source #

Sum of all elements.

productA :: (Unbox a, Num a) => Array a -> a Source #

Product of all elements.

maximumA :: (HasCallStack, Unbox a, Ord a) => Array a -> a Source #

Maximum of all elements.

minimumA :: (HasCallStack, Unbox a, Ord a) => Array a -> a Source #

Minimum of all elements.

anyA :: Unbox a => (a -> Bool) -> Array a -> Bool Source #

Test if the predicate holds for any element.

allA :: Unbox a => (a -> Bool) -> Array a -> Bool Source #

Test if the predicate holds for all elements.

broadcast :: (HasCallStack, Unbox a) => [Int] -> ShapeL -> Array a -> Array a Source #

Put the dimensions of the argument into the specified dimensions, and just replicate the data along all other dimensions. The list of dimensions indicies must have the same rank as the argument array and it must be strictly ascending.

update :: (HasCallStack, Unbox a) => Array a -> [([Int], a)] -> Array a Source #

Update the array at the specified indicies to the associated value.

generate :: Unbox a => ShapeL -> ([Int] -> a) -> Array a Source #

Generate an array with a function that computes the value for each index.

iterateN :: Unbox a => Int -> (a -> a) -> a -> Array a Source #

Iterate a function n times.

iota :: (Unbox a, Enum a, Num a) => Int -> Array a Source #

Generate a vector from 0 to n-1.

bitcast :: forall a b. (HasCallStack, Unbox a, Unbox b) => Array a -> Array b Source #

Convert between types by just reinterpreting the bits as another type. For instance the floating point number (1.5 :: Float) will convert to (0x3fc00000 :: Word32) since they have the same bit representation.

Orphan instances

Vector Vector Source # 
Instance details

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #