tensorflow-0.3.0.0: TensorFlow bindings.
Safe HaskellNone
LanguageHaskell2010

TensorFlow.Types

Synopsis

Documentation

class TensorType a where Source #

The class of scalar types supported by tensorflow.

Instances

Instances details
TensorType Bool Source # 
Instance details

Defined in TensorFlow.Types

TensorType Double Source # 
Instance details

Defined in TensorFlow.Types

TensorType Float Source # 
Instance details

Defined in TensorFlow.Types

TensorType Int8 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Int16 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Int32 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Int64 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Word8 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Word16 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Word32 Source # 
Instance details

Defined in TensorFlow.Types

TensorType Word64 Source # 
Instance details

Defined in TensorFlow.Types

TensorType ByteString Source # 
Instance details

Defined in TensorFlow.Types

TensorType Variant Source # 
Instance details

Defined in TensorFlow.Types

TensorType ResourceHandle Source # 
Instance details

Defined in TensorFlow.Types

TensorType (Complex Double) Source # 
Instance details

Defined in TensorFlow.Types

TensorType (Complex Float) Source # 
Instance details

Defined in TensorFlow.Types

newtype TensorData a Source #

Tensor data with the correct memory layout for tensorflow.

Constructors

TensorData 

Instances

Instances details
(TensorType a, a ~ a') => Fetchable (Tensor v a) (TensorData a') Source # 
Instance details

Defined in TensorFlow.Nodes

Methods

