1
0
mirror of https://github.com/tensorflow/haskell.git synced 2024-06-02 19:13:34 +02:00
tensorflow-haskell/docs/haddock/tensorflow-0.1.0.0/tensorflow.txt
Greg Steuck ea8b62e47b Haddock (#3)
* Trivial script for regenerating haddocks: exclude .haddock files.

* Haddock regen
2016-10-25 12:43:06 -07:00

627 lines
27 KiB
Plaintext

-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | TensorFlow bindings.
--
-- Please see README.md
@package tensorflow
@version 0.1.0.0
-- | Originally taken from internal proto-lens code.
module TensorFlow.Internal.VarInt
-- | Decode an unsigned varint.
getVarInt :: Parser Word64
-- | Encode a Word64.
putVarInt :: Word64 -> Builder
module TensorFlow.Internal.FFI
data TensorFlowException
TensorFlowException :: Code -> Text -> TensorFlowException
data Session
-- | Runs the given action after creating a session with options populated
-- by the given optionSetter.
withSession :: (SessionOptions -> IO ()) -> ((IO () -> IO ()) -> Session -> IO a) -> IO a
extendGraph :: Session -> GraphDef -> IO ()
run :: Session -> [(ByteString, TensorData)] -> [ByteString] -> [ByteString] -> IO [TensorData]
-- | All of the data needed to represent a tensor.
data TensorData
TensorData :: [Int64] -> !DataType -> !(Vector Word8) -> TensorData
[tensorDataDimensions] :: TensorData -> [Int64]
[tensorDataType] :: TensorData -> !DataType
[tensorDataBytes] :: TensorData -> !(Vector Word8)
setSessionConfig :: ConfigProto -> SessionOptions -> IO ()
setSessionTarget :: ByteString -> SessionOptions -> IO ()
-- | Returns the serialized OpList of all OpDefs defined in this address
-- space.
getAllOpList :: IO ByteString
-- | Serializes the given msg and provides it as (ptr,len) argument to the
-- given action.
useProtoAsVoidPtrLen :: (Message msg, Num c) => msg -> (Ptr b -> c -> IO a) -> IO a
instance GHC.Classes.Eq TensorFlow.Internal.FFI.TensorData
instance GHC.Show.Show TensorFlow.Internal.FFI.TensorData
instance GHC.Classes.Eq TensorFlow.Internal.FFI.TensorFlowException
instance GHC.Show.Show TensorFlow.Internal.FFI.TensorFlowException
instance GHC.Exception.Exception TensorFlow.Internal.FFI.TensorFlowException
module TensorFlow.Types
-- | The class of scalar types supported by tensorflow.
class TensorType a
tensorType :: TensorType a => a -> DataType
tensorRefType :: TensorType a => a -> DataType
tensorVal :: TensorType a => Lens' TensorProto [a]
-- | Decode the bytes of a TensorData into a Vector.
decodeTensorData :: TensorType a => TensorData a -> Vector a
-- | Encode a Vector into a TensorData.
--
-- The values should be in row major order, e.g.,
--
-- element 0: index (0, ..., 0) element 1: index (0, ..., 1) ...
encodeTensorData :: TensorType a => Shape -> Vector a -> TensorData a
-- | Data about a tensor that is encoded for the TensorFlow APIs.
newtype TensorData a
TensorData :: TensorData -> TensorData a
[unTensorData] :: TensorData a -> TensorData
-- | Shape (dimensions) of a tensor.
newtype Shape
Shape :: [Int64] -> Shape
protoShape :: Lens' TensorShapeProto Shape
class Attribute a
attrLens :: Attribute a => Lens' AttrValue a
-- | A <a>Constraint</a> specifying the possible choices of a
-- <a>TensorType</a>.
--
-- We implement a <a>Constraint</a> like <tt>OneOf '[Double, Float]
-- a</tt> by turning the natural representation as a conjunction, i.e.,
--
-- <pre>
-- a == Double || a == Float
-- </pre>
--
-- into a disjunction like
--
-- <pre>
-- a /= Int32 &amp;&amp; a /= Int64 &amp;&amp; a /= ByteString &amp;&amp; ...
-- </pre>
--
-- using an enumeration of all the possible <a>TensorType</a>s.
type OneOf ts a = (TensorType a, TensorTypes ts, NoneOf (AllTensorTypes \\ ts) a)
-- | A constraint checking that two types are different.
-- | Helper types to produce a reasonable type error message when the
-- Constraint "a /= a" fails. TODO(judahjacobson): Use ghc-8's
-- CustomTypeErrors for this.
data TypeError a
data ExcludedCase
-- | A <a>Constraint</a> checking that the input is a list of
-- <a>TensorType</a>s. Helps improve error messages when using
-- <a>OneOf</a>.
-- | A constraint that the type <tt>a</tt> doesn't appear in the type list
-- <tt>ts</tt>. Assumes that <tt>a</tt> and each of the elements of
-- <tt>ts</tt> are <a>TensorType</a>s.
-- | Takes the difference of two lists of types.
-- | Removes a type from the given list of types.
-- | An enumeration of all valid <a>TensorType</a>s.
type AllTensorTypes = '[Float, Double, Int8, Int16, Int32, Int64, Word8, Word16, ByteString, Bool]
instance GHC.Show.Show TensorFlow.Types.Shape
instance TensorFlow.Types.TensorType GHC.Types.Float
instance TensorFlow.Types.TensorType GHC.Types.Double
instance TensorFlow.Types.TensorType GHC.Int.Int32
instance TensorFlow.Types.TensorType GHC.Int.Int64
instance TensorFlow.Types.TensorType GHC.Word.Word8
instance TensorFlow.Types.TensorType GHC.Word.Word16
instance TensorFlow.Types.TensorType GHC.Int.Int16
instance TensorFlow.Types.TensorType GHC.Int.Int8
instance TensorFlow.Types.TensorType Data.ByteString.Internal.ByteString
instance TensorFlow.Types.TensorType GHC.Types.Bool
instance TensorFlow.Types.TensorType (Data.Complex.Complex GHC.Types.Float)
instance TensorFlow.Types.TensorType (Data.Complex.Complex GHC.Types.Double)
instance GHC.Exts.IsList TensorFlow.Types.Shape
instance TensorFlow.Types.Attribute GHC.Types.Float
instance TensorFlow.Types.Attribute Data.ByteString.Internal.ByteString
instance TensorFlow.Types.Attribute GHC.Int.Int64
instance TensorFlow.Types.Attribute Proto.Tensorflow.Core.Framework.Types.DataType
instance TensorFlow.Types.Attribute Proto.Tensorflow.Core.Framework.Tensor.TensorProto
instance TensorFlow.Types.Attribute GHC.Types.Bool
instance TensorFlow.Types.Attribute TensorFlow.Types.Shape
instance TensorFlow.Types.Attribute Proto.Tensorflow.Core.Framework.AttrValue.AttrValue'ListValue
instance TensorFlow.Types.Attribute [Proto.Tensorflow.Core.Framework.Types.DataType]
instance TensorFlow.Types.Attribute [GHC.Int.Int64]
module TensorFlow.Output
-- | A type of graph node which has no outputs. These nodes are valuable
-- for causing side effects when they are run.
newtype ControlNode
ControlNode :: Op -> ControlNode
[unControlNode] :: ControlNode -> Op
-- | 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.
newtype Device
Device :: Text -> Device
[deviceName] :: Device -> Text
-- | The name of a node in the graph. This corresponds to the proto field
-- NodeDef.name. Includes the scope prefix (if any) and a unique
-- identifier (if the node was implicitly named).
newtype NodeName
NodeName :: Text -> NodeName
[unNodeName] :: NodeName -> Text
-- | The representation of a node in a TensorFlow graph.
data Op
-- | Properties are fixed, including the device, name, and scope.
Rendered :: !NodeDef -> Op
-- | Properties are not fixed, and may change depending on which context
-- this op is rendered in.
Unrendered :: !OpDef -> Op
-- | Traverse on the <a>Unrendered</a> of an <a>Op</a>.
--
-- Same implementation as _Left.
opUnrendered :: Traversal' Op OpDef
-- | Op definition. This corresponds somewhat to the <a>NodeDef</a> proto.
data OpDef
OpDef :: !PendingNodeName -> !OpType -> !(Map Text AttrValue) -> [Output] -> [NodeName] -> OpDef
[_opName] :: OpDef -> !PendingNodeName
[_opType] :: OpDef -> !OpType
[_opAttrs] :: OpDef -> !(Map Text AttrValue)
[_opInputs] :: OpDef -> [Output]
[_opControlInputs] :: OpDef -> [NodeName]
opName :: Lens' OpDef PendingNodeName
opType :: Lens' OpDef OpType
opAttr :: Attribute a => Text -> Lens' OpDef a
opInputs :: Lens' OpDef [Output]
opControlInputs :: Lens' OpDef [NodeName]
-- | The type of op of a node in the graph. This corresponds to the proto
-- field NodeDef.op.
newtype OpType
OpType :: Text -> OpType
[unOpType] :: OpType -> Text
newtype OutputIx
OutputIx :: Int -> OutputIx
[unOutputIx] :: OutputIx -> Int
-- | An output of a TensorFlow node.
data Output
Output :: !OutputIx -> !Op -> Output
output :: OutputIx -> Op -> Output
outputIndex :: Lens' Output OutputIx
outputOp :: Lens' Output Op
-- | The name specified for an unrendered Op. If an Op has an ImplicitName,
-- it will be assigned based on the opType plus a unique identifier. Does
-- not contain the "scope" prefix.
data PendingNodeName
ExplicitName :: !Text -> PendingNodeName
ImplicitName :: PendingNodeName
instance GHC.Classes.Ord TensorFlow.Output.Op
instance GHC.Classes.Eq TensorFlow.Output.Op
instance GHC.Show.Show TensorFlow.Output.Output
instance GHC.Classes.Ord TensorFlow.Output.Output
instance GHC.Classes.Eq TensorFlow.Output.Output
instance GHC.Classes.Ord TensorFlow.Output.OpDef
instance GHC.Classes.Eq TensorFlow.Output.OpDef
instance GHC.Show.Show TensorFlow.Output.NodeName
instance GHC.Classes.Ord TensorFlow.Output.NodeName
instance GHC.Classes.Eq TensorFlow.Output.NodeName
instance GHC.Show.Show TensorFlow.Output.PendingNodeName
instance GHC.Classes.Ord TensorFlow.Output.PendingNodeName
instance GHC.Classes.Eq TensorFlow.Output.PendingNodeName
instance Data.String.IsString TensorFlow.Output.Device
instance GHC.Classes.Ord TensorFlow.Output.Device
instance GHC.Classes.Eq TensorFlow.Output.Device
instance GHC.Show.Show TensorFlow.Output.OutputIx
instance GHC.Enum.Enum TensorFlow.Output.OutputIx
instance GHC.Num.Num TensorFlow.Output.OutputIx
instance GHC.Classes.Ord TensorFlow.Output.OutputIx
instance GHC.Classes.Eq TensorFlow.Output.OutputIx
instance GHC.Show.Show TensorFlow.Output.OpType
instance GHC.Classes.Ord TensorFlow.Output.OpType
instance GHC.Classes.Eq TensorFlow.Output.OpType
instance Data.String.IsString TensorFlow.Output.OpType
instance GHC.Show.Show TensorFlow.Output.Device
instance GHC.Show.Show TensorFlow.Output.Op
instance Data.String.IsString TensorFlow.Output.Output
module TensorFlow.Tensor
-- | A named output of a TensorFlow operation.
--
-- The type parameter <tt>a</tt> is the type of the elements in the
-- <a>Tensor</a>. The parameter <tt>v</tt> is either <a>Value</a> or
-- <a>Ref</a>, depending on whether the graph is treating this op output
-- as an immutable <a>Value</a> or a stateful <a>Ref</a> (e.g., a
-- variable). Note that a <tt>Tensor Ref</tt> can be casted into a
-- <tt>Tensor Value</tt> via <a>value</a>.
data Tensor v a
Tensor :: (TensorKind v) -> Output -> Tensor v a
data Value
data Ref
-- | This class provides a runtime switch on whether a <a>Tensor</a> should
-- be treated as a <a>Value</a> or as a <a>Ref</a>.
data TensorKind v
ValueKind :: TensorKind Value
RefKind :: TensorKind Ref
tensorKind :: Lens' (Tensor v a) (TensorKind v)
tensorOutput :: Lens' (Tensor v a) Output
-- | Lens for the attributes of a tensor.
--
-- Only valid if the tensor has not yet been rendered. If the tensor has
-- been rendered, the traversal will be over nothing (nothing can be read
-- or written).
tensorAttr :: Attribute attr => Text -> Traversal' (Tensor v a) attr
-- | Cast a 'Tensor *' into a 'Tensor Value'. Common usage is to cast a Ref
-- into Value. This behaves like a no-op.
value :: Tensor v a -> Tensor Value a
-- | A pair of a <a>Tensor</a> and some data that should be fed into that
-- <a>Tensor</a> when running the graph.
data Feed
Feed :: Output -> TensorData -> Feed
-- | Create a <a>Feed</a> for feeding the given data into a <a>Tensor</a>
-- when running the graph.
--
-- Note that if a <a>Tensor</a> is rendered, its identity may change; so
-- feeding the rendered <a>Tensor</a> may be different than feeding the
-- original <a>Tensor</a>.
feed :: Tensor v a -> TensorData a -> Feed
-- | Create a <a>Tensor</a> for a given name. This can be used to reference
-- nodes in a <tt>GraphDef</tt> that was loaded via <tt>addGraphDef</tt>.
-- TODO(judahjacobson): add more safety checks here.
tensorFromName :: TensorKind v -> Text -> Tensor v a
module TensorFlow.Build
-- | A type of graph node which has no outputs. These nodes are valuable
-- for causing side effects when they are run.
newtype ControlNode
ControlNode :: Op -> ControlNode
[unControlNode] :: ControlNode -> Op
data Unique
explicitName :: Text -> PendingNodeName
implicitName :: PendingNodeName
opDef :: OpType -> OpDef
opDefWithName :: PendingNodeName -> OpType -> OpDef
opName :: Lens' OpDef PendingNodeName
opType :: Lens' OpDef OpType
opAttr :: Attribute a => Text -> Lens' OpDef a
opInputs :: Lens' OpDef [Output]
opControlInputs :: Lens' OpDef [NodeName]
data GraphState
-- | Render a <a>Tensor</a>, fixing its name, scope, device and control
-- inputs from the <a>Build</a> context. Also renders any dependencies of
-- the <a>Tensor</a> that weren't already rendered.
--
-- This operation is idempotent; <tt>render &gt;=&gt; render ===
-- render</tt>. However, rendering a (previously un-rendered)
-- <a>Tensor</a> in two different contexts may result in two different
-- <a>Tensor</a>s.
render :: Tensor v a -> Build (Tensor v a)
-- | Render a <a>Tensor</a> and get its node's name.
renderNodeName :: Tensor v a -> Build NodeName
renderedNodeDefs :: Lens' GraphState (Map NodeName NodeDef)
-- | An action for building nodes in a TensorFlow graph. Used to manage
-- build state internally as part of the <tt>Session</tt> monad.
data BuildT m a
-- | An action for building nodes in a TensorFlow graph.
type Build = BuildT Identity
-- | Registers the given node to be executed before the next <a>run</a>.
addInitializer :: ControlNode -> Build ()
-- | This is Control.Monad.Morph.hoist sans the dependency.
hoistBuildT :: (forall a. m a -> n a) -> BuildT m b -> BuildT n b
evalBuildT :: Monad m => BuildT m a -> m a
runBuildT :: BuildT m a -> m (a, GraphState)
-- | Produce a GraphDef proto representation of the nodes that are rendered
-- in the given <a>Build</a> action.
asGraphDef :: Build a -> GraphDef
addGraphDef :: GraphDef -> Build ()
-- | Get all the initializers that have accumulated so far, and clear that
-- buffer.
flushInitializers :: Monad m => BuildT m [NodeName]
-- | Get all the NodeDefs that have accumulated so far, and clear that
-- buffer.
flushNodeBuffer :: Monad m => BuildT m [NodeDef]
-- | Render the given op if it hasn't been rendered already, and return its
-- name.
getOrAddOp :: Op -> Build NodeName
-- | Add a new node for a given <a>OpDef</a>. This is used for making
-- "stateful" ops which are not safe to dedup (e.g, "variable" and
-- "assign").
addNewOp :: OpDef -> Build NodeDef
-- | Render an <a>Output</a> and return a string representation for the
-- TensorFlow foreign APIs.
renderOutput :: Output -> Build Text
-- | Places all nodes rendered in the given <a>Build</a> action on the same
-- device as the given Tensor (see also <a>withDevice</a>). Make sure
-- that the action has side effects of rendering the desired tensors. A
-- pure return would not have the desired effect.
colocateWith :: Tensor v b -> Build a -> Build a
-- | Modify some part of the state, run an action, and restore the state
-- after that action is done.
withStateLens :: MonadState s m => Lens' s a -> (a -> a) -> m b -> m b
-- | Set a device for all nodes rendered in the given <a>Build</a> action
-- (unless further overridden by another use of withDevice).
withDevice :: Maybe Device -> Build a -> Build a
-- | Prepend a scope to all nodes rendered in the given <a>Build</a>
-- action.
withNameScope :: Text -> Build a -> Build a
-- | Add control inputs to all nodes rendered in the given <a>Build</a>
-- action.
withNodeDependencies :: Set NodeName -> Build a -> Build a
-- | Records the given summary action in Build for retrieval with
-- <a>collectAllSummaries</a>. The summary op is required to produce a
-- Summary protocol buffer in string form. For safety, use the
-- pre-composed functions: Logging.scalarSummary and
-- Logging.histogramSummary.
addSummary :: SummaryTensor -> Build ()
-- | Synonym for the tensors that return serialized Summary proto.
type SummaryTensor = Tensor Value ByteString
-- | Retrieves the summary ops collected thus far. Typically this only
-- happens once, but if <a>buildWithSummary</a> is used repeatedly, the
-- values accumulate.
collectAllSummaries :: Monad m => BuildT m [SummaryTensor]
instance GHC.Base.Monad m => Control.Monad.State.Class.MonadState TensorFlow.Build.GraphState (TensorFlow.Build.BuildT m)
instance Control.Monad.Trans.Class.MonadTrans TensorFlow.Build.BuildT
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (TensorFlow.Build.BuildT m)
instance GHC.Base.Monad m => GHC.Base.Monad (TensorFlow.Build.BuildT m)
instance GHC.Base.Monad m => GHC.Base.Applicative (TensorFlow.Build.BuildT m)
instance GHC.Base.Functor m => GHC.Base.Functor (TensorFlow.Build.BuildT m)
instance GHC.Classes.Ord TensorFlow.Build.PendingNode
instance GHC.Classes.Eq TensorFlow.Build.PendingNode
instance Data.String.IsString TensorFlow.Build.Scope
instance GHC.Classes.Ord TensorFlow.Build.Scope
instance GHC.Classes.Eq TensorFlow.Build.Scope
instance GHC.Enum.Enum TensorFlow.Build.Unique
instance GHC.Classes.Ord TensorFlow.Build.Unique
instance GHC.Classes.Eq TensorFlow.Build.Unique
instance GHC.Show.Show TensorFlow.Build.Scope
module TensorFlow.BuildOp
-- | Class of types that can be used as op outputs.
class OpResult a
-- | Class of types that can be used as op functions.
class BuildOp f
-- | Starts an operation that returns a structured set of tensors
-- (singletons or tuples).
buildOp :: BuildOp f => OpDef -> f
-- | Starts an operation that returns a list of tensors.
buildListOp :: BuildOp f => [Int64] -> OpDef -> f
-- | Returns true if all the integers in each tuple are identical. Throws
-- an error with a descriptive message if not.
eqLengthGuard :: [(String, [(String, Int)])] -> Bool
instance GHC.Show.Show TensorFlow.BuildOp.ResultState
instance (TensorFlow.BuildOp.OpResult a1, TensorFlow.BuildOp.OpResult a2) => TensorFlow.BuildOp.OpResult (a1, a2)
instance (TensorFlow.BuildOp.OpResult a1, TensorFlow.BuildOp.OpResult a2, TensorFlow.BuildOp.OpResult a3) => TensorFlow.BuildOp.OpResult (a1, a2, a3)
instance (TensorFlow.BuildOp.OpResult a1, TensorFlow.BuildOp.OpResult a2, TensorFlow.BuildOp.OpResult a3, TensorFlow.BuildOp.OpResult a4) => TensorFlow.BuildOp.OpResult (a1, a2, a3, a4)
instance (TensorFlow.BuildOp.OpResult a1, TensorFlow.BuildOp.OpResult a2, TensorFlow.BuildOp.OpResult a3, TensorFlow.BuildOp.OpResult a4, TensorFlow.BuildOp.OpResult a5) => TensorFlow.BuildOp.OpResult (a1, a2, a3, a4, a5)
instance (TensorFlow.BuildOp.OpResult a1, TensorFlow.BuildOp.OpResult a2, TensorFlow.BuildOp.OpResult a3, TensorFlow.BuildOp.OpResult a4, TensorFlow.BuildOp.OpResult a5, TensorFlow.BuildOp.OpResult a6) => TensorFlow.BuildOp.OpResult (a1, a2, a3, a4, a5, a6)
instance TensorFlow.BuildOp.OpResult (TensorFlow.Tensor.Tensor TensorFlow.Tensor.Value a)
instance TensorFlow.BuildOp.OpResult (TensorFlow.Tensor.Tensor TensorFlow.Tensor.Ref a)
instance TensorFlow.BuildOp.OpResult TensorFlow.Output.ControlNode
instance TensorFlow.BuildOp.OpResult a => TensorFlow.BuildOp.OpResult [a]
instance TensorFlow.BuildOp.BuildOp TensorFlow.Output.ControlNode
instance TensorFlow.BuildOp.BuildOp (TensorFlow.Tensor.Tensor TensorFlow.Tensor.Value a)
instance TensorFlow.BuildOp.BuildOp (TensorFlow.Tensor.Tensor TensorFlow.Tensor.Ref a)
instance TensorFlow.BuildOp.BuildOp [TensorFlow.Tensor.Tensor TensorFlow.Tensor.Value a]
instance (TensorFlow.BuildOp.OpResult t1, TensorFlow.BuildOp.OpResult t2) => TensorFlow.BuildOp.BuildOp (t1, t2)
instance (TensorFlow.BuildOp.OpResult t1, TensorFlow.BuildOp.OpResult t2, TensorFlow.BuildOp.OpResult t3) => TensorFlow.BuildOp.BuildOp (t1, t2, t3)
instance (TensorFlow.BuildOp.OpResult t1, TensorFlow.BuildOp.OpResult t2, TensorFlow.BuildOp.OpResult t3, TensorFlow.BuildOp.OpResult t4) => TensorFlow.BuildOp.BuildOp (t1, t2, t3, t4)
instance (TensorFlow.BuildOp.OpResult t1, TensorFlow.BuildOp.OpResult t2, TensorFlow.BuildOp.OpResult t3, TensorFlow.BuildOp.OpResult t4, TensorFlow.BuildOp.OpResult t5) => TensorFlow.BuildOp.BuildOp (t1, t2, t3, t4, t5)
instance (TensorFlow.BuildOp.OpResult t1, TensorFlow.BuildOp.OpResult t2, TensorFlow.BuildOp.OpResult t3, TensorFlow.BuildOp.OpResult t4, TensorFlow.BuildOp.OpResult t5, TensorFlow.BuildOp.OpResult t6) => TensorFlow.BuildOp.BuildOp (t1, t2, t3, t4, t5, t6)
instance TensorFlow.BuildOp.OpResult a => TensorFlow.BuildOp.BuildOp (TensorFlow.Build.Build a)
instance TensorFlow.BuildOp.BuildOp f => TensorFlow.BuildOp.BuildOp (TensorFlow.Tensor.Tensor v a -> f)
instance TensorFlow.BuildOp.BuildOp f => TensorFlow.BuildOp.BuildOp ([TensorFlow.Tensor.Tensor v a] -> f)
module TensorFlow.Nodes
-- | Types that contain ops which can be run.
class Nodes t
getNodes :: Nodes t => t -> Build (Set NodeName)
-- | Types that tensor representations (e.g. <a>Tensor</a>,
-- <a>ControlNode</a>) can be fetched into.
--
-- Includes collections of tensors (e.g. tuples).
class Nodes t => Fetchable t a
getFetch :: Fetchable t a => t -> Build (Fetch a)
-- | Fetch action. Keeps track of what needs to be fetched and how to
-- decode the fetched data.
data Fetch a
Fetch :: Set Text -> (Map Text TensorData -> a) -> Fetch a
-- | Nodes to fetch
[fetches] :: Fetch a -> Set Text
-- | Function to create an <tt>a</tt> from the fetched data.
[fetchRestore] :: Fetch a -> Map Text TensorData -> a
nodesUnion :: (Monoid b, Traversable t, Applicative f) => t (f b) -> f b
fetchTensorList :: TensorType a => Tensor v a -> Build (Fetch (Shape, [a]))
fetchTensorVector :: TensorType a => Tensor v a -> Build (Fetch (Shape, Vector a))
newtype Scalar a
Scalar :: a -> Scalar a
[unScalar] :: Scalar a -> a
instance Data.String.IsString a => Data.String.IsString (TensorFlow.Nodes.Scalar a)
instance GHC.Real.RealFrac a => GHC.Real.RealFrac (TensorFlow.Nodes.Scalar a)
instance GHC.Float.RealFloat a => GHC.Float.RealFloat (TensorFlow.Nodes.Scalar a)
instance GHC.Real.Real a => GHC.Real.Real (TensorFlow.Nodes.Scalar a)
instance GHC.Float.Floating a => GHC.Float.Floating (TensorFlow.Nodes.Scalar a)
instance GHC.Real.Fractional a => GHC.Real.Fractional (TensorFlow.Nodes.Scalar a)
instance GHC.Num.Num a => GHC.Num.Num (TensorFlow.Nodes.Scalar a)
instance GHC.Classes.Ord a => GHC.Classes.Ord (TensorFlow.Nodes.Scalar a)
instance GHC.Classes.Eq a => GHC.Classes.Eq (TensorFlow.Nodes.Scalar a)
instance GHC.Show.Show a => GHC.Show.Show (TensorFlow.Nodes.Scalar a)
instance GHC.Base.Functor TensorFlow.Nodes.Fetch
instance GHC.Base.Applicative TensorFlow.Nodes.Fetch
instance (TensorFlow.Nodes.Nodes t1, TensorFlow.Nodes.Nodes t2) => TensorFlow.Nodes.Nodes (t1, t2)
instance (TensorFlow.Nodes.Nodes t1, TensorFlow.Nodes.Nodes t2, TensorFlow.Nodes.Nodes t3) => TensorFlow.Nodes.Nodes (t1, t2, t3)
instance (TensorFlow.Nodes.Fetchable t1 a1, TensorFlow.Nodes.Fetchable t2 a2) => TensorFlow.Nodes.Fetchable (t1, t2) (a1, a2)
instance (TensorFlow.Nodes.Fetchable t1 a1, TensorFlow.Nodes.Fetchable t2 a2, TensorFlow.Nodes.Fetchable t3 a3) => TensorFlow.Nodes.Fetchable (t1, t2, t3) (a1, a2, a3)
instance TensorFlow.Nodes.Nodes t => TensorFlow.Nodes.Nodes [t]
instance TensorFlow.Nodes.Fetchable t a => TensorFlow.Nodes.Fetchable [t] [a]
instance TensorFlow.Nodes.Nodes TensorFlow.Output.ControlNode
instance (a ~ ()) => TensorFlow.Nodes.Fetchable TensorFlow.Output.ControlNode a
instance TensorFlow.Nodes.Nodes (TensorFlow.Tensor.Tensor v a)
instance (TensorFlow.Types.TensorType a, a ~ a') => TensorFlow.Nodes.Fetchable (TensorFlow.Tensor.Tensor v a) (Data.Vector.Vector a')
instance (TensorFlow.Types.TensorType a, a ~ a') => TensorFlow.Nodes.Fetchable (TensorFlow.Tensor.Tensor v a) (TensorFlow.Nodes.Scalar a')
module TensorFlow.ControlFlow
-- | Modify a <a>Build</a> action, such that all new ops rendered in it
-- will depend on the nodes in the first argument.
withControlDependencies :: Nodes t => t -> Build a -> Build a
-- | Create an op that groups multiple operations.
--
-- When this op finishes, all ops in the input <tt>n</tt> have finished.
-- This op has no output.
group :: Nodes t => t -> Build ControlNode
-- | Returns a <a>Tensor</a> with the same shape and contents as the input.
identity :: TensorType a => Tensor v a -> Tensor v a
-- | Does nothing. Only useful as a placeholder for control edges.
noOp :: ControlNode
-- | Returns a <a>Tensor</a> with a given name and the same shape and
-- contents as the input.
--
-- TODO(judahjacobson): This breaks when used with uninitialize
-- <tt>Tensor Ref</tt>s, since <tt>RefIdentity</tt> doesn't have
-- SetAllowsUninitializedInput(). Look into whether we can change that
-- op.
named :: TensorType a => Text -> Tensor v a -> Tensor v a
module TensorFlow.Session
data Session a
-- | Setting of an option for the session (see
-- <a>runSessionWithOptions</a>).
data SessionOption
-- | Uses the specified config for the created session.
sessionConfig :: ConfigProto -> SessionOption
-- | Target can be: "local", ip:port, host:port. The set of supported
-- factories depends on the linked in libraries. REQUIRES
-- "/<i>learning</i>brain/public:tensorflow_remote" dependency for the
-- binary.
sessionTarget :: ByteString -> SessionOption
-- | Run <a>Session</a> actions in a new TensorFlow session.
runSession :: Session a -> IO a
-- | Run <a>Session</a> actions in a new TensorFlow session created with
-- the given option setter actions (<a>sessionTarget</a>,
-- <a>sessionConfig</a>).
runSessionWithOptions :: [SessionOption] -> Session a -> IO a
-- | Lift a <a>Build</a> action into a <a>Session</a>, including any
-- explicit op renderings.
build :: Build a -> Session a
-- | Helper combinator for doing something with the result of a
-- <a>Build</a> action. Example usage:
--
-- <pre>
-- buildAnd run :: Fetchable t a =&gt; Build t -&gt; Session a
-- </pre>
buildAnd :: (a -> Session b) -> Build a -> Session b
-- | Lift a <a>Build</a> action into a <a>Session</a>, including any
-- explicit op renderings. Returns the merged summary ops which can be
-- used for logging, see <a>build</a> for a convenient wrapper.
buildWithSummary :: Build a -> Session (a, [SummaryTensor])
-- | Add all pending rendered nodes to the TensorFlow graph and runs any
-- pending initializers.
--
-- Note that run, runWithFeeds, etc. will all call this function
-- implicitly.
extend :: Session ()
addGraphDef :: GraphDef -> Build ()
-- | Run a subgraph <tt>t</tt>, rendering any dependent nodes that aren't
-- already rendered, and fetch the corresponding values for <tt>a</tt>.
run :: Fetchable t a => t -> Session a
-- | Run a subgraph <tt>t</tt>, rendering any dependent nodes that aren't
-- already rendered, feed the given input values, and fetch the
-- corresponding result values for <tt>a</tt>.
runWithFeeds :: Fetchable t a => [Feed] -> t -> Session a
-- | Run a subgraph <tt>t</tt>, rendering and extending any dependent nodes
-- that aren't already rendered. This behaves like <a>run</a> except that
-- it doesn't do any fetches.
run_ :: Nodes t => t -> Session ()
-- | Run a subgraph <tt>t</tt>, rendering any dependent nodes that aren't
-- already rendered, feed the given input values, and fetch the
-- corresponding result values for <tt>a</tt>. This behaves like
-- <a>runWithFeeds</a> except that it doesn't do any fetches.
runWithFeeds_ :: Nodes t => [Feed] -> t -> 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.
asyncProdNodes :: Nodes t => t -> Session ()
instance Control.Monad.IO.Class.MonadIO TensorFlow.Session.Session
instance GHC.Base.Monad TensorFlow.Session.Session
instance GHC.Base.Applicative TensorFlow.Session.Session
instance GHC.Base.Functor TensorFlow.Session.Session