Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type Session = SessionT IO
- data Options
- sessionConfig :: Lens' Options ConfigProto
- sessionTarget :: Lens' Options ByteString
- sessionTracer :: Lens' Options Tracer
- runSession :: (MonadMask m, MonadIO m) => SessionT m a -> m a
- runSessionWithOptions :: (MonadMask m, MonadIO m) => Options -> SessionT m a -> m a
- class Monad m => MonadBuild m where
- class Nodes t => Fetchable t a
- class Nodes t
- run :: (MonadIO m, Fetchable t a) => t -> SessionT m a
- run_ :: (MonadIO m, Nodes t) => t -> SessionT m ()
- data Feed
- feed :: Rendered t => t a -> TensorData a -> Feed
- runWithFeeds :: (MonadIO m, Fetchable t a) => [Feed] -> t -> SessionT m a
- runWithFeeds_ :: (MonadIO m, Nodes t) => [Feed] -> t -> SessionT m ()
- asyncProdNodes :: (MonadIO m, Nodes t) => t -> SessionT m ()
- type Build = BuildT Identity
- data BuildT m a
- render :: MonadBuild m => Tensor Build a -> m (Tensor Value a)
- asGraphDef :: Build a -> GraphDef
- addGraphDef :: MonadBuild m => GraphDef -> m ()
- opName :: Lens' OpDef PendingNodeName
- opAttr :: Attribute a => Text -> Lens' OpDef a
- addInitializer :: MonadBuild m => ControlNode -> m ()
- data ControlNode
- data Tensor v a
- data Value a
- data Ref a
- value :: Tensor Ref a -> Tensor Value a
- tensorFromName :: TensorKind v => Text -> Tensor v a
- expr :: TensorKind v => Tensor v a -> Tensor Build a
- class TensorType a
- data TensorData a
- class TensorType a => TensorDataType s a where
- decodeTensorData :: TensorData a -> s a
- encodeTensorData :: Shape -> s a -> TensorData a
- type ResourceHandle = ResourceHandleProto
- newtype Scalar a = Scalar {
- unScalar :: a
- newtype Shape = Shape [Int64]
- type OneOf ts a = (TensorType a, TensorTypes' ts, NoneOf (AllTensorTypes \\ ts) a)
- type family a /= b :: Constraint where ...
- colocateWith :: (MonadBuild m, Rendered t) => t b -> m a -> m a
- newtype Device = Device {
- deviceName :: Text
- withDevice :: MonadBuild m => Maybe Device -> m a -> m a
- withNameScope :: MonadBuild m => Text -> m a -> m a
- withControlDependencies :: (MonadBuild m, Nodes t) => t -> m a -> m a
- group :: (MonadBuild m, Nodes t) => t -> m ControlNode
- noOp :: MonadBuild m => m ControlNode
Session
Customization for session. Use the lenses to update:
sessionTarget
, sessionTracer
, sessionConfig
.
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.
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).
Instances
a ~ () => Fetchable ControlNode a Source # | |
Defined in TensorFlow.Nodes | |
Fetchable t a => Fetchable [t] [a] Source # | |
Fetchable t a => Fetchable (Maybe t) (Maybe a) Source # | |
l ~ List ('[] :: [Type]) => Fetchable (ListOf f ('[] :: [Type])) l Source # | |
(TensorType a, TensorDataType s a, a ~ a') => Fetchable (Tensor v a) (s a') Source # | |
(TensorType a, a ~ a') => Fetchable (Tensor v a) (TensorData a') Source # | |
Defined in TensorFlow.Nodes | |
(Fetchable t1 a1, Fetchable t2 a2) => Fetchable (t1, t2) (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 # | |
(Fetchable t1 a1, Fetchable t2 a2, Fetchable t3 a3) => Fetchable (t1, t2, t3) (a1, a2, a3) Source # | |
Types that contain ops which can be run.
Instances
Nodes ControlNode Source # | |
Defined in TensorFlow.Nodes | |
Nodes t => Nodes [t] Source # | |
Nodes t => Nodes (Maybe t) Source # | |
(Nodes t1, Nodes t2) => Nodes (t1, t2) Source # | |
(Nodes (f a), Nodes (ListOf f as)) => Nodes (ListOf f (a ': as)) Source # | |
Nodes (ListOf f ('[] :: [Type])) Source # | |
Nodes (Tensor v a) Source # | |
(Nodes t1, Nodes t2, Nodes t3) => Nodes (t1, t2, t3) 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.
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
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
An action for building nodes in a TensorFlow graph.
Used to manage build state internally as part of the Session
monad.
Instances
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 Value
s.
asGraphDef :: Build a -> GraphDef Source #
Produce a GraphDef proto representation of the nodes that are rendered in
the given Build
action.
addGraphDef :: MonadBuild m => GraphDef -> m () Source #
opName :: Lens' OpDef PendingNodeName 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.
Instances
Nodes ControlNode Source # | |
Defined in TensorFlow.Nodes | |
BuildResult ControlNode Source # | |
Defined in TensorFlow.BuildOp buildResult :: Result ControlNode Source # | |
a ~ () => Fetchable ControlNode a Source # | |
Defined in TensorFlow.Nodes |
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
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.
Instances
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 # | |
Defined in TensorFlow.Nodes |
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.
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
type ResourceHandle = ResourceHandleProto Source #
Instances
Shape (dimensions) of a tensor.
TensorFlow supports shapes of unknown rank, which are represented as
Nothing :: Maybe Shape
in Haskell.
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 TensorType
s.
type family a /= b :: Constraint where ... Source #
A constraint checking that two types are different.
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.
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.
Device | |
|
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.