tensorflow-0.2.0.0: TensorFlow bindings.

Safe HaskellNone
LanguageHaskell2010

TensorFlow.Core

Contents

Description

The core functionality of TensorFlow.

Unless you are defining ops, you do not need to import other modules from this package.

Basic ops are provided in the tensorflow-ops and tensorflow-core-ops packages.

Synopsis

Session

data Options Source #

Customization for session. Use the lenses to update: sessionTarget, sessionTracer, sessionConfig.

Instances

Default Options Source # 

Methods

def :: Options

sessionConfig :: Lens' Options ConfigProto Source #

Uses the specified config for the created session.

sessionTarget :: Lens' Options ByteString Source #

Target can be: "local", ip:port, host:port. The set of supported factories depends on the linked in libraries.

sessionTracer :: Lens' Options Tracer Source #

Uses the given logger to monitor session progress.

runSession :: (MonadMask m, MonadIO m) => SessionT m a -> m a Source #

Run Session actions in a new TensorFlow session.

runSessionWithOptions :: (MonadMask m, MonadIO m) => Options -> SessionT m a -> m a Source #

Run Session actions in a new TensorFlow session created with the given option setter actions (sessionTarget, sessionConfig).

Building graphs

class Monad m => MonadBuild m where Source #

Lift a Build action into a monad, including any explicit op renderings.

Minimal complete definition

build

Methods

build :: Build a -> m a Source #

Instances

Monad m => MonadBuild (BuildT m) Source # 

Methods

build :: Build a -> BuildT m a Source #

Monad m => MonadBuild (SessionT m) Source # 

Methods

build :: Build a -> SessionT m a Source #

Running graphs

class Nodes t => Fetchable t a Source #

Types that tensor representations (e.g. Tensor, ControlNode) can be fetched into.

Includes collections of tensors (e.g. tuples).

Minimal complete definition

getFetch

Instances

(~) * a () => Fetchable ControlNode a Source # 
Fetchable t a => Fetchable [t] [a] Source # 

Methods

getFetch :: [t] -> Build (Fetch [a]) Source #

Fetchable t a => Fetchable (Maybe t) (Maybe a) Source # 

Methods

getFetch :: Maybe t -> Build (Fetch (Maybe a)) Source #

(~) * l (List ([] *)) => Fetchable (ListOf f ([] *)) l Source # 

Methods

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

(TensorType a, TensorDataType s a, (~) * a a') => Fetchable (Tensor v a) (s a') Source # 

Methods

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

(TensorType a, (~) * a a') => Fetchable (Tensor v a) (TensorData a') Source # 

Methods

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

(Fetchable t1 a1, Fetchable t2 a2) => Fetchable (t1, t2) (a1, a2) Source # 

Methods

getFetch :: (t1, t2) -> Build (Fetch (a1, a2)) Source #

(Fetchable (f t) a, Fetchable (ListOf f ts) (List as), (~) (* -> *) i Identity) => Fetchable (ListOf f ((:) * t ts)) (ListOf i ((:) * a as)) Source # 

Methods

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

(Fetchable t1 a1, Fetchable t2 a2, Fetchable t3 a3) => Fetchable (t1, t2, t3) (a1, a2, a3) Source # 

Methods

getFetch :: (t1, t2, t3) -> Build (Fetch (a1, a2, a3)) Source #

class Nodes t Source #

Types that contain ops which can be run.

Minimal complete definition

getNodes

Instances

Nodes ControlNode Source # 
Nodes t => Nodes [t] Source # 

Methods

getNodes :: [t] -> Build (Set NodeName) Source #

Nodes t => Nodes (Maybe t) Source # 
(Nodes t1, Nodes t2) => Nodes (t1, t2) Source # 

Methods

getNodes :: (t1, t2) -> Build (Set NodeName) Source #

(Nodes (f a), Nodes (ListOf f as)) => Nodes (ListOf f ((:) * a as)) Source # 

