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

Description

 
Synopsis

Documentation

newtype DimVal Source #

Deprecated: Use dimensions package's Idx instead

term-level representation of an index.

Constructors

DimVal Int32

Deprecated: Use dimensions package's Idx instead

Instances
Bounded DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Enum DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Eq DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Methods

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

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

Integral DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Num DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Ord DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Read DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Real DimVal Source # 
Instance details

Defined in Torch.Indef.Types

Show DimVal Source # 
Instance details

Defined in Torch.Indef.Types

newtype Step Source #

newtype wrapper around the C-level representation of a step size

Constructors

Step CLong 
Instances
Bounded Step Source # 
Instance details

Defined in Torch.Indef.Types

Enum Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

succ :: Step -> Step #

pred :: Step -> Step #

toEnum :: Int -> Step #

fromEnum :: Step -> Int #

enumFrom :: Step -> [Step] #

enumFromThen :: Step -> Step -> [Step] #

enumFromTo :: Step -> Step -> [Step] #

enumFromThenTo :: Step -> Step -> Step -> [Step] #

Eq Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

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

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

Integral Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

quot :: Step -> Step -> Step #

rem :: Step -> Step -> Step #

div :: Step -> Step -> Step #

mod :: Step -> Step -> Step #

quotRem :: Step -> Step -> (Step, Step) #

divMod :: Step -> Step -> (Step, Step) #

toInteger :: Step -> Integer #

Num Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

(+) :: Step -> Step -> Step #

(-) :: Step -> Step -> Step #

(*) :: Step -> Step -> Step #

negate :: Step -> Step #

abs :: Step -> Step #

signum :: Step -> Step #

fromInteger :: Integer -> Step #

Ord Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

compare :: Step -> Step -> Ordering #

(<) :: Step -> Step -> Bool #

(<=) :: Step -> Step -> Bool #

(>) :: Step -> Step -> Bool #

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

max :: Step -> Step -> Step #

min :: Step -> Step -> Step #

Read Step Source # 
Instance details

Defined in Torch.Indef.Types

Real Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

toRational :: Step -> Rational #

Show Step Source # 
Instance details

Defined in Torch.Indef.Types

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

newtype Stride Source #

newtype wrapper around the C-level representation of a tensor's internal Storage stride for each dimension.

Constructors

Stride CLLong 
Instances
Bounded Stride Source # 
Instance details

Defined in Torch.Indef.Types

Enum Stride Source # 
Instance details

Defined in Torch.Indef.Types

Eq Stride Source # 
Instance details

Defined in Torch.Indef.Types

Methods

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

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

Integral Stride Source # 
Instance details

Defined in Torch.Indef.Types

Num Stride Source # 
Instance details

Defined in Torch.Indef.Types

Ord Stride Source # 
Instance details

Defined in Torch.Indef.Types

Read Stride Source # 
Instance details

Defined in Torch.Indef.Types

Real Stride Source # 
Instance details

Defined in Torch.Indef.Types

Show Stride Source # 
Instance details

Defined in Torch.Indef.Types

newtype StorageOffset Source #

newtype wrapper around the C-level representation of a storage offset

Constructors

Offset CPtrdiff 
Instances
Bounded StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Enum StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Eq StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Integral StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Num StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Ord StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Read StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Real StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

Show StorageOffset Source # 
Instance details

Defined in Torch.Indef.Types

newtype Size Source #

newtype wrapper around the C-level representation of a dimension's size

Constructors

Size CLLong 
Instances
Bounded Size Source # 
Instance details

Defined in Torch.Indef.Types

Enum Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

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

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

Integral Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Instance details

Defined in Torch.Indef.Types

Real Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

toRational :: Size -> Rational #

Show Size Source # 
Instance details

Defined in Torch.Indef.Types

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype KeepDim Source #

haskell representation of a CInt which determines whether or not to return dimensions

Constructors

KeepDim 

Fields

fromKeepDim :: Integral i => Maybe KeepDim -> i Source #

cast a KeepDim to a numerical representation.

NOTE: don't bind the i in case there are some differences between THC and TH

keep :: KeepDim Source #

smart constructors for keepdim since we don't get inference for free like Num

ignore :: KeepDim Source #

smart constructors for keepdim since we don't get inference for free like Num

data SortOrder Source #

Simple datatype to represent sort order arguments which torch provides to us.

Constructors

Ascending 
Descending 

data TopKOrder Source #

Constructors

KAscending 
KNone 
KDescending 

newtype AllocatorContext Source #

Warning: this should not be used or referenced -- we are still figuring out what to do with this.

this is supposed to represent the AllocatorContext, but it should not be exposed to a user.

Constructors

AllocatorContext (Ptr ())

Warning: this should not be used or referenced -- we are still figuring out what to do with this.

(.:) :: (b -> c) -> (a0 -> a1 -> b) -> a0 -> a1 -> c infixl 5 Source #

The blackbird combinator.

(stites): This happens often enough that I'm pulling in the blackbird

FIXME(stites): remove this

managedState :: Managed (Ptr CState) Source #

run a function with a managed state's raw internal pointer.

withLift :: Managed (IO x) -> IO x Source #

withDynamic :: Managed (IO (Ptr CTensor)) -> IO Dynamic Source #

smart constructor for a Managed Dynamic tensor

withStorage :: Managed (IO (Ptr CStorage)) -> IO Storage Source #

smart constructor for a Managed Storage tensor

with2DynamicState :: Dynamic -> Dynamic -> (Ptr CState -> Ptr CTensor -> Ptr CTensor -> IO x) -> IO x Source #

run a function with two tensors with reference to the first tensor's underlying state.

with3DynamicState :: Dynamic -> Dynamic -> Dynamic -> (Ptr CState -> Ptr CTensor -> Ptr CTensor -> Ptr CTensor -> IO x) -> IO x Source #

run a function with three tensors with reference to the first tensor's underlying state.

mkDynamic :: Ptr CTensor -> IO Dynamic Source #

smart constructor for a Dynamic tensor

mkStorage :: Ptr CStorage -> IO Storage Source #

smart constructor for Storage