getFetch :: Tensor v a -> Build (Fetch (TensorData a')) Source #

class TensorType a => TensorDataType s a where Source #

Types that can be converted to and from TensorData.

Vector is the most efficient to encode/decode for most element types.

Methods

decodeTensorData :: TensorData a -> s a Source #

Decode the bytes of a TensorData into an s.

encodeTensorData :: Shape -> s a -> TensorData a Source #

Encode an s into a TensorData.

The values should be in row major order, e.g.,

element 0: index (0, ..., 0) element 1: index (0, ..., 1) ...

Instances

Instances details
TensorDataType Vector Bool Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Double Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Float Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Int8 Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Int16 Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Int32 Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Int64 Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Word8 Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector Word16 Source # 
Instance details

Defined in TensorFlow.Types

(Storable a, TensorDataType Vector a, TensorType a) => TensorDataType Vector a Source # 
Instance details

Defined in TensorFlow.Types

Methods

decodeTensorData :: TensorData a -> Vector a Source #

encodeTensorData :: Shape -> Vector a -> TensorData a Source #

TensorDataType Vector ByteString Source # 
Instance details

Defined in TensorFlow.Types

(TensorDataType Vector a, TensorType a) => TensorDataType Scalar a Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector (Complex Double) Source # 
Instance details

Defined in TensorFlow.Types

TensorDataType Vector (Complex Float) Source # 
Instance details

Defined in TensorFlow.Types

newtype Scalar a Source #

Constructors

Scalar 

Fields

Instances

Instances details
(TensorDataType Vector a, TensorType a) => TensorDataType Scalar a Source # 
Instance details

Defined in TensorFlow.Types

Eq a => Eq (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

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

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

Floating a => Floating (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

pi :: Scalar a #

exp :: Scalar a -> Scalar a #

log :: Scalar a -> Scalar a #

sqrt :: Scalar a -> Scalar a #

(**) :: Scalar a -> Scalar a -> Scalar a #

logBase :: Scalar a -> Scalar a -> Scalar a #

sin :: Scalar a -> Scalar a #

cos :: Scalar a -> Scalar a #

tan :: Scalar a -> Scalar a #

asin :: Scalar a -> Scalar a #

acos :: Scalar a -> Scalar a #

atan :: Scalar a -> Scalar a #

sinh :: Scalar a -> Scalar a #

cosh :: Scalar a -> Scalar a #

tanh :: Scalar a -> Scalar a #

asinh :: Scalar a -> Scalar a #

acosh :: Scalar a -> Scalar a #

atanh :: Scalar a -> Scalar a #

log1p :: Scalar a -> Scalar a #

expm1 :: Scalar a -> Scalar a #

log1pexp :: Scalar a -> Scalar a #

log1mexp :: Scalar a -> Scalar a #

Fractional a => Fractional (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

(/) :: Scalar a -> Scalar a -> Scalar a #

recip :: Scalar a -> Scalar a #

fromRational :: Rational -> Scalar a #

Num a => Num (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

(+) :: Scalar a -> Scalar a -> Scalar a #

(-) :: Scalar a -> Scalar a -> Scalar a #

(*) :: Scalar a -> Scalar a -> Scalar a #

negate :: Scalar a -> Scalar a #

abs :: Scalar a -> Scalar a #

signum :: Scalar a -> Scalar a #

fromInteger :: Integer -> Scalar a #

Ord a => Ord (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

compare :: Scalar a -> Scalar a -> Ordering #

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

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

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

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

max :: Scalar a -> Scalar a -> Scalar a #

min :: Scalar a -> Scalar a -> Scalar a #

Real a => Real (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

toRational :: Scalar a -> Rational #

RealFloat a => RealFloat (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

RealFrac a => RealFrac (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

properFraction :: Integral b => Scalar a -> (b, Scalar a) #

truncate :: Integral b => Scalar a -> b #

round :: Integral b => Scalar a -> b #

ceiling :: Integral b => Scalar a -> b #

floor :: Integral b => Scalar a -> b #

Show a => Show (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

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

show :: Scalar a -> String #

showList :: [Scalar a] -> ShowS #

IsString a => IsString (Scalar a) Source # 
Instance details

Defined in TensorFlow.Types

Methods

fromString :: String -> Scalar a #

newtype Shape Source #

Shape (dimensions) of a tensor.

TensorFlow supports shapes of unknown rank, which are represented as Nothing :: Maybe Shape in Haskell.

Constructors

Shape [Int64] 

Instances

Instances details
IsList Shape Source # 
Instance details

Defined in TensorFlow.Types

Associated Types

type Item Shape #

Show Shape Source # 
Instance details

Defined in TensorFlow.Types

Methods

showsPrec :: Int -> Shape -> ShowS #

show :: Shape -> String #

showList :: [Shape] -> ShowS #

Attribute Shape Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue Shape Source #

Attribute (Maybe Shape) Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue (Maybe Shape) Source #

type Item Shape Source # 
Instance details

Defined in TensorFlow.Types

class Attribute a where Source #

Methods

attrLens :: Lens' AttrValue a Source #

Instances

Instances details
Attribute Bool Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue Bool Source #

Attribute Float Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue Float Source #

Attribute Int64 Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue Int64 Source #

Attribute ByteString Source # 
Instance details

Defined in TensorFlow.Types

Attribute AttrValue'ListValue Source # 
Instance details

Defined in TensorFlow.Types

Attribute TensorProto Source # 
Instance details

Defined in TensorFlow.Types

Attribute DataType Source # 
Instance details

Defined in TensorFlow.Types

Attribute Shape Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue Shape Source #

Attribute [Int64] Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue [Int64] Source #

Attribute [DataType] Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue [DataType] Source #

Attribute (Maybe Shape) Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue (Maybe Shape) Source #

data DataType #

Instances

Instances details
Bounded DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Enum DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Eq DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Ord DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Show DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

NFData DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Methods

rnf :: DataType -> () #

FieldDefault DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

MessageEnum DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Types

Attribute DataType Source # 
Instance details

Defined in TensorFlow.Types

HasField OpDef'ArgDef "type'" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.OpDef

Methods

fieldOf :: Functor f => Proxy# "type'" -> (DataType -> f DataType) -> OpDef'ArgDef -> f OpDef'ArgDef

HasField AttrValue "type'" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.AttrValue

Methods

fieldOf :: Functor f => Proxy# "type'" -> (DataType -> f DataType) -> AttrValue -> f AttrValue

HasField CostGraphDef'Node'OutputInfo "dtype" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.CostGraph

HasField TensorProto "dtype" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.Tensor

Methods

fieldOf :: Functor f => Proxy# "dtype" -> (DataType -> f DataType) -> TensorProto -> f TensorProto

HasField ResourceHandleProto'DtypeAndShape "dtype" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.ResourceHandle

HasField TensorDescription "dtype" DataType 
Instance details

Defined in Proto.Tensorflow.Core.Framework.TensorDescription

Methods

fieldOf :: Functor f => Proxy# "dtype" -> (DataType -> f DataType) -> TensorDescription -> f TensorDescription

HasField AttrValue "maybe'type'" (Maybe DataType) 
Instance details

Defined in Proto.Tensorflow.Core.Framework.AttrValue

Methods

fieldOf :: Functor f => Proxy# "maybe'type'" -> (Maybe DataType -> f (Maybe DataType)) -> AttrValue -> f AttrValue

HasField AttrValue'ListValue "type'" [DataType] 
Instance details

Defined in Proto.Tensorflow.Core.Framework.AttrValue

Methods

fieldOf :: Functor f => Proxy# "type'" -> ([DataType] -> f [DataType]) -> AttrValue'ListValue -> f AttrValue'ListValue

HasField AttrValue'ListValue "vec'type'" (Vector DataType) 
Instance details

Defined in Proto.Tensorflow.Core.Framework.AttrValue

Methods

fieldOf :: Functor f => Proxy# "vec'type'" -> (Vector DataType -> f (Vector DataType)) -> AttrValue'ListValue -> f AttrValue'ListValue

Attribute [DataType] Source # 
Instance details

Defined in TensorFlow.Types

Methods

attrLens :: Lens' AttrValue [DataType] Source #

data Variant Source #

Dynamic type. TensorFlow variants aren't supported yet. This type acts a placeholder to simplify op generation.

Instances

Instances details
TensorType Variant Source # 
Instance details

Defined in TensorFlow.Types

Lists

data ListOf f as where Source #

A heterogeneous list type.

Constructors

Nil :: ListOf f '[] 
(:/) :: f a -> ListOf f as -> ListOf f (a ': as) infixr 5 

Instances

Instances details
All Eq (Map f as) => Eq (ListOf f as) Source # 
Instance details

Defined in TensorFlow.Types

Methods

(==) :: ListOf f as -> ListOf f as -> Bool #

(/=) :: ListOf f as -> ListOf f as -> Bool #

All Show (Map f as) => Show (ListOf f as) Source # 
Instance details

Defined in TensorFlow.Types

Methods

showsPrec :: Int -> ListOf f as -> ShowS #

show :: ListOf f as -> String #

showList :: [ListOf f as] -> ShowS #

(Nodes (f a), Nodes (ListOf f as)) => Nodes (ListOf f (a ': as)) Source # 
Instance details

Defined in TensorFlow.Nodes

Methods

getNodes :: ListOf f (a ': as) -> Build (Set NodeName) Source #

Nodes (ListOf f ('[] :: [Type])) Source # 
Instance details

Defined in TensorFlow.Nodes

Methods

getNodes :: ListOf f '[] -> Build (Set NodeName) Source #

BuildInputs (ListOf (Tensor v) as) Source # 
Instance details

Defined in TensorFlow.BuildOp

Methods

buildInputs :: ListOf (Tensor v) as -> Build [Output] Source #

TensorTypes as => PureResult (TensorList Build as) Source # 
Instance details

Defined in TensorFlow.BuildOp

Methods

pureResult :: ReaderT (Build OpDef) (State ResultState) (TensorList Build as) Source #

(TensorKind v, Rendered (Tensor v), TensorTypes as) => BuildResult (TensorList v as) Source # 
Instance details

Defined in TensorFlow.BuildOp

Methods

buildResult :: Result (TensorList v as) Source #

l ~ List ('[] :: [Type]) => Fetchable (ListOf f ('[] :: [Type])) l Source # 
Instance details

Defined in TensorFlow.Nodes

Methods

getFetch :: ListOf f '[] -> Build (Fetch l) Source #

(Fetchable (f t) a, Fetchable (ListOf f ts) (List as), i ~ Identity) => Fetchable (ListOf f (t ': ts)) (ListOf i (a ': as)) Source # 
Instance details

Defined in TensorFlow.Nodes

Methods

getFetch :: ListOf f (t ': ts) -> Build (Fetch (ListOf i (a ': as))) Source #

(/:/) :: a -> List as -> List (a ': as) infixr 5 Source #

Equivalent of :/ for lists.

class TensorTypes (ts :: [*]) where Source #

Instances

Instances details
TensorTypes ('[] :: [Type]) Source # 
Instance details

Defined in TensorFlow.Types

(TensorType t, TensorTypes ts) => TensorTypes (t ': ts) Source #

A constraint that the input is a list of TensorTypes.

Instance details

Defined in TensorFlow.Types

Methods

tensorTypes :: TensorTypeList (t ': ts) Source #

fromTensorTypes :: forall as. TensorTypes as => Proxy as -> [DataType] Source #

Type constraints

type OneOf ts a = (TensorType a, TensorTypes' ts, NoneOf (AllTensorTypes \\ ts) a) Source #

A Constraint specifying the possible choices of a TensorType.

We implement a Constraint like OneOf '[Double, Float] a by turning the natural representation as a conjunction, i.e.,

   a == Double || a == Float

into a disjunction like

    a /= Int32 && a /= Int64 && a /= ByteString && ...

using an enumeration of all the possible TensorTypes.

type family a /= b :: Constraint where ... Source #

A constraint checking that two types are different.

Equations

a /= a = TypeError a ~ ExcludedCase 
a /= b = () 

type OneOfs ts as = (TensorTypes as, TensorTypes' ts, NoneOfs (AllTensorTypes \\ ts) as) Source #

Implementation of constraints

data TypeError a Source #

Helper types to produce a reasonable type error message when the Constraint "a /= a" fails. TODO(judahjacobson): Use ghc-8's CustomTypeErrors for this.

type family NoneOf ts a :: Constraint where ... Source #

A constraint that the type a doesn't appear in the type list ts. Assumes that a and each of the elements of ts are TensorTypes.

Equations

NoneOf (t1 ': (t2 ': (t3 ': (t4 ': ts)))) a = (a /= t1, a /= t2, a /= t3, a /= t4, NoneOf ts a) 
NoneOf (t1 ': (t2 ': (t3 ': ts))) a = (a /= t1, a /= t2, a /= t3, NoneOf ts a) 
NoneOf (t1 ': (t2 ': ts)) a = (a /= t1, a /= t2, NoneOf ts a) 
NoneOf (t1 ': ts) a = (a /= t1, NoneOf ts a) 
NoneOf '[] a = () 

type family as \\ bs where ... Source #

Takes the difference of two lists of types.

Equations

as \\ '[] = as 
as \\ (b ': bs) = Delete b as \\ bs 

type family Delete a as where ... Source #

Removes a type from the given list of types.

Equations

Delete a '[] = '[] 
Delete a (a ': as) = Delete a as 
Delete a (b ': as) = b ': Delete a as 

type AllTensorTypes = '[Float, Double, Int8, Int16, Int32, Int64, Word8, Word16, ByteString, Bool] Source #

An enumeration of all valid TensorTypes.