Methods

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

Nodes (ListOf f ([] *)) Source # 

Methods

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

Nodes (Tensor v a) Source # 

Methods

getNodes :: Tensor v a -> Build (Set NodeName) Source #

(Nodes t1, Nodes t2, Nodes t3) => Nodes (t1, t2, t3) Source # 

Methods

getNodes :: (t1, t2, t3) -> Build (Set NodeName) Source #

run :: (MonadIO m, Fetchable t a) => t -> SessionT m a Source #

Run a subgraph t, rendering any dependent nodes that aren't already rendered, and fetch the corresponding values for a.

run_ :: (MonadIO m, Nodes t) => t -> SessionT m () Source #

Run a subgraph t, rendering and extending any dependent nodes that aren't already rendered. This behaves like run except that it doesn't do any fetches.

data Feed Source #

A pair of a Tensor and some data that should be fed into that Tensor when running the graph.

feed :: Rendered t => t a -> TensorData a -> Feed Source #

Create a Feed for feeding the given data into a Tensor when running the graph.

Note that if a Tensor is rendered, its identity may change; so feeding the rendered Tensor may be different than feeding the original Tensor.

runWithFeeds :: (MonadIO m, Fetchable t a) => [Feed] -> t -> SessionT m a Source #

Run a subgraph t, rendering any dependent nodes that aren't already rendered, feed the given input values, and fetch the corresponding result values for a.

runWithFeeds_ :: (MonadIO m, Nodes t) => [Feed] -> t -> SessionT m () Source #

Run a subgraph t, rendering any dependent nodes that aren't already rendered, feed the given input values, and fetch the corresponding result values for a. This behaves like runWithFeeds except that it doesn't do any fetches.

Async

asyncProdNodes Source #

Arguments

:: (MonadIO m, Nodes t) 
=> t

Node to evaluate concurrently.

-> SessionT m () 

Starts a concurrent thread which evaluates the given Nodes forever until runSession exits or an exception occurs. Graph extension happens synchronously, but the resultant run proceeds as a separate thread.

Build

type Build = BuildT Identity Source #

An action for building nodes in a TensorFlow graph.

data BuildT m a Source #

An action for building nodes in a TensorFlow graph. Used to manage build state internally as part of the Session monad.

Instances

MonadTrans BuildT Source # 

Methods

lift :: Monad m => m a -> BuildT m a #

TensorKind Build Source # 

Methods

toBuild :: Build a -> Build a Source #

Monad m => MonadState GraphState (BuildT m) Source # 

Methods

get :: BuildT m GraphState

put :: GraphState -> BuildT m ()

state :: (GraphState -> (a, GraphState)) -> BuildT m a

Monad m => Monad (BuildT m) Source # 

Methods

(>>=) :: BuildT m a -> (a -> BuildT m b) -> BuildT m b #

(>>) :: BuildT m a -> BuildT m b -> BuildT m b #

return :: a -> BuildT m a #

fail :: String -> BuildT m a #

Functor m => Functor (BuildT m) Source # 

Methods

fmap :: (a -> b) -> BuildT m a -> BuildT m b #

(<$) :: a -> BuildT m b -> BuildT m a #

MonadFix m => MonadFix (BuildT m) Source # 

Methods

mfix :: (a -> BuildT m a) -> BuildT m a #

Monad m => Applicative (BuildT m) Source # 

Methods

pure :: a -> BuildT m a #

(<*>) :: BuildT m (a -> b) -> BuildT m a -> BuildT m b #

liftA2 :: (a -> b -> c) -> BuildT m a -> BuildT m b -> BuildT m c #

(*>) :: BuildT m a -> BuildT m b -> BuildT m b #

(<*) :: BuildT m a -> BuildT m b -> BuildT m a #

MonadIO m => MonadIO (BuildT m) Source # 

Methods

