tensorflow-0.1.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 Session a

data Options

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

Instances

Default Options 

sessionConfig :: Lens' Options ConfigProto

Uses the specified config for the created session.

sessionTarget :: Lens' Options ByteString

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

sessionTracer :: Lens' Options Tracer

Uses the given logger to monitor session progress.

runSession :: Session a -> IO a

Run Session actions in a new TensorFlow session.

runSessionWithOptions :: Options -> Session a -> IO a

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

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

Methods

build :: Build a -> m a

Running graphs

class Nodes t => Fetchable t a

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 
Fetchable t a => Fetchable [t] [a] 
(~) * l (List ([] *)) => Fetchable (ListOf f ([] *)) l 
(TensorType a, TensorDataType s a, (~) * a a') => Fetchable (Tensor v a) (s a') 
(TensorType a, (~) * a a') => Fetchable (Tensor v a) (TensorData a') 
(Fetchable t1 a1, Fetchable t2 a2) => Fetchable (t1, t2) (a1, a2) 
(Fetchable (f t) a, Fetchable (ListOf f ts) (List as), (~) (* -> *) i Identity) => Fetchable (ListOf f ((:) * t ts)) (ListOf i ((:) * a as)) 
(Fetchable t1 a1, Fetchable t2 a2, Fetchable t3 a3) => Fetchable (t1, t2, t3) (a1, a2, a3) 

class Nodes t

Types that contain ops which can be run.

Minimal complete definition

getNodes

Instances

Nodes ControlNode 
Nodes t => Nodes [t] 
(Nodes t1, Nodes t2) => Nodes (t1, t2) 
(Nodes (f a), Nodes (ListOf f as)) => Nodes (ListOf f ((:) * a as)) 
Nodes (ListOf f ([] *)) 
Nodes (Tensor v a) 
(Nodes t1, Nodes t2, Nodes t3) => Nodes (t1, t2, t3) 

run :: Fetchable t a => t -> Session a

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

run_ :: Nodes t => t -> Session ()

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

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

feed :: Rendered v => Tensor v a -> TensorData a -> Feed

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 :: Fetchable t a => [Feed] -> t -> Session a

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_ :: Nodes t => [Feed] -> t -> Session ()

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

Arguments

:: Nodes t 
=> t

Node to evaluate concurrently.

-> Session () 

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

An action for building nodes in a TensorFlow graph.

data BuildT m a

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

Instances

MonadTrans BuildT 
TensorKind Build 
Monad m => MonadState GraphState (BuildT m) 
Monad m => Monad (BuildT m) 
Functor m => Functor (BuildT m) 
Monad m => Applicative (BuildT m) 
MonadIO m => MonadIO (BuildT m) 
MonadThrow m => MonadThrow (BuildT m) 
MonadMask m => MonadMask (BuildT m) 
MonadCatch m => MonadCatch (BuildT m) 
Monad m => MonadBuild (BuildT m) 
TensorTypes as => PureResult (TensorList Build as) 
PureResult (Tensor Build a) 

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

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

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

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

Tensor

data ControlNode

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

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

BuildInputs (ListOf (Tensor v) as) 
BuildInputs (Tensor v a) 
TensorTypes as => PureResult (TensorList Build as) 
PureResult (Tensor Build a) 
(Rendered v, TensorTypes as) => BuildResult (TensorList v as) 
Rendered v => BuildResult (Tensor v a) 
Nodes (Tensor v a) 
(TensorType a, TensorDataType s a, (~) * a a') => Fetchable (Tensor v a) (s a') 
(TensorType a, (~) * a a') => Fetchable (Tensor v a) (TensorData a') 

value :: Tensor Ref a -> Tensor Value a

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

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

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.

expr :: TensorKind v => Tensor v a -> Tensor Build a

Element types

data TensorData a

Tensor data with the correct memory layout for tensorflow.

Instances

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

class TensorType a => TensorDataType s a where

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

Decode the bytes of a TensorData into an s.

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

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

newtype Scalar a

Constructors

Scalar 

Fields

unScalar :: a
 

Instances

TensorDataType Vector a => TensorDataType Scalar a 
Eq a => Eq (Scalar a) 
Floating a => Floating (Scalar a) 
Fractional a => Fractional (Scalar a) 
Num a => Num (Scalar a) 
Ord a => Ord (Scalar a) 
Real a => Real (Scalar a) 
RealFloat a => RealFloat (Scalar a) 
RealFrac a => RealFrac (Scalar a) 
Show a => Show (Scalar a) 
IsString a => IsString (Scalar a) 

newtype Shape

Shape (dimensions) of a tensor.

Constructors

Shape [Int64] 

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

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

A constraint checking that two types are different.

Equations

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

Op combinators

colocateWith :: (MonadBuild m, Rendered v) => Tensor v b -> m a -> m a

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

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

deviceName :: Text
 

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

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

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

Dependencies

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

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

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

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