TensorFlow.Core (original) (raw)

SessionBuilding graphs

class Monad m => MonadBuild m where Source #

Lift a [Build](TensorFlow-Core.html#t:Build "TensorFlow.Core") action into a monad, including any explicit op renderings.

Instances

Instances details

Running graphs

class Nodes t => Fetchable t a Source #

Types that tensor representations (e.g. [Tensor](TensorFlow-Core.html#t:Tensor "TensorFlow.Core"), [ControlNode](TensorFlow-Core.html#t:ControlNode "TensorFlow.Core")) can be fetched into.

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

Instances

Instances details

| a ~ () => Fetchable ControlNode a Source # | | | ----------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: ControlNode -> Build (Fetch a) Source # | | | Fetchable t a => Fetchable [t] [a] Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: [t] -> Build (Fetch [a]) Source # | | | Fetchable t a => Fetchable (Maybe t) (Maybe a) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: Maybe t -> Build (Fetch (Maybe a)) Source # | | | l ~ List ('[] :: [Type]) => Fetchable (ListOf f ('[] :: [Type])) l Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: ListOf f '[] -> Build (Fetch l) Source # | | | (TensorType a, TensorDataType s a, a ~ a') => Fetchable (Tensor v a) (s a') Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: Tensor v a -> Build (Fetch (s a')) Source # | | | (TensorType a, a ~ a') => Fetchable (Tensor v a) (TensorData a') Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: Tensor v a -> Build (Fetch (TensorData a')) Source # | | | (Fetchable t1 a1, Fetchable t2 a2) => Fetchable (t1, t2) (a1, a2) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: (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 # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: 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 # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetFetch :: (t1, t2, t3) -> Build (Fetch (a1, a2, a3)) Source # | |

class Nodes t Source #

Types that contain ops which can be run.

Instances

Instances details

| Nodes ControlNode Source # | | | --------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: ControlNode -> Build (Set NodeName) Source # | | | Nodes t => Nodes [t] Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: [t] -> Build (Set NodeName) Source # | | | Nodes t => Nodes (Maybe t) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: Maybe t -> Build (Set NodeName) Source # | | | (Nodes t1, Nodes t2) => Nodes (t1, t2) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: (t1, t2) -> Build (Set NodeName) Source # | | | (Nodes (f a), Nodes (ListOf f as)) => Nodes (ListOf f (a ': as)) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: ListOf f (a ': as) -> Build (Set NodeName) Source # | | | Nodes (ListOf f ('[] :: [Type])) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: ListOf f '[] -> Build (Set NodeName) Source # | | | Nodes (Tensor v a) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: Tensor v a -> Build (Set NodeName) Source # | | | (Nodes t1, Nodes t2, Nodes t3) => Nodes (t1, t2, t3) Source # | | | Instance detailsDefined in TensorFlow.Nodes MethodsgetNodes :: (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](TensorFlow-Core.html#v:run "TensorFlow.Core") except that it doesn't do any fetches.

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](TensorFlow-Core.html#v:runWithFeeds "TensorFlow.Core") except that it doesn't do any fetches.

Async

asyncProdNodes Source #

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

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.

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

Render a [Tensor](TensorFlow-Core.html#t:Tensor "TensorFlow.Core"), fixing its name, scope, device and control inputs from the [MonadBuild](TensorFlow-Core.html#t:MonadBuild "TensorFlow.Core") context. Also renders any dependencies of the [Tensor](TensorFlow-Core.html#t:Tensor "TensorFlow.Core") that weren't already rendered.

This operation is idempotent; calling [render](TensorFlow-Core.html#v:render "TensorFlow.Core") on the same input in the same context will produce the same result. However, rendering the sameTensor Build in two different contexts may result in two differentTensor Values.

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](TensorFlow-Core.html#t:Tensor "TensorFlow.Core"). The parameter v is either:

Note that [expr](TensorFlow-Core.html#v:expr "TensorFlow.Core"), [value](TensorFlow-Core.html#v:value "TensorFlow.Core"), [render](TensorFlow-Core.html#v:render "TensorFlow.Core") and [renderValue](TensorFlow-Tensor.html#v:renderValue "TensorFlow.Tensor") can help convert between the different types of [Tensor](TensorFlow-Core.html#t:Tensor "TensorFlow.Core").

Element types

data TensorData a Source #

Tensor data with the correct memory layout for tensorflow.

Instances

Instances details

newtype Shape Source #

Shape (dimensions) of a tensor.

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

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

A [Constraint](../base-4.13.0.0/Data-Kind.html#t:Constraint "Data.Kind") specifying the possible choices of a [TensorType](TensorFlow-Core.html#t:TensorType "TensorFlow.Core").

We implement a [Constraint](../base-4.13.0.0/Data-Kind.html#t:Constraint "Data.Kind") 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 [TensorType](TensorFlow-Core.html#t:TensorType "TensorFlow.Core")s.

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

A constraint checking that two types are different.

Op combinators

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

Places all nodes rendered in the given [Build](TensorFlow-Core.html#t:Build "TensorFlow.Core") action on the same device as the given Tensor (see also [withDevice](TensorFlow-Core.html#v:withDevice "TensorFlow.Core")). 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.

Dependencies

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