liftIO :: IO a -> BuildT m a #

MonadThrow m => MonadThrow (BuildT m) Source # 

Methods

throwM :: Exception e => e -> BuildT m a

MonadMask m => MonadMask (BuildT m) Source # 

Methods

mask :: ((forall a. BuildT m a -> BuildT m a) -> BuildT m b) -> BuildT m b

uninterruptibleMask :: ((forall a. BuildT m a -> BuildT m a) -> BuildT m b) -> BuildT m b

MonadCatch m => MonadCatch (BuildT m) Source # 

Methods

catch :: Exception e => BuildT m a -> (e -> BuildT m a) -> BuildT m a

Monad m => MonadBuild (BuildT m) Source # 

Methods

build :: Build a -> BuildT m a Source #

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

Methods

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

PureResult (Tensor Build a) Source # 

Methods

pureResult :: ReaderT * (Build OpDef) (State ResultState) (Tensor Build a) Source #

render :: MonadBuild m => Tensor Build a -> m (Tensor Value a) Source #

Render a Tensor, fixing its name, scope, device and control inputs from the MonadBuild context. Also renders any dependencies of the Tensor that weren't already rendered.

This operation is idempotent; calling render on the same input in the same context will produce the same result. However, rendering the same Tensor Build in two different contexts may result in two different Tensor Values.

asGraphDef :: Build a -> GraphDef Source #

Produce a GraphDef proto representation of the nodes that are rendered in the given Build action.

opAttr :: Attribute a => Text -> Lens' OpDef a Source #

addInitializer :: MonadBuild m => ControlNode -> m () Source #

Registers the given node to be executed before the next run.

Tensor

data ControlNode Source #

A type of graph node which has no outputs. These nodes are valuable for causing side effects when they are run.

data Tensor v a Source #

A named output of a TensorFlow operation.

The type parameter a is the type of the elements in the Tensor. The parameter v is either:

  • Build: An unrendered, immutable value.
  • Value: A rendered, immutable value.
  • Ref: A rendered stateful handle (e.g., a variable).

Note that expr, value, render and renderValue can help convert between the different types of Tensor.

Instances

data Value a Source #

Instances

Monad Value Source # 

Methods

(>>=) :: Value a -> (a -> Value b) -> Value b #

(>>) :: Value a -> Value b -> Value b #

return :: a -> Value a #

fail :: String -> Value a #

Functor Value Source # 

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Applicative Value Source # 

Methods

pure :: a -> Value a #

(<*>) :: Value (a -> b) -> Value a -> Value b #

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

(*>) :: Value a -> Value b -> Value b #

(<*) :: Value a -> Value b -> Value a #

TensorKind Value Source # 

Methods

toBuild :: Value a -> Build a Source #

Rendered (Tensor Value) Source # 

data Ref a Source #

Instances

Monad Ref Source # 

Methods

(>>=) :: Ref a -> (a -> Ref b) -> Ref b #

(>>) :: Ref a -> Ref b -> Ref b #

return :: a -> Ref a #

fail :: String -> Ref a #

Functor Ref Source # 

Methods

fmap :: (a -> b) -> Ref a -> Ref b #

(<$) :: a -> Ref b -> Ref a #

Applicative Ref Source # 

Methods

pure :: a -> Ref a #

(<*>) :: Ref (a -> b) -> Ref a -> Ref b #

liftA2 :: (a -> b -> c) -> Ref a -> Ref b -> Ref c #

(*>) :: Ref a -> Ref b -> Ref b #

(<*) :: Ref a -> Ref b -> Ref a #

TensorKind Ref Source # 

Methods

toBuild :: Ref a -> Build a Source #

Rendered (Tensor Ref) Source # 

value :: Tensor Ref a -> Tensor Value a Source #

Cast a 'Tensor Ref' into a 'Tensor Value'. This behaves like a no-op.

tensorFromName :: TensorKind v => Text -> Tensor v a Source #

