hasktorch-indef-0.0.1.0: Core Hasktorch abstractions wrapping FFI bindings

Copyright(c) Sam Stites 2017
LicenseBSD3
Maintainersam@stites.io
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Torch.Indef.Storage

Contents

Description

Storages are basically a way to access memory of a C pointer or array. Storages can also map the contents of a file to memory. A Storage is an array of basic C types.

Several Storage classes for all the basic C types exist and have the following self-explanatory names: ByteStorage, CharStorage, ShortStorage, IntStorage, LongStorage, FloatStorage, DoubleStorage.

Note that ByteStorage and CharStorage represent both arrays of bytes. ByteStorage represents an array of unsigned chars, while CharStorage represents an array of signed chars.

Synopsis

Documentation

class IsList l where #

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: base-4.7.0.0

Minimal complete definition

fromList, toList

Associated Types

type Item l :: Type #

The Item type function returns the type of items of the structure l.

Methods

fromList :: [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [Item l] -> l #

The fromListN function takes the input list's length as a hint. Its behaviour should be equivalent to fromList. The hint can be used to construct the structure l more efficiently compared to fromList. If the given hint does not equal to the input list's length the behaviour of fromListN is not specified.

toList :: l -> [Item l] #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

Instances
IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item CallStack :: Type #

IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item Version :: Type #

IsList IntSet

Since: containers-0.5.6.2

Instance details

Defined in Data.IntSet.Internal

Associated Types

type Item IntSet :: Type #

IsList Storage Source # 
Instance details

Defined in Torch.Indef.Storage

Associated Types

type Item Storage :: Type #

IsList Dynamic Source # 
Instance details

Defined in Torch.Indef.Dynamic.Tensor

Associated Types

type Item Dynamic :: Type #

IsList ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Associated Types

type Item ByteArray :: Type #

Methods

fromList :: [Item ByteArray] -> ByteArray #

fromListN :: Int -> [Item ByteArray] -> ByteArray #

toList :: ByteArray -> [Item ByteArray] #

IsList [a]

Since: base-4.7.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item [a] :: Type #

Methods

fromList :: [Item [a]] -> [a] #

fromListN :: Int -> [Item [a]] -> [a] #

toList :: [a] -> [Item [a]] #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) :: Type #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

IsList (IntMap a)

Since: containers-0.5.6.2

Instance details

Defined in Data.IntMap.Internal

Associated Types

type Item (IntMap a) :: Type #

Methods

fromList :: [Item (IntMap a)] -> IntMap a #

fromListN :: Int -> [Item (IntMap a)] -> IntMap a #

toList :: IntMap a -> [Item (IntMap a)] #

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) :: Type #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Ord a => IsList (Set a)

Since: containers-0.5.6.2

Instance details

Defined in Data.Set.Internal

Associated Types

type Item (Set a) :: Type #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a) :: Type #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Storable a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Storable

Associated Types

type Item (Vector a) :: Type #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Prim a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Associated Types

type Item (Vector a) :: Type #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

IsList (Array a) 
Instance details

Defined in Data.Primitive.Array

Associated Types

type Item (Array a) :: Type #

Methods

fromList :: [Item (Array a)] -> Array a #

fromListN :: Int -> [Item (Array a)] -> Array a #

toList :: Array a -> [Item (Array a)] #

Prim a => IsList (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

Associated Types

type Item (PrimArray a) :: Type #

Methods

fromList :: [Item (PrimArray a)] -> PrimArray a #

fromListN :: Int -> [Item (PrimArray a)] -> PrimArray a #

toList :: PrimArray a -> [Item (PrimArray a)] #

IsList (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Associated Types

type Item (SmallArray a) :: Type #

Methods

fromList :: [Item (SmallArray a)] -> SmallArray a #

fromListN :: Int -> [Item (SmallArray a)] -> SmallArray a #

toList :: SmallArray a -> [Item (SmallArray a)] #

PrimUnlifted a => IsList (UnliftedArray a) 
Instance details

Defined in Data.Primitive.UnliftedArray

Associated Types

type Item (UnliftedArray a) :: Type #

Methods

fromList :: [Item (UnliftedArray a)] -> UnliftedArray a #

fromListN :: Int -> [Item (UnliftedArray a)] -> UnliftedArray a #

toList :: UnliftedArray a -> [Item (UnliftedArray a)] #

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) :: Type #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

data Storage #

Instances
IsList Storage Source # 
Instance details

Defined in Torch.Indef.Storage

Associated Types

type Item Storage :: Type #

Eq Storage 
Instance details

Defined in Torch.Sig.Types

Methods

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

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

Show Storage Source # 
Instance details

Defined in Torch.Indef.Storage

type Item Storage Source # 
Instance details

Defined in Torch.Indef.Storage

storagedata :: Storage -> [HsReal] Source #

return the internal data of Storage as a list of haskell values.

size :: Storage -> Int Source #

Returns the number of elements in the storage. Equivalent to #.

set :: Storage -> Word -> HsReal -> IO () Source #

set the value at Index to HsReal in a given Storage.

get :: Storage -> Word -> HsReal Source #

get the value at Index from a given Storage.

empty :: Storage Source #

make a new empty Storage.

newWithSize :: Word -> Storage Source #

create a new storage of a given length, StorageSize.

newWithSize1 :: HsReal -> Storage Source #

make a new Storage with a single value.

newWithSize2 :: HsReal -> HsReal -> Storage Source #

make a new Storage with two values.

newWithSize3 :: HsReal -> HsReal -> HsReal -> Storage Source #

make a new Storage with three values.

newWithSize4 :: HsReal -> HsReal -> HsReal -> HsReal -> Storage Source #

make a new Storage with four values.

newWithMapping Source #

Arguments

:: [Int8]

filename

-> Word64

size

-> Int32

flags

-> IO Storage 

FIXME: This is totally broken. This takes a filename, size, and flags, and produces Storage from these inputs. Figure out how to fix this, ideally.

See: https://github.com/torch/torch7/blob/04e1d1dce0f02aea82dc433c4f39e42650c4390f/lib/TH/generic/THStorage.h#L49

newWithData Source #

Arguments

:: [HsReal] 
-> Word64

storage size

-> Storage 

make a new Storage from a given list and StorageSize.

FIXME: find out if StorageSize always corresponds to the length of the list. If so, remove it!

setFlag :: Storage -> Int8 -> IO () Source #

set the flags of a given Storage. Flags are applied via bitwise-or.

clearFlag :: Storage -> Int8 -> IO () Source #

clear the flags of a given Storage. Flags are cleanred via bitwise-and.

retain :: Storage -> IO () Source #

Increment the reference counter of the storage.

This method should be used with extreme care. In general, they should never be called, except if you know what you are doing, as the handling of references is done automatically. They can be useful in threaded environments. Note that these methods are atomic operations.

resize :: Storage -> Word32 -> IO () Source #

Resize the storage to the provided size. The new contents are undetermined.

fill :: Storage -> HsReal -> IO () Source #

Fill the Storage with the given value.

Orphan instances

IsList Storage Source # 
Instance details

Associated Types

type Item Storage :: Type #

Show Storage Source # 
Instance details