Create a Tensor for a given name. This can be used to reference nodes in a GraphDef that was loaded via addGraphDef. TODO(judahjacobson): add more safety checks here.

Element types

class TensorType a Source #

The class of scalar types supported by tensorflow.

Minimal complete definition

tensorType, tensorRefType, tensorVal

Instances

TensorType Bool Source # 
TensorType Double Source # 
TensorType Float Source # 
TensorType Int8 Source # 
TensorType Int16 Source # 
TensorType Int32 Source # 
TensorType Int64 Source # 
TensorType Word8 Source # 
TensorType Word16 Source # 
TensorType Word32 Source # 
TensorType Word64 Source # 
TensorType ByteString Source # 
TensorType Variant Source # 
TensorType ResourceHandle Source # 
TensorType (Complex Double) Source # 
TensorType (Complex Float) Source # 

data TensorData a Source #

Tensor data with the correct memory layout for tensorflow.

Instances

(TensorType a, (~) * a a') => Fetchable (Tensor v a) (TensorData a') Source # 

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.

Minimal complete definition

decodeTensorData, encodeTensorData

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

TensorDataType Vector Bool Source # 
TensorDataType Vector Double Source # 
TensorDataType Vector Float Source # 
TensorDataType Vector Int8 Source # 
TensorDataType Vector Int16 Source # 
TensorDataType Vector Int32 Source # 
TensorDataType Vector Int64 Source # 
TensorDataType Vector Word8 Source # 
TensorDataType Vector Word16 Source # 
(Storable a, TensorDataType Vector a, TensorType a) => TensorDataType Vector a Source # 

Methods

decodeTensorData :: TensorData a -> Vector a Source #

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

TensorDataType Vector ByteString Source # 
(TensorDataType Vector a, TensorType a) => TensorDataType Scalar a Source # 
TensorDataType Vector (Complex Double) Source # 
TensorDataType Vector (Complex Float) Source # 

newtype Scalar a Source #

Constructors

Scalar 

Fields

Instances

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

Methods

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

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

Floating a => Floating (Scalar a) Source # 

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 # 

Methods

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

recip :: Scalar a -> Scalar a #

fromRational :: Rational -> Scalar a #

Num a => Num (Scalar a) Source # 

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 # 

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 # 

Methods

toRational :: Scalar a -> Rational #

RealFloat a => RealFloat (Scalar a) Source # 
RealFrac a => RealFrac (Scalar a) Source # 

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 # 

Methods

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

show :: Scalar a -> String #

showList :: [Scalar a] -> ShowS #

IsString a => IsString (Scalar a) Source # 

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

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 = () 

Op combinators

colocateWith :: (MonadBuild m, Rendered t) => t b -> m a -> m a Source #

Places all nodes rendered in the given Build action on the same device as the given Tensor (see also withDevice). Make sure that the action has side effects of rendering the desired tensors. A pure return would not have the desired effect.

newtype Device Source #

A device that a node can be assigned to. There's a naming convention where the device names are constructed from job and replica names.

Constructors

Device 

Fields

withDevice :: MonadBuild m => Maybe Device -> m a -> m a Source #

Set a device for all nodes rendered in the given Build action (unless further overridden by another use of withDevice).

withNameScope :: MonadBuild m => Text -> m a -> m a Source #

Prepend a scope to all nodes rendered in the given Build action.

Dependencies

withControlDependencies :: (MonadBuild m, Nodes t) => t -> m a -> m a Source #

Modify a Build action, such that all new ops rendered in it will depend on the nodes in the first argument.

group :: (MonadBuild m, Nodes t) => t -> m ControlNode Source #

Create an op that groups multiple operations.

When this op finishes, all ops in the input n have finished. This op has no output.

Misc

noOp :: MonadBuild m => m ControlNode Source #

Does nothing. Only useful as a placeholder for control edges.