{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE TypeInType #-}

{-# LANGUAGE OverloadedStrings #-}


module MathFlow.TF where

import GHC.TypeLits
import Data.Singletons
import Data.Singletons.TH
import Data.Promotion.Prelude
import MathFlow.Core
import MathFlow.PyString



assert :: Tensor n t a 
assert = TSym "tf.Assert" 


noGradient :: String -> Tensor n t a 
noGradient op_type = TSym "tf.NoGradient" <+> TArgS "op_type" op_type 


notDifferentiable :: String -> Tensor n t a 
notDifferentiable op_type = TSym "tf.NotDifferentiable" <+> TArgS "op_type" op_type 

tfPrint' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
tfPrint' input_ data' message first_n summarize name = TSym "tf.Print" <+> TArgS "input_" input_ <+> TArgS "data" data' <+> TArgS "message" message <+> TArgS "first_n" first_n <+> TArgS "summarize" summarize <+> TArgS "name" name 
tfPrint :: String -> String -> Tensor n t a 
tfPrint input_ data' = TSym "tf.Print" <+> TArgS "input_" input_ <+> TArgS "data" data' 

abs' :: Tensor n t a -> String -> Tensor n t a 
abs' x name = TSym "tf.abs" <+> TArgT "x" x <+> TArgS "name" name 


accumulateN' :: SingI n => String -> Sing n -> String -> String -> Tensor n t a 
accumulateN' inputs shape tensor_dtype name = TSym "tf.accumulate_n" <+> TArgS "inputs" inputs <+> TArgSing "shape" shape <+> TArgS "tensor_dtype" tensor_dtype <+> TArgS "name" name 
accumulateN :: String -> Tensor n t a 
accumulateN inputs = TSym "tf.accumulate_n" <+> TArgS "inputs" inputs 

acos' :: Tensor n t a -> String -> Tensor n t a 
acos' x name = TSym "tf.acos" <+> TArgT "x" x <+> TArgS "name" name 


add' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
add' x y name = TSym "tf.add" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
add :: Tensor n t a -> Tensor n t a -> Tensor n t a 
add x y = TSym "tf.add" <+> TArgT "x" x <+> TArgT "y" y 


addCheckNumericsOps :: Tensor n t a 
addCheckNumericsOps = TSym "tf.add_check_numerics_ops" 

addN' :: String -> String -> Tensor n t a 
addN' inputs name = TSym "tf.add_n" <+> TArgS "inputs" inputs <+> TArgS "name" name 
addN :: String -> Tensor n t a 
addN inputs = TSym "tf.add_n" <+> TArgS "inputs" inputs 


addToCollection :: String -> String -> Tensor n t a 
addToCollection name value = TSym "tf.add_to_collection" <+> TArgS "name" name <+> TArgS "value" value 


allVariables :: Tensor n t a 
allVariables = TSym "tf.all_variables" 

argMax' :: String -> String -> String -> Tensor n t a 
argMax' input dimension name = TSym "tf.arg_max" <+> TArgS "input" input <+> TArgS "dimension" dimension <+> TArgS "name" name 
argMax :: String -> String -> Tensor n t a 
argMax input dimension = TSym "tf.arg_max" <+> TArgS "input" input <+> TArgS "dimension" dimension 

argMin' :: String -> String -> String -> Tensor n t a 
argMin' input dimension name = TSym "tf.arg_min" <+> TArgS "input" input <+> TArgS "dimension" dimension <+> TArgS "name" name 
argMin :: String -> String -> Tensor n t a 
argMin input dimension = TSym "tf.arg_min" <+> TArgS "input" input <+> TArgS "dimension" dimension 

argmax' :: String -> String -> String -> String -> Tensor n t a 
argmax' input axis name dimension = TSym "tf.argmax" <+> TArgS "input" input <+> TArgS "axis" axis <+> TArgS "name" name <+> TArgS "dimension" dimension 
argmax :: String -> Tensor n t a 
argmax input = TSym "tf.argmax" <+> TArgS "input" input 

argmin' :: String -> String -> String -> String -> Tensor n t a 
argmin' input axis name dimension = TSym "tf.argmin" <+> TArgS "input" input <+> TArgS "axis" axis <+> TArgS "name" name <+> TArgS "dimension" dimension 
argmin :: String -> Tensor n t a 
argmin input = TSym "tf.argmin" <+> TArgS "input" input 


asDtype :: String -> Tensor n t a 
asDtype type_value = TSym "tf.as_dtype" <+> TArgS "type_value" type_value 

asString' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
asString' input precision scientific shortest width fill name = TSym "tf.as_string" <+> TArgS "input" input <+> TArgS "precision" precision <+> TArgS "scientific" scientific <+> TArgS "shortest" shortest <+> TArgS "width" width <+> TArgS "fill" fill <+> TArgS "name" name 
asString :: String -> Tensor n t a 
asString input = TSym "tf.as_string" <+> TArgS "input" input 

asin' :: Tensor n t a -> String -> Tensor n t a 
asin' x name = TSym "tf.asin" <+> TArgT "x" x <+> TArgS "name" name 


assertEqual' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertEqual' x y data' summarize message name = TSym "tf.assert_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertEqual x y = TSym "tf.assert_equal" <+> TArgT "x" x <+> TArgT "y" y 

assertGreater' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertGreater' x y data' summarize message name = TSym "tf.assert_greater" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertGreater :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertGreater x y = TSym "tf.assert_greater" <+> TArgT "x" x <+> TArgT "y" y 

assertGreaterEqual' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertGreaterEqual' x y data' summarize message name = TSym "tf.assert_greater_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertGreaterEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertGreaterEqual x y = TSym "tf.assert_greater_equal" <+> TArgT "x" x <+> TArgT "y" y 

assertInteger' :: Tensor n t a -> String -> String -> Tensor n t a 
assertInteger' x message name = TSym "tf.assert_integer" <+> TArgT "x" x <+> TArgS "message" message <+> TArgS "name" name 
assertInteger :: Tensor n t a -> Tensor n t a 
assertInteger x = TSym "tf.assert_integer" <+> TArgT "x" x 

assertLess' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertLess' x y data' summarize message name = TSym "tf.assert_less" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertLess :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertLess x y = TSym "tf.assert_less" <+> TArgT "x" x <+> TArgT "y" y 

assertLessEqual' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertLessEqual' x y data' summarize message name = TSym "tf.assert_less_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertLessEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertLessEqual x y = TSym "tf.assert_less_equal" <+> TArgT "x" x <+> TArgT "y" y 

assertNegative' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertNegative' x data' summarize message name = TSym "tf.assert_negative" <+> TArgT "x" x <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertNegative :: Tensor n t a -> Tensor n t a 
assertNegative x = TSym "tf.assert_negative" <+> TArgT "x" x 

assertNonNegative' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertNonNegative' x data' summarize message name = TSym "tf.assert_non_negative" <+> TArgT "x" x <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertNonNegative :: Tensor n t a -> Tensor n t a 
assertNonNegative x = TSym "tf.assert_non_negative" <+> TArgT "x" x 

assertNonPositive' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertNonPositive' x data' summarize message name = TSym "tf.assert_non_positive" <+> TArgT "x" x <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertNonPositive :: Tensor n t a -> Tensor n t a 
assertNonPositive x = TSym "tf.assert_non_positive" <+> TArgT "x" x 

assertNoneEqual' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertNoneEqual' x y data' summarize message name = TSym "tf.assert_none_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertNoneEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
assertNoneEqual x y = TSym "tf.assert_none_equal" <+> TArgT "x" x <+> TArgT "y" y 

assertPositive' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
assertPositive' x data' summarize message name = TSym "tf.assert_positive" <+> TArgT "x" x <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertPositive :: Tensor n t a -> Tensor n t a 
assertPositive x = TSym "tf.assert_positive" <+> TArgT "x" x 


assertProperIterable :: String -> Tensor n t a 
assertProperIterable values = TSym "tf.assert_proper_iterable" <+> TArgS "values" values 

assertRank' :: Tensor n t a -> String -> String -> String -> String -> String -> Tensor n t a 
assertRank' x rank data' summarize message name = TSym "tf.assert_rank" <+> TArgT "x" x <+> TArgS "rank" rank <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertRank :: Tensor n t a -> String -> Tensor n t a 
assertRank x rank = TSym "tf.assert_rank" <+> TArgT "x" x <+> TArgS "rank" rank 

assertRankAtLeast' :: Tensor n t a -> String -> String -> String -> String -> String -> Tensor n t a 
assertRankAtLeast' x rank data' summarize message name = TSym "tf.assert_rank_at_least" <+> TArgT "x" x <+> TArgS "rank" rank <+> TArgS "data" data' <+> TArgS "summarize" summarize <+> TArgS "message" message <+> TArgS "name" name 
assertRankAtLeast :: Tensor n t a -> String -> Tensor n t a 
assertRankAtLeast x rank = TSym "tf.assert_rank_at_least" <+> TArgT "x" x <+> TArgS "rank" rank 


assertSameFloatDtype :: Tensor n t a 
assertSameFloatDtype = TSym "tf.assert_same_float_dtype" 

assertScalar' :: Tensor n t a -> String -> Tensor n t a 
assertScalar' tensor name = TSym "tf.assert_scalar" <+> TArgT "tensor" tensor <+> TArgS "name" name 
assertScalar :: Tensor n t a -> Tensor n t a 
assertScalar tensor = TSym "tf.assert_scalar" <+> TArgT "tensor" tensor 

assertType' :: Tensor n t a -> String -> String -> String -> Tensor n t a 
assertType' tensor tf_type message name = TSym "tf.assert_type" <+> TArgT "tensor" tensor <+> TArgS "tf_type" tf_type <+> TArgS "message" message <+> TArgS "name" name 
assertType :: Tensor n t a -> String -> Tensor n t a 
assertType tensor tf_type = TSym "tf.assert_type" <+> TArgT "tensor" tensor <+> TArgS "tf_type" tf_type 


assertVariablesInitialized :: Tensor n t a 
assertVariablesInitialized = TSym "tf.assert_variables_initialized" 

assign' :: String -> String -> String -> String -> String -> Tensor n t a 
assign' ref value validate_shape use_locking name = TSym "tf.assign" <+> TArgS "ref" ref <+> TArgS "value" value <+> TArgS "validate_shape" validate_shape <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
assign :: String -> String -> Tensor n t a 
assign ref value = TSym "tf.assign" <+> TArgS "ref" ref <+> TArgS "value" value 

assignAdd' :: String -> String -> String -> String -> Tensor n t a 
assignAdd' ref value use_locking name = TSym "tf.assign_add" <+> TArgS "ref" ref <+> TArgS "value" value <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
assignAdd :: String -> String -> Tensor n t a 
assignAdd ref value = TSym "tf.assign_add" <+> TArgS "ref" ref <+> TArgS "value" value 

assignSub' :: String -> String -> String -> String -> Tensor n t a 
assignSub' ref value use_locking name = TSym "tf.assign_sub" <+> TArgS "ref" ref <+> TArgS "value" value <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
assignSub :: String -> String -> Tensor n t a 
assignSub ref value = TSym "tf.assign_sub" <+> TArgS "ref" ref <+> TArgS "value" value 

atan' :: Tensor n t a -> String -> Tensor n t a 
atan' x name = TSym "tf.atan" <+> TArgT "x" x <+> TArgS "name" name 


atan2' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
atan2' y x name = TSym "tf.atan2" <+> TArgT "y" y <+> TArgT "x" x <+> TArgS "name" name 
atan2 :: Tensor n t a -> Tensor n t a -> Tensor n t a 
atan2 y x = TSym "tf.atan2" <+> TArgT "y" y <+> TArgT "x" x 

batchToSpace' :: String -> String -> String -> String -> Tensor n t a 
batchToSpace' input crops block_size name = TSym "tf.batch_to_space" <+> TArgS "input" input <+> TArgS "crops" crops <+> TArgS "block_size" block_size <+> TArgS "name" name 
batchToSpace :: String -> String -> String -> Tensor n t a 
batchToSpace input crops block_size = TSym "tf.batch_to_space" <+> TArgS "input" input <+> TArgS "crops" crops <+> TArgS "block_size" block_size 

batchToSpaceNd' :: String -> String -> String -> String -> Tensor n t a 
batchToSpaceNd' input block_shape crops name = TSym "tf.batch_to_space_nd" <+> TArgS "input" input <+> TArgS "block_shape" block_shape <+> TArgS "crops" crops <+> TArgS "name" name 
batchToSpaceNd :: String -> String -> String -> Tensor n t a 
batchToSpaceNd input block_shape crops = TSym "tf.batch_to_space_nd" <+> TArgS "input" input <+> TArgS "block_shape" block_shape <+> TArgS "crops" crops 

betainc' :: Tensor n t a -> Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
betainc' a b x name = TSym "tf.betainc" <+> TArgT "a" a <+> TArgT "b" b <+> TArgT "x" x <+> TArgS "name" name 
betainc :: Tensor n t a -> Tensor n t a -> Tensor n t a -> Tensor n t a 
betainc a b x = TSym "tf.betainc" <+> TArgT "a" a <+> TArgT "b" b <+> TArgT "x" x 

bincount' :: String -> String -> String -> String -> String -> Tensor n t a 
bincount' arr weights minlength maxlength dtype = TSym "tf.bincount" <+> TArgS "arr" arr <+> TArgS "weights" weights <+> TArgS "minlength" minlength <+> TArgS "maxlength" maxlength <+> TArgS "dtype" dtype 
bincount :: String -> Tensor n t a 
bincount arr = TSym "tf.bincount" <+> TArgS "arr" arr 

bitcast' :: String -> String -> String -> Tensor n t a 
bitcast' input type' name = TSym "tf.bitcast" <+> TArgS "input" input <+> TArgS "type" type' <+> TArgS "name" name 
bitcast :: String -> String -> Tensor n t a 
bitcast input type' = TSym "tf.bitcast" <+> TArgS "input" input <+> TArgS "type" type' 

booleanMask' :: Tensor n t a -> String -> String -> Tensor n t a 
booleanMask' tensor mask name = TSym "tf.boolean_mask" <+> TArgT "tensor" tensor <+> TArgS "mask" mask <+> TArgS "name" name 
booleanMask :: Tensor n t a -> String -> Tensor n t a 
booleanMask tensor mask = TSym "tf.boolean_mask" <+> TArgT "tensor" tensor <+> TArgS "mask" mask 


broadcastDynamicShape :: String -> String -> Tensor n t a 
broadcastDynamicShape shape_x shape_y = TSym "tf.broadcast_dynamic_shape" <+> TArgS "shape_x" shape_x <+> TArgS "shape_y" shape_y 


broadcastStaticShape :: String -> String -> Tensor n t a 
broadcastStaticShape shape_x shape_y = TSym "tf.broadcast_static_shape" <+> TArgS "shape_x" shape_x <+> TArgS "shape_y" shape_y 

tfcase' :: String -> String -> String -> String -> String -> Tensor n t a 
tfcase' pred_fn_pairs default' exclusive strict name = TSym "tf.case" <+> TArgS "pred_fn_pairs" pred_fn_pairs <+> TArgS "default" default' <+> TArgS "exclusive" exclusive <+> TArgS "strict" strict <+> TArgS "name" name 
tfcase :: String -> String -> Tensor n t a 
tfcase pred_fn_pairs default' = TSym "tf.case" <+> TArgS "pred_fn_pairs" pred_fn_pairs <+> TArgS "default" default' 

cast' :: Tensor n t a -> String -> String -> Tensor n t a 
cast' x dtype name = TSym "tf.cast" <+> TArgT "x" x <+> TArgS "dtype" dtype <+> TArgS "name" name 
cast :: Tensor n t a -> String -> Tensor n t a 
cast x dtype = TSym "tf.cast" <+> TArgT "x" x <+> TArgS "dtype" dtype 

ceil' :: Tensor n t a -> String -> Tensor n t a 
ceil' x name = TSym "tf.ceil" <+> TArgT "x" x <+> TArgS "name" name 
ceil :: Tensor n t a -> Tensor n t a 
ceil x = TSym "tf.ceil" <+> TArgT "x" x 

checkNumerics' :: Tensor n t a -> String -> String -> Tensor n t a 
checkNumerics' tensor message name = TSym "tf.check_numerics" <+> TArgT "tensor" tensor <+> TArgS "message" message <+> TArgS "name" name 
checkNumerics :: Tensor n t a -> String -> Tensor n t a 
checkNumerics tensor message = TSym "tf.check_numerics" <+> TArgT "tensor" tensor <+> TArgS "message" message 

cholesky' :: String -> String -> Tensor n t a 
cholesky' input name = TSym "tf.cholesky" <+> TArgS "input" input <+> TArgS "name" name 
cholesky :: String -> Tensor n t a 
cholesky input = TSym "tf.cholesky" <+> TArgS "input" input 

choleskySolve' :: String -> String -> String -> Tensor n t a 
choleskySolve' chol rhs name = TSym "tf.cholesky_solve" <+> TArgS "chol" chol <+> TArgS "rhs" rhs <+> TArgS "name" name 
choleskySolve :: String -> String -> Tensor n t a 
choleskySolve chol rhs = TSym "tf.cholesky_solve" <+> TArgS "chol" chol <+> TArgS "rhs" rhs 

clipByAverageNorm' :: String -> String -> String -> Tensor n t a 
clipByAverageNorm' t clip_norm name = TSym "tf.clip_by_average_norm" <+> TArgS "t" t <+> TArgS "clip_norm" clip_norm <+> TArgS "name" name 
clipByAverageNorm :: String -> String -> Tensor n t a 
clipByAverageNorm t clip_norm = TSym "tf.clip_by_average_norm" <+> TArgS "t" t <+> TArgS "clip_norm" clip_norm 

clipByGlobalNorm' :: String -> String -> String -> String -> Tensor n t a 
clipByGlobalNorm' t_list clip_norm use_norm name = TSym "tf.clip_by_global_norm" <+> TArgS "t_list" t_list <+> TArgS "clip_norm" clip_norm <+> TArgS "use_norm" use_norm <+> TArgS "name" name 
clipByGlobalNorm :: String -> String -> Tensor n t a 
clipByGlobalNorm t_list clip_norm = TSym "tf.clip_by_global_norm" <+> TArgS "t_list" t_list <+> TArgS "clip_norm" clip_norm 

clipByNorm' :: String -> String -> String -> String -> Tensor n t a 
clipByNorm' t clip_norm axes name = TSym "tf.clip_by_norm" <+> TArgS "t" t <+> TArgS "clip_norm" clip_norm <+> TArgS "axes" axes <+> TArgS "name" name 
clipByNorm :: String -> String -> Tensor n t a 
clipByNorm t clip_norm = TSym "tf.clip_by_norm" <+> TArgS "t" t <+> TArgS "clip_norm" clip_norm 

clipByValue' :: String -> String -> String -> String -> Tensor n t a 
clipByValue' t clip_value_min clip_value_max name = TSym "tf.clip_by_value" <+> TArgS "t" t <+> TArgS "clip_value_min" clip_value_min <+> TArgS "clip_value_max" clip_value_max <+> TArgS "name" name 
clipByValue :: String -> String -> String -> Tensor n t a 
clipByValue t clip_value_min clip_value_max = TSym "tf.clip_by_value" <+> TArgS "t" t <+> TArgS "clip_value_min" clip_value_min <+> TArgS "clip_value_max" clip_value_max 

complex' :: String -> String -> String -> Tensor n t a 
complex' real imag name = TSym "tf.complex" <+> TArgS "real" real <+> TArgS "imag" imag <+> TArgS "name" name 
complex :: String -> String -> Tensor n t a 
complex real imag = TSym "tf.complex" <+> TArgS "real" real <+> TArgS "imag" imag 

concat' :: String -> String -> String -> Tensor n t a 
concat' values axis name = TSym "tf.concat" <+> TArgS "values" values <+> TArgS "axis" axis <+> TArgS "name" name 
concat :: String -> String -> Tensor n t a 
concat values axis = TSym "tf.concat" <+> TArgS "values" values <+> TArgS "axis" axis 


cond :: Tensor n t a 
cond = TSym "tf.cond" 

confusionMatrix' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
confusionMatrix' labels predictions num_classes dtype name weights = TSym "tf.confusion_matrix" <+> TArgS "labels" labels <+> TArgS "predictions" predictions <+> TArgS "num_classes" num_classes <+> TArgS "dtype" dtype <+> TArgS "name" name <+> TArgS "weights" weights 
confusionMatrix :: String -> String -> Tensor n t a 
confusionMatrix labels predictions = TSym "tf.confusion_matrix" <+> TArgS "labels" labels <+> TArgS "predictions" predictions 

conj' :: Tensor n t a -> String -> Tensor n t a 
conj' x name = TSym "tf.conj" <+> TArgT "x" x <+> TArgS "name" name 
conj :: Tensor n t a -> Tensor n t a 
conj x = TSym "tf.conj" <+> TArgT "x" x 

constant' :: SingI n => String -> String -> Sing n -> String -> String -> Tensor n t a 
constant' value dtype shape name verify_shape = TSym "tf.constant" <+> TArgS "value" value <+> TArgS "dtype" dtype <+> TArgSing "shape" shape <+> TArgS "name" name <+> TArgS "verify_shape" verify_shape 
constant :: String -> Tensor n t a 
constant value = TSym "tf.constant" <+> TArgS "value" value 


container :: String -> Tensor n t a 
container container_name = TSym "tf.container" <+> TArgS "container_name" container_name 


controlDependencies :: String -> Tensor n t a 
controlDependencies control_inputs = TSym "tf.control_dependencies" <+> TArgS "control_inputs" control_inputs 

convertToTensor' :: String -> String -> String -> String -> Tensor n t a 
convertToTensor' value dtype name preferred_dtype = TSym "tf.convert_to_tensor" <+> TArgS "value" value <+> TArgS "dtype" dtype <+> TArgS "name" name <+> TArgS "preferred_dtype" preferred_dtype 
convertToTensor :: String -> Tensor n t a 
convertToTensor value = TSym "tf.convert_to_tensor" <+> TArgS "value" value 

convertToTensorOrIndexedSlices' :: String -> String -> String -> Tensor n t a 
convertToTensorOrIndexedSlices' value dtype name = TSym "tf.convert_to_tensor_or_indexed_slices" <+> TArgS "value" value <+> TArgS "dtype" dtype <+> TArgS "name" name 
convertToTensorOrIndexedSlices :: String -> Tensor n t a 
convertToTensorOrIndexedSlices value = TSym "tf.convert_to_tensor_or_indexed_slices" <+> TArgS "value" value 

convertToTensorOrSparseTensor' :: String -> String -> String -> Tensor n t a 
convertToTensorOrSparseTensor' value dtype name = TSym "tf.convert_to_tensor_or_sparse_tensor" <+> TArgS "value" value <+> TArgS "dtype" dtype <+> TArgS "name" name 
convertToTensorOrSparseTensor :: String -> Tensor n t a 
convertToTensorOrSparseTensor value = TSym "tf.convert_to_tensor_or_sparse_tensor" <+> TArgS "value" value 

cos' :: Tensor n t a -> String -> Tensor n t a 
cos' x name = TSym "tf.cos" <+> TArgT "x" x <+> TArgS "name" name 


countNonzero' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
countNonzero' input_tensor axis keep_dims dtype name reduction_indices = TSym "tf.count_nonzero" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "dtype" dtype <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
countNonzero :: String -> Tensor n t a 
countNonzero input_tensor = TSym "tf.count_nonzero" <+> TArgS "input_tensor" input_tensor 

countUpTo' :: String -> String -> String -> Tensor n t a 
countUpTo' ref limit name = TSym "tf.count_up_to" <+> TArgS "ref" ref <+> TArgS "limit" limit <+> TArgS "name" name 
countUpTo :: String -> String -> Tensor n t a 
countUpTo ref limit = TSym "tf.count_up_to" <+> TArgS "ref" ref <+> TArgS "limit" limit 

createPartitionedVariables' :: SingI n => Sing n -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
createPartitionedVariables' shape slicing initializer dtype trainable collections name reuse = TSym "tf.create_partitioned_variables" <+> TArgSing "shape" shape <+> TArgS "slicing" slicing <+> TArgS "initializer" initializer <+> TArgS "dtype" dtype <+> TArgS "trainable" trainable <+> TArgS "collections" collections <+> TArgS "name" name <+> TArgS "reuse" reuse 
createPartitionedVariables :: SingI n => Sing n -> String -> String -> Tensor n t a 
createPartitionedVariables shape slicing initializer = TSym "tf.create_partitioned_variables" <+> TArgSing "shape" shape <+> TArgS "slicing" slicing <+> TArgS "initializer" initializer 

cross' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
cross' a b name = TSym "tf.cross" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "name" name 
cross :: Tensor n t a -> Tensor n t a -> Tensor n t a 
cross a b = TSym "tf.cross" <+> TArgT "a" a <+> TArgT "b" b 

cumprod' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
cumprod' x axis exclusive reverse name = TSym "tf.cumprod" <+> TArgT "x" x <+> TArgS "axis" axis <+> TArgS "exclusive" exclusive <+> TArgS "reverse" reverse <+> TArgS "name" name 
cumprod :: Tensor n t a -> Tensor n t a 
cumprod x = TSym "tf.cumprod" <+> TArgT "x" x 

cumsum' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
cumsum' x axis exclusive reverse name = TSym "tf.cumsum" <+> TArgT "x" x <+> TArgS "axis" axis <+> TArgS "exclusive" exclusive <+> TArgS "reverse" reverse <+> TArgS "name" name 
cumsum :: Tensor n t a -> Tensor n t a 
cumsum x = TSym "tf.cumsum" <+> TArgT "x" x 

decodeBase64' :: String -> String -> Tensor n t a 
decodeBase64' input name = TSym "tf.decode_base64" <+> TArgS "input" input <+> TArgS "name" name 
decodeBase64 :: String -> Tensor n t a 
decodeBase64 input = TSym "tf.decode_base64" <+> TArgS "input" input 

decodeCsv' :: String -> String -> String -> String -> Tensor n t a 
decodeCsv' records record_defaults field_delim name = TSym "tf.decode_csv" <+> TArgS "records" records <+> TArgS "record_defaults" record_defaults <+> TArgS "field_delim" field_delim <+> TArgS "name" name 
decodeCsv :: String -> String -> Tensor n t a 
decodeCsv records record_defaults = TSym "tf.decode_csv" <+> TArgS "records" records <+> TArgS "record_defaults" record_defaults 

decodeJsonExample' :: String -> String -> Tensor n t a 
decodeJsonExample' json_examples name = TSym "tf.decode_json_example" <+> TArgS "json_examples" json_examples <+> TArgS "name" name 
decodeJsonExample :: String -> Tensor n t a 
decodeJsonExample json_examples = TSym "tf.decode_json_example" <+> TArgS "json_examples" json_examples 

decodeRaw' :: String -> String -> String -> String -> Tensor n t a 
decodeRaw' bytes out_type little_endian name = TSym "tf.decode_raw" <+> TArgS "bytes" bytes <+> TArgS "out_type" out_type <+> TArgS "little_endian" little_endian <+> TArgS "name" name 
decodeRaw :: String -> String -> Tensor n t a 
decodeRaw bytes out_type = TSym "tf.decode_raw" <+> TArgS "bytes" bytes <+> TArgS "out_type" out_type 

deleteSessionTensor' :: String -> String -> Tensor n t a 
deleteSessionTensor' handle name = TSym "tf.delete_session_tensor" <+> TArgS "handle" handle <+> TArgS "name" name 
deleteSessionTensor :: String -> Tensor n t a 
deleteSessionTensor handle = TSym "tf.delete_session_tensor" <+> TArgS "handle" handle 

depthToSpace' :: String -> String -> String -> Tensor n t a 
depthToSpace' input block_size name = TSym "tf.depth_to_space" <+> TArgS "input" input <+> TArgS "block_size" block_size <+> TArgS "name" name 
depthToSpace :: String -> String -> Tensor n t a 
depthToSpace input block_size = TSym "tf.depth_to_space" <+> TArgS "input" input <+> TArgS "block_size" block_size 

dequantize' :: String -> String -> String -> String -> String -> Tensor n t a 
dequantize' input min_range max_range mode name = TSym "tf.dequantize" <+> TArgS "input" input <+> TArgS "min_range" min_range <+> TArgS "max_range" max_range <+> TArgS "mode" mode <+> TArgS "name" name 
dequantize :: String -> String -> String -> Tensor n t a 
dequantize input min_range max_range = TSym "tf.dequantize" <+> TArgS "input" input <+> TArgS "min_range" min_range <+> TArgS "max_range" max_range 

deserializeManySparse' :: String -> String -> String -> String -> Tensor n t a 
deserializeManySparse' serialized_sparse dtype rank name = TSym "tf.deserialize_many_sparse" <+> TArgS "serialized_sparse" serialized_sparse <+> TArgS "dtype" dtype <+> TArgS "rank" rank <+> TArgS "name" name 
deserializeManySparse :: String -> String -> Tensor n t a 
deserializeManySparse serialized_sparse dtype = TSym "tf.deserialize_many_sparse" <+> TArgS "serialized_sparse" serialized_sparse <+> TArgS "dtype" dtype 


device :: String -> Tensor n t a 
device device_name_or_function = TSym "tf.device" <+> TArgS "device_name_or_function" device_name_or_function 

diag' :: String -> String -> Tensor n t a 
diag' diagonal name = TSym "tf.diag" <+> TArgS "diagonal" diagonal <+> TArgS "name" name 
diag :: String -> Tensor n t a 
diag diagonal = TSym "tf.diag" <+> TArgS "diagonal" diagonal 

diagPart' :: String -> String -> Tensor n t a 
diagPart' input name = TSym "tf.diag_part" <+> TArgS "input" input <+> TArgS "name" name 
diagPart :: String -> Tensor n t a 
diagPart input = TSym "tf.diag_part" <+> TArgS "input" input 

digamma' :: Tensor n t a -> String -> Tensor n t a 
digamma' x name = TSym "tf.digamma" <+> TArgT "x" x <+> TArgS "name" name 
digamma :: Tensor n t a -> Tensor n t a 
digamma x = TSym "tf.digamma" <+> TArgT "x" x 

div' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
div' x y name = TSym "tf.div" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
div :: Tensor n t a -> Tensor n t a -> Tensor n t a 
div x y = TSym "tf.div" <+> TArgT "x" x <+> TArgT "y" y 

divide' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
divide' x y name = TSym "tf.divide" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
divide :: Tensor n t a -> Tensor n t a -> Tensor n t a 
divide x y = TSym "tf.divide" <+> TArgT "x" x <+> TArgT "y" y 

dynamicPartition' :: String -> String -> String -> String -> Tensor n t a 
dynamicPartition' data' partitions num_partitions name = TSym "tf.dynamic_partition" <+> TArgS "data" data' <+> TArgS "partitions" partitions <+> TArgS "num_partitions" num_partitions <+> TArgS "name" name 
dynamicPartition :: String -> String -> String -> Tensor n t a 
dynamicPartition data' partitions num_partitions = TSym "tf.dynamic_partition" <+> TArgS "data" data' <+> TArgS "partitions" partitions <+> TArgS "num_partitions" num_partitions 

dynamicStitch' :: String -> String -> String -> Tensor n t a 
dynamicStitch' indices data' name = TSym "tf.dynamic_stitch" <+> TArgS "indices" indices <+> TArgS "data" data' <+> TArgS "name" name 
dynamicStitch :: String -> String -> Tensor n t a 
dynamicStitch indices data' = TSym "tf.dynamic_stitch" <+> TArgS "indices" indices <+> TArgS "data" data' 

editDistance' :: String -> String -> String -> String -> Tensor n t a 
editDistance' hypothesis truth normalize name = TSym "tf.edit_distance" <+> TArgS "hypothesis" hypothesis <+> TArgS "truth" truth <+> TArgS "normalize" normalize <+> TArgS "name" name 
editDistance :: String -> String -> Tensor n t a 
editDistance hypothesis truth = TSym "tf.edit_distance" <+> TArgS "hypothesis" hypothesis <+> TArgS "truth" truth 


einsum :: String -> Tensor n t a 
einsum equation = TSym "tf.einsum" <+> TArgS "equation" equation 

encodeBase64' :: String -> String -> String -> Tensor n t a 
encodeBase64' input pad name = TSym "tf.encode_base64" <+> TArgS "input" input <+> TArgS "pad" pad <+> TArgS "name" name 
encodeBase64 :: String -> Tensor n t a 
encodeBase64 input = TSym "tf.encode_base64" <+> TArgS "input" input 

equal' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
equal' x y name = TSym "tf.equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
equal :: Tensor n t a -> Tensor n t a -> Tensor n t a 
equal x y = TSym "tf.equal" <+> TArgT "x" x <+> TArgT "y" y 

erf' :: Tensor n t a -> String -> Tensor n t a 
erf' x name = TSym "tf.erf" <+> TArgT "x" x <+> TArgS "name" name 
erf :: Tensor n t a -> Tensor n t a 
erf x = TSym "tf.erf" <+> TArgT "x" x 

erfc' :: Tensor n t a -> String -> Tensor n t a 
erfc' x name = TSym "tf.erfc" <+> TArgT "x" x <+> TArgS "name" name 
erfc :: Tensor n t a -> Tensor n t a 
erfc x = TSym "tf.erfc" <+> TArgT "x" x 

exp' :: Tensor n t a -> String -> Tensor n t a 
exp' x name = TSym "tf.exp" <+> TArgT "x" x <+> TArgS "name" name 
exp :: Tensor n t a -> Tensor n t a 
exp x = TSym "tf.exp" <+> TArgT "x" x 

expandDims' :: String -> String -> String -> String -> Tensor n t a 
expandDims' input axis name dim = TSym "tf.expand_dims" <+> TArgS "input" input <+> TArgS "axis" axis <+> TArgS "name" name <+> TArgS "dim" dim 
expandDims :: String -> Tensor n t a 
expandDims input = TSym "tf.expand_dims" <+> TArgS "input" input 

expm1' :: Tensor n t a -> String -> Tensor n t a 
expm1' x name = TSym "tf.expm1" <+> TArgT "x" x <+> TArgS "name" name 
expm1 :: Tensor n t a -> Tensor n t a 
expm1 x = TSym "tf.expm1" <+> TArgT "x" x 

extractImagePatches' :: SingI n => String -> String -> Sing n -> String -> String -> String -> Tensor n t a 
extractImagePatches' images ksizes strides rates padding name = TSym "tf.extract_image_patches" <+> TArgS "images" images <+> TArgS "ksizes" ksizes <+> TArgSing "strides" strides <+> TArgS "rates" rates <+> TArgS "padding" padding <+> TArgS "name" name 
extractImagePatches :: SingI n => String -> String -> Sing n -> String -> String -> Tensor n t a 
extractImagePatches images ksizes strides rates padding = TSym "tf.extract_image_patches" <+> TArgS "images" images <+> TArgS "ksizes" ksizes <+> TArgSing "strides" strides <+> TArgS "rates" rates <+> TArgS "padding" padding 

eye' :: String -> String -> String -> String -> String -> Tensor n t a 
eye' num_rows num_columns batch_shape dtype name = TSym "tf.eye" <+> TArgS "num_rows" num_rows <+> TArgS "num_columns" num_columns <+> TArgS "batch_shape" batch_shape <+> TArgS "dtype" dtype <+> TArgS "name" name 
eye :: String -> Tensor n t a 
eye num_rows = TSym "tf.eye" <+> TArgS "num_rows" num_rows 

fakeQuantWithMinMaxArgs' :: String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxArgs' inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_args" <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxArgs :: String -> Tensor n t a 
fakeQuantWithMinMaxArgs inputs = TSym "tf.fake_quant_with_min_max_args" <+> TArgS "inputs" inputs 

fakeQuantWithMinMaxArgsGradient' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxArgsGradient' gradients inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_args_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxArgsGradient :: String -> String -> Tensor n t a 
fakeQuantWithMinMaxArgsGradient gradients inputs = TSym "tf.fake_quant_with_min_max_args_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs 

fakeQuantWithMinMaxVars' :: String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVars' inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_vars" <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxVars :: String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVars inputs min max = TSym "tf.fake_quant_with_min_max_vars" <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max 

fakeQuantWithMinMaxVarsGradient' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsGradient' gradients inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_vars_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxVarsGradient :: String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsGradient gradients inputs min max = TSym "tf.fake_quant_with_min_max_vars_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max 

fakeQuantWithMinMaxVarsPerChannel' :: String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsPerChannel' inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_vars_per_channel" <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxVarsPerChannel :: String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsPerChannel inputs min max = TSym "tf.fake_quant_with_min_max_vars_per_channel" <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max 

fakeQuantWithMinMaxVarsPerChannelGradient' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsPerChannelGradient' gradients inputs min max num_bits name = TSym "tf.fake_quant_with_min_max_vars_per_channel_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max <+> TArgS "num_bits" num_bits <+> TArgS "name" name 
fakeQuantWithMinMaxVarsPerChannelGradient :: String -> String -> String -> String -> Tensor n t a 
fakeQuantWithMinMaxVarsPerChannelGradient gradients inputs min max = TSym "tf.fake_quant_with_min_max_vars_per_channel_gradient" <+> TArgS "gradients" gradients <+> TArgS "inputs" inputs <+> TArgS "min" min <+> TArgS "max" max 

fft' :: String -> String -> Tensor n t a 
fft' input name = TSym "tf.fft" <+> TArgS "input" input <+> TArgS "name" name 
fft :: String -> Tensor n t a 
fft input = TSym "tf.fft" <+> TArgS "input" input 

fft2d' :: String -> String -> Tensor n t a 
fft2d' input name = TSym "tf.fft2d" <+> TArgS "input" input <+> TArgS "name" name 
fft2d :: String -> Tensor n t a 
fft2d input = TSym "tf.fft2d" <+> TArgS "input" input 

fft3d' :: String -> String -> Tensor n t a 
fft3d' input name = TSym "tf.fft3d" <+> TArgS "input" input <+> TArgS "name" name 
fft3d :: String -> Tensor n t a 
fft3d input = TSym "tf.fft3d" <+> TArgS "input" input 

fill' :: String -> String -> String -> Tensor n t a 
fill' dims value name = TSym "tf.fill" <+> TArgS "dims" dims <+> TArgS "value" value <+> TArgS "name" name 
fill :: String -> String -> Tensor n t a 
fill dims value = TSym "tf.fill" <+> TArgS "dims" dims <+> TArgS "value" value 

fixedSizePartitioner' :: String -> String -> Tensor n t a 
fixedSizePartitioner' num_shards axis = TSym "tf.fixed_size_partitioner" <+> TArgS "num_shards" num_shards <+> TArgS "axis" axis 
fixedSizePartitioner :: String -> Tensor n t a 
fixedSizePartitioner num_shards = TSym "tf.fixed_size_partitioner" <+> TArgS "num_shards" num_shards 

floor' :: Tensor n t a -> String -> Tensor n t a 
floor' x name = TSym "tf.floor" <+> TArgT "x" x <+> TArgS "name" name 
floor :: Tensor n t a -> Tensor n t a 
floor x = TSym "tf.floor" <+> TArgT "x" x 

floorDiv' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
floorDiv' x y name = TSym "tf.floor_div" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
floorDiv :: Tensor n t a -> Tensor n t a -> Tensor n t a 
floorDiv x y = TSym "tf.floor_div" <+> TArgT "x" x <+> TArgT "y" y 

floordiv' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
floordiv' x y name = TSym "tf.floordiv" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
floordiv :: Tensor n t a -> Tensor n t a -> Tensor n t a 
floordiv x y = TSym "tf.floordiv" <+> TArgT "x" x <+> TArgT "y" y 

floormod' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
floormod' x y name = TSym "tf.floormod" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
floormod :: Tensor n t a -> Tensor n t a -> Tensor n t a 
floormod x y = TSym "tf.floormod" <+> TArgT "x" x <+> TArgT "y" y 

foldl' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
foldl' fn elems initializer parallel_iterations back_prop swap_memory name = TSym "tf.foldl" <+> TArgS "fn" fn <+> TArgS "elems" elems <+> TArgS "initializer" initializer <+> TArgS "parallel_iterations" parallel_iterations <+> TArgS "back_prop" back_prop <+> TArgS "swap_memory" swap_memory <+> TArgS "name" name 
foldl :: String -> String -> Tensor n t a 
foldl fn elems = TSym "tf.foldl" <+> TArgS "fn" fn <+> TArgS "elems" elems 

foldr' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
foldr' fn elems initializer parallel_iterations back_prop swap_memory name = TSym "tf.foldr" <+> TArgS "fn" fn <+> TArgS "elems" elems <+> TArgS "initializer" initializer <+> TArgS "parallel_iterations" parallel_iterations <+> TArgS "back_prop" back_prop <+> TArgS "swap_memory" swap_memory <+> TArgS "name" name 
foldr :: String -> String -> Tensor n t a 
foldr fn elems = TSym "tf.foldr" <+> TArgS "fn" fn <+> TArgS "elems" elems 

gather' :: String -> String -> String -> String -> Tensor n t a 
gather' params indices validate_indices name = TSym "tf.gather" <+> TArgS "params" params <+> TArgS "indices" indices <+> TArgS "validate_indices" validate_indices <+> TArgS "name" name 
gather :: String -> String -> Tensor n t a 
gather params indices = TSym "tf.gather" <+> TArgS "params" params <+> TArgS "indices" indices 

gatherNd' :: String -> String -> String -> Tensor n t a 
gatherNd' params indices name = TSym "tf.gather_nd" <+> TArgS "params" params <+> TArgS "indices" indices <+> TArgS "name" name 
gatherNd :: String -> String -> Tensor n t a 
gatherNd params indices = TSym "tf.gather_nd" <+> TArgS "params" params <+> TArgS "indices" indices 

getCollection' :: String -> String -> Tensor n t a 
getCollection' key scope = TSym "tf.get_collection" <+> TArgS "key" key <+> TArgS "scope" scope 
getCollection :: String -> Tensor n t a 
getCollection key = TSym "tf.get_collection" <+> TArgS "key" key 


getCollectionRef :: String -> Tensor n t a 
getCollectionRef key = TSym "tf.get_collection_ref" <+> TArgS "key" key 


getDefaultGraph :: Tensor n t a 
getDefaultGraph = TSym "tf.get_default_graph" 


getDefaultSession :: Tensor n t a 
getDefaultSession = TSym "tf.get_default_session" 


getLocalVariable :: Tensor n t a 
getLocalVariable = TSym "tf.get_local_variable" 


getSeed :: String -> Tensor n t a 
getSeed op_seed = TSym "tf.get_seed" <+> TArgS "op_seed" op_seed 

getSessionHandle' :: String -> String -> Tensor n t a 
getSessionHandle' data' name = TSym "tf.get_session_handle" <+> TArgS "data" data' <+> TArgS "name" name 
getSessionHandle :: String -> Tensor n t a 
getSessionHandle data' = TSym "tf.get_session_handle" <+> TArgS "data" data' 

getSessionTensor' :: String -> String -> String -> Tensor n t a 
getSessionTensor' handle dtype name = TSym "tf.get_session_tensor" <+> TArgS "handle" handle <+> TArgS "dtype" dtype <+> TArgS "name" name 
getSessionTensor :: String -> String -> Tensor n t a 
getSessionTensor handle dtype = TSym "tf.get_session_tensor" <+> TArgS "handle" handle <+> TArgS "dtype" dtype 

getVariable' :: SingI n => String -> Sing n -> String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
getVariable' name shape dtype initializer regularizer trainable collections caching_device partitioner validate_shape use_resource custom_getter = TSym "tf.get_variable" <+> TArgS "name" name <+> TArgSing "shape" shape <+> TArgS "dtype" dtype <+> TArgS "initializer" initializer <+> TArgS "regularizer" regularizer <+> TArgS "trainable" trainable <+> TArgS "collections" collections <+> TArgS "caching_device" caching_device <+> TArgS "partitioner" partitioner <+> TArgS "validate_shape" validate_shape <+> TArgS "use_resource" use_resource <+> TArgS "custom_getter" custom_getter 
getVariable :: String -> Tensor n t a 
getVariable name = TSym "tf.get_variable" <+> TArgS "name" name 


getVariableScope :: Tensor n t a 
getVariableScope = TSym "tf.get_variable_scope" 

globalNorm' :: String -> String -> Tensor n t a 
globalNorm' t_list name = TSym "tf.global_norm" <+> TArgS "t_list" t_list <+> TArgS "name" name 
globalNorm :: String -> Tensor n t a 
globalNorm t_list = TSym "tf.global_norm" <+> TArgS "t_list" t_list 


globalVariables :: Tensor n t a 
globalVariables = TSym "tf.global_variables" 


globalVariablesInitializer :: Tensor n t a 
globalVariablesInitializer = TSym "tf.global_variables_initializer" 

gradients' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
gradients' ys xs grad_ys name colocate_gradients_with_ops gate_gradients aggregation_method = TSym "tf.gradients" <+> TArgS "ys" ys <+> TArgS "xs" xs <+> TArgS "grad_ys" grad_ys <+> TArgS "name" name <+> TArgS "colocate_gradients_with_ops" colocate_gradients_with_ops <+> TArgS "gate_gradients" gate_gradients <+> TArgS "aggregation_method" aggregation_method 
gradients :: String -> String -> Tensor n t a 
gradients ys xs = TSym "tf.gradients" <+> TArgS "ys" ys <+> TArgS "xs" xs 

greater' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
greater' x y name = TSym "tf.greater" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
greater :: Tensor n t a -> Tensor n t a -> Tensor n t a 
greater x y = TSym "tf.greater" <+> TArgT "x" x <+> TArgT "y" y 

greaterEqual' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
greaterEqual' x y name = TSym "tf.greater_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
greaterEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
greaterEqual x y = TSym "tf.greater_equal" <+> TArgT "x" x <+> TArgT "y" y 


group :: Tensor n t a 
group = TSym "tf.group" 

hessians' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
hessians' ys xs name colocate_gradients_with_ops gate_gradients aggregation_method = TSym "tf.hessians" <+> TArgS "ys" ys <+> TArgS "xs" xs <+> TArgS "name" name <+> TArgS "colocate_gradients_with_ops" colocate_gradients_with_ops <+> TArgS "gate_gradients" gate_gradients <+> TArgS "aggregation_method" aggregation_method 
hessians :: String -> String -> Tensor n t a 
hessians ys xs = TSym "tf.hessians" <+> TArgS "ys" ys <+> TArgS "xs" xs 

histogramFixedWidth' :: String -> String -> String -> String -> String -> Tensor n t a 
histogramFixedWidth' values value_range nbins dtype name = TSym "tf.histogram_fixed_width" <+> TArgS "values" values <+> TArgS "value_range" value_range <+> TArgS "nbins" nbins <+> TArgS "dtype" dtype <+> TArgS "name" name 
histogramFixedWidth :: String -> String -> Tensor n t a 
histogramFixedWidth values value_range = TSym "tf.histogram_fixed_width" <+> TArgS "values" values <+> TArgS "value_range" value_range 

identity' :: String -> String -> Tensor n t a 
identity' input name = TSym "tf.identity" <+> TArgS "input" input <+> TArgS "name" name 
identity :: String -> Tensor n t a 
identity input = TSym "tf.identity" <+> TArgS "input" input 

ifft' :: String -> String -> Tensor n t a 
ifft' input name = TSym "tf.ifft" <+> TArgS "input" input <+> TArgS "name" name 
ifft :: String -> Tensor n t a 
ifft input = TSym "tf.ifft" <+> TArgS "input" input 

ifft2d' :: String -> String -> Tensor n t a 
ifft2d' input name = TSym "tf.ifft2d" <+> TArgS "input" input <+> TArgS "name" name 
ifft2d :: String -> Tensor n t a 
ifft2d input = TSym "tf.ifft2d" <+> TArgS "input" input 

ifft3d' :: String -> String -> Tensor n t a 
ifft3d' input name = TSym "tf.ifft3d" <+> TArgS "input" input <+> TArgS "name" name 
ifft3d :: String -> Tensor n t a 
ifft3d input = TSym "tf.ifft3d" <+> TArgS "input" input 

igamma' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
igamma' a x name = TSym "tf.igamma" <+> TArgT "a" a <+> TArgT "x" x <+> TArgS "name" name 
igamma :: Tensor n t a -> Tensor n t a -> Tensor n t a 
igamma a x = TSym "tf.igamma" <+> TArgT "a" a <+> TArgT "x" x 

igammac' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
igammac' a x name = TSym "tf.igammac" <+> TArgT "a" a <+> TArgT "x" x <+> TArgS "name" name 
igammac :: Tensor n t a -> Tensor n t a -> Tensor n t a 
igammac a x = TSym "tf.igammac" <+> TArgT "a" a <+> TArgT "x" x 

imag' :: String -> String -> Tensor n t a 
imag' input name = TSym "tf.imag" <+> TArgS "input" input <+> TArgS "name" name 
imag :: String -> Tensor n t a 
imag input = TSym "tf.imag" <+> TArgS "input" input 

importGraphDef' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
importGraphDef' graph_def input_map return_elements name op_dict producer_op_list = TSym "tf.import_graph_def" <+> TArgS "graph_def" graph_def <+> TArgS "input_map" input_map <+> TArgS "return_elements" return_elements <+> TArgS "name" name <+> TArgS "op_dict" op_dict <+> TArgS "producer_op_list" producer_op_list 
importGraphDef :: String -> Tensor n t a 
importGraphDef graph_def = TSym "tf.import_graph_def" <+> TArgS "graph_def" graph_def 


initializeAllTables :: Tensor n t a 
initializeAllTables = TSym "tf.initialize_all_tables" 


initializeAllVariables :: Tensor n t a 
initializeAllVariables = TSym "tf.initialize_all_variables" 


initializeLocalVariables :: Tensor n t a 
initializeLocalVariables = TSym "tf.initialize_local_variables" 


initializeVariables :: Tensor n t a 
initializeVariables = TSym "tf.initialize_variables" 

invertPermutation' :: Tensor n t a -> String -> Tensor n t a 
invertPermutation' x name = TSym "tf.invert_permutation" <+> TArgT "x" x <+> TArgS "name" name 
invertPermutation :: Tensor n t a -> Tensor n t a 
invertPermutation x = TSym "tf.invert_permutation" <+> TArgT "x" x 

isFinite' :: Tensor n t a -> String -> Tensor n t a 
isFinite' x name = TSym "tf.is_finite" <+> TArgT "x" x <+> TArgS "name" name 
isFinite :: Tensor n t a -> Tensor n t a 
isFinite x = TSym "tf.is_finite" <+> TArgT "x" x 

isInf' :: Tensor n t a -> String -> Tensor n t a 
isInf' x name = TSym "tf.is_inf" <+> TArgT "x" x <+> TArgS "name" name 
isInf :: Tensor n t a -> Tensor n t a 
isInf x = TSym "tf.is_inf" <+> TArgT "x" x 

isNan' :: Tensor n t a -> String -> Tensor n t a 
isNan' x name = TSym "tf.is_nan" <+> TArgT "x" x <+> TArgS "name" name 
isNan :: Tensor n t a -> Tensor n t a 
isNan x = TSym "tf.is_nan" <+> TArgT "x" x 

isNonDecreasing' :: Tensor n t a -> String -> Tensor n t a 
isNonDecreasing' x name = TSym "tf.is_non_decreasing" <+> TArgT "x" x <+> TArgS "name" name 
isNonDecreasing :: Tensor n t a -> Tensor n t a 
isNonDecreasing x = TSym "tf.is_non_decreasing" <+> TArgT "x" x 


isNumericTensor :: Tensor n t a -> Tensor n t a 
isNumericTensor tensor = TSym "tf.is_numeric_tensor" <+> TArgT "tensor" tensor 

isStrictlyIncreasing' :: Tensor n t a -> String -> Tensor n t a 
isStrictlyIncreasing' x name = TSym "tf.is_strictly_increasing" <+> TArgT "x" x <+> TArgS "name" name 
isStrictlyIncreasing :: Tensor n t a -> Tensor n t a 
isStrictlyIncreasing x = TSym "tf.is_strictly_increasing" <+> TArgT "x" x 


isVariableInitialized :: Tensor n t a 
isVariableInitialized = TSym "tf.is_variable_initialized" 

lbeta' :: Tensor n t a -> String -> Tensor n t a 
lbeta' x name = TSym "tf.lbeta" <+> TArgT "x" x <+> TArgS "name" name 
lbeta :: Tensor n t a -> Tensor n t a 
lbeta x = TSym "tf.lbeta" <+> TArgT "x" x 

less' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
less' x y name = TSym "tf.less" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
less :: Tensor n t a -> Tensor n t a -> Tensor n t a 
less x y = TSym "tf.less" <+> TArgT "x" x <+> TArgT "y" y 

lessEqual' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
lessEqual' x y name = TSym "tf.less_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
lessEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
lessEqual x y = TSym "tf.less_equal" <+> TArgT "x" x <+> TArgT "y" y 

lgamma' :: Tensor n t a -> String -> Tensor n t a 
lgamma' x name = TSym "tf.lgamma" <+> TArgT "x" x <+> TArgS "name" name 
lgamma :: Tensor n t a -> Tensor n t a 
lgamma x = TSym "tf.lgamma" <+> TArgT "x" x 

linSpace' :: String -> String -> String -> String -> Tensor n t a 
linSpace' start stop num name = TSym "tf.lin_space" <+> TArgS "start" start <+> TArgS "stop" stop <+> TArgS "num" num <+> TArgS "name" name 
linSpace :: String -> String -> String -> Tensor n t a 
linSpace start stop num = TSym "tf.lin_space" <+> TArgS "start" start <+> TArgS "stop" stop <+> TArgS "num" num 

linspace' :: String -> String -> String -> String -> Tensor n t a 
linspace' start stop num name = TSym "tf.linspace" <+> TArgS "start" start <+> TArgS "stop" stop <+> TArgS "num" num <+> TArgS "name" name 
linspace :: String -> String -> String -> Tensor n t a 
linspace start stop num = TSym "tf.linspace" <+> TArgS "start" start <+> TArgS "stop" stop <+> TArgS "num" num 


loadFileSystemLibrary :: String -> Tensor n t a 
loadFileSystemLibrary library_filename = TSym "tf.load_file_system_library" <+> TArgS "library_filename" library_filename 


loadOpLibrary :: String -> Tensor n t a 
loadOpLibrary library_filename = TSym "tf.load_op_library" <+> TArgS "library_filename" library_filename 


localVariables :: Tensor n t a 
localVariables = TSym "tf.local_variables" 


localVariablesInitializer :: Tensor n t a 
localVariablesInitializer = TSym "tf.local_variables_initializer" 

log' :: Tensor n t a -> String -> Tensor n t a 
log' x name = TSym "tf.log" <+> TArgT "x" x <+> TArgS "name" name 
log :: Tensor n t a -> Tensor n t a 
log x = TSym "tf.log" <+> TArgT "x" x 

log1p' :: Tensor n t a -> String -> Tensor n t a 
log1p' x name = TSym "tf.log1p" <+> TArgT "x" x <+> TArgS "name" name 
log1p :: Tensor n t a -> Tensor n t a 
log1p x = TSym "tf.log1p" <+> TArgT "x" x 

logSigmoid' :: Tensor n t a -> String -> Tensor n t a 
logSigmoid' x name = TSym "tf.log_sigmoid" <+> TArgT "x" x <+> TArgS "name" name 
logSigmoid :: Tensor n t a -> Tensor n t a 
logSigmoid x = TSym "tf.log_sigmoid" <+> TArgT "x" x 

logicalAnd' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
logicalAnd' x y name = TSym "tf.logical_and" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
logicalAnd :: Tensor n t a -> Tensor n t a -> Tensor n t a 
logicalAnd x y = TSym "tf.logical_and" <+> TArgT "x" x <+> TArgT "y" y 

logicalNot' :: Tensor n t a -> String -> Tensor n t a 
logicalNot' x name = TSym "tf.logical_not" <+> TArgT "x" x <+> TArgS "name" name 
logicalNot :: Tensor n t a -> Tensor n t a 
logicalNot x = TSym "tf.logical_not" <+> TArgT "x" x 

logicalOr' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
logicalOr' x y name = TSym "tf.logical_or" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
logicalOr :: Tensor n t a -> Tensor n t a -> Tensor n t a 
logicalOr x y = TSym "tf.logical_or" <+> TArgT "x" x <+> TArgT "y" y 

logicalXor' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
logicalXor' x y name = TSym "tf.logical_xor" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
logicalXor :: Tensor n t a -> Tensor n t a -> Tensor n t a 
logicalXor x y = TSym "tf.logical_xor" <+> TArgT "x" x <+> TArgT "y" y 


makeNdarray :: Tensor n t a -> Tensor n t a 
makeNdarray tensor = TSym "tf.make_ndarray" <+> TArgT "tensor" tensor 

makeTemplate' :: String -> String -> String -> String -> String -> Tensor n t a 
makeTemplate' name_ func_ create_scope_now_ unique_name_ custom_getter_ = TSym "tf.make_template" <+> TArgS "name_" name_ <+> TArgS "func_" func_ <+> TArgS "create_scope_now_" create_scope_now_ <+> TArgS "unique_name_" unique_name_ <+> TArgS "custom_getter_" custom_getter_ 
makeTemplate :: String -> String -> Tensor n t a 
makeTemplate name_ func_ = TSym "tf.make_template" <+> TArgS "name_" name_ <+> TArgS "func_" func_ 

makeTensorProto' :: SingI n => String -> String -> Sing n -> String -> Tensor n t a 
makeTensorProto' values dtype shape verify_shape = TSym "tf.make_tensor_proto" <+> TArgS "values" values <+> TArgS "dtype" dtype <+> TArgSing "shape" shape <+> TArgS "verify_shape" verify_shape 
makeTensorProto :: String -> Tensor n t a 
makeTensorProto values = TSym "tf.make_tensor_proto" <+> TArgS "values" values 

mapFn' :: String -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
mapFn' fn elems dtype parallel_iterations back_prop swap_memory infer_shape name = TSym "tf.map_fn" <+> TArgS "fn" fn <+> TArgS "elems" elems <+> TArgS "dtype" dtype <+> TArgS "parallel_iterations" parallel_iterations <+> TArgS "back_prop" back_prop <+> TArgS "swap_memory" swap_memory <+> TArgS "infer_shape" infer_shape <+> TArgS "name" name 
mapFn :: String -> String -> Tensor n t a 
mapFn fn elems = TSym "tf.map_fn" <+> TArgS "fn" fn <+> TArgS "elems" elems 

matchingFiles' :: String -> String -> Tensor n t a 
matchingFiles' pattern name = TSym "tf.matching_files" <+> TArgS "pattern" pattern <+> TArgS "name" name 
matchingFiles :: String -> Tensor n t a 
matchingFiles pattern = TSym "tf.matching_files" <+> TArgS "pattern" pattern 

matmul' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
matmul' a b transpose_a transpose_b adjoint_a adjoint_b a_is_sparse b_is_sparse name = TSym "tf.matmul" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "transpose_a" transpose_a <+> TArgS "transpose_b" transpose_b <+> TArgS "adjoint_a" adjoint_a <+> TArgS "adjoint_b" adjoint_b <+> TArgS "a_is_sparse" a_is_sparse <+> TArgS "b_is_sparse" b_is_sparse <+> TArgS "name" name 
matmul :: Tensor n t a -> Tensor n t a -> Tensor n t a 
matmul a b = TSym "tf.matmul" <+> TArgT "a" a <+> TArgT "b" b 

matrixBandPart' :: String -> String -> String -> String -> Tensor n t a 
matrixBandPart' input num_lower num_upper name = TSym "tf.matrix_band_part" <+> TArgS "input" input <+> TArgS "num_lower" num_lower <+> TArgS "num_upper" num_upper <+> TArgS "name" name 
matrixBandPart :: String -> String -> String -> Tensor n t a 
matrixBandPart input num_lower num_upper = TSym "tf.matrix_band_part" <+> TArgS "input" input <+> TArgS "num_lower" num_lower <+> TArgS "num_upper" num_upper 

matrixDeterminant' :: String -> String -> Tensor n t a 
matrixDeterminant' input name = TSym "tf.matrix_determinant" <+> TArgS "input" input <+> TArgS "name" name 
matrixDeterminant :: String -> Tensor n t a 
matrixDeterminant input = TSym "tf.matrix_determinant" <+> TArgS "input" input 

matrixDiag' :: String -> String -> Tensor n t a 
matrixDiag' diagonal name = TSym "tf.matrix_diag" <+> TArgS "diagonal" diagonal <+> TArgS "name" name 
matrixDiag :: String -> Tensor n t a 
matrixDiag diagonal = TSym "tf.matrix_diag" <+> TArgS "diagonal" diagonal 

matrixDiagPart' :: String -> String -> Tensor n t a 
matrixDiagPart' input name = TSym "tf.matrix_diag_part" <+> TArgS "input" input <+> TArgS "name" name 
matrixDiagPart :: String -> Tensor n t a 
matrixDiagPart input = TSym "tf.matrix_diag_part" <+> TArgS "input" input 

matrixInverse' :: String -> String -> String -> Tensor n t a 
matrixInverse' input adjoint name = TSym "tf.matrix_inverse" <+> TArgS "input" input <+> TArgS "adjoint" adjoint <+> TArgS "name" name 
matrixInverse :: String -> Tensor n t a 
matrixInverse input = TSym "tf.matrix_inverse" <+> TArgS "input" input 

matrixSetDiag' :: String -> String -> String -> Tensor n t a 
matrixSetDiag' input diagonal name = TSym "tf.matrix_set_diag" <+> TArgS "input" input <+> TArgS "diagonal" diagonal <+> TArgS "name" name 
matrixSetDiag :: String -> String -> Tensor n t a 
matrixSetDiag input diagonal = TSym "tf.matrix_set_diag" <+> TArgS "input" input <+> TArgS "diagonal" diagonal 

matrixSolve' :: String -> String -> String -> String -> Tensor n t a 
matrixSolve' matrix rhs adjoint name = TSym "tf.matrix_solve" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs <+> TArgS "adjoint" adjoint <+> TArgS "name" name 
matrixSolve :: String -> String -> Tensor n t a 
matrixSolve matrix rhs = TSym "tf.matrix_solve" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs 

matrixSolveLs' :: String -> String -> String -> String -> String -> Tensor n t a 
matrixSolveLs' matrix rhs l2_regularizer fast name = TSym "tf.matrix_solve_ls" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs <+> TArgS "l2_regularizer" l2_regularizer <+> TArgS "fast" fast <+> TArgS "name" name 
matrixSolveLs :: String -> String -> Tensor n t a 
matrixSolveLs matrix rhs = TSym "tf.matrix_solve_ls" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs 

matrixTranspose' :: Tensor n t a -> String -> Tensor n t a 
matrixTranspose' a name = TSym "tf.matrix_transpose" <+> TArgT "a" a <+> TArgS "name" name 
matrixTranspose :: Tensor n t a -> Tensor n t a 
matrixTranspose a = TSym "tf.matrix_transpose" <+> TArgT "a" a 

matrixTriangularSolve' :: String -> String -> String -> String -> String -> Tensor n t a 
matrixTriangularSolve' matrix rhs lower adjoint name = TSym "tf.matrix_triangular_solve" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs <+> TArgS "lower" lower <+> TArgS "adjoint" adjoint <+> TArgS "name" name 
matrixTriangularSolve :: String -> String -> Tensor n t a 
matrixTriangularSolve matrix rhs = TSym "tf.matrix_triangular_solve" <+> TArgS "matrix" matrix <+> TArgS "rhs" rhs 

maximum' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
maximum' x y name = TSym "tf.maximum" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
maximum :: Tensor n t a -> Tensor n t a -> Tensor n t a 
maximum x y = TSym "tf.maximum" <+> TArgT "x" x <+> TArgT "y" y 


meshgrid :: Tensor n t a 
meshgrid = TSym "tf.meshgrid" 


minMaxVariablePartitioner :: Tensor n t a 
minMaxVariablePartitioner = TSym "tf.min_max_variable_partitioner" 

minimum' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
minimum' x y name = TSym "tf.minimum" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
minimum :: Tensor n t a -> Tensor n t a -> Tensor n t a 
minimum x y = TSym "tf.minimum" <+> TArgT "x" x <+> TArgT "y" y 

mod' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
mod' x y name = TSym "tf.mod" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
mod :: Tensor n t a -> Tensor n t a -> Tensor n t a 
mod x y = TSym "tf.mod" <+> TArgT "x" x <+> TArgT "y" y 


modelVariables :: Tensor n t a 
modelVariables = TSym "tf.model_variables" 


movingAverageVariables :: Tensor n t a 
movingAverageVariables = TSym "tf.moving_average_variables" 

multinomial' :: String -> String -> String -> String -> Tensor n t a 
multinomial' logits num_samples seed name = TSym "tf.multinomial" <+> TArgS "logits" logits <+> TArgS "num_samples" num_samples <+> TArgS "seed" seed <+> TArgS "name" name 
multinomial :: String -> String -> Tensor n t a 
multinomial logits num_samples = TSym "tf.multinomial" <+> TArgS "logits" logits <+> TArgS "num_samples" num_samples 

multiply' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
multiply' x y name = TSym "tf.multiply" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
multiply :: Tensor n t a -> Tensor n t a -> Tensor n t a 
multiply x y = TSym "tf.multiply" <+> TArgT "x" x <+> TArgT "y" y 


nameScope :: Tensor n t a 
nameScope = TSym "tf.name_scope" 

negative' :: Tensor n t a -> String -> Tensor n t a 
negative' x name = TSym "tf.negative" <+> TArgT "x" x <+> TArgS "name" name 
negative :: Tensor n t a -> Tensor n t a 
negative x = TSym "tf.negative" <+> TArgT "x" x 


noOp :: Tensor n t a 
noOp = TSym "tf.no_op" 


noRegularizer :: String -> Tensor n t a 
noRegularizer _' = TSym "tf.no_regularizer" <+> TArgS "_" _' 

norm' :: Tensor n t a -> String -> String -> String -> String -> Tensor n t a 
norm' tensor ord axis keep_dims name = TSym "tf.norm" <+> TArgT "tensor" tensor <+> TArgS "ord" ord <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name 
norm :: Tensor n t a -> Tensor n t a 
norm tensor = TSym "tf.norm" <+> TArgT "tensor" tensor 

notEqual' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
notEqual' x y name = TSym "tf.not_equal" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
notEqual :: Tensor n t a -> Tensor n t a -> Tensor n t a 
notEqual x y = TSym "tf.not_equal" <+> TArgT "x" x <+> TArgT "y" y 

oneHot' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
oneHot' indices depth on_value off_value axis dtype name = TSym "tf.one_hot" <+> TArgS "indices" indices <+> TArgS "depth" depth <+> TArgS "on_value" on_value <+> TArgS "off_value" off_value <+> TArgS "axis" axis <+> TArgS "dtype" dtype <+> TArgS "name" name 
oneHot :: String -> String -> Tensor n t a 
oneHot indices depth = TSym "tf.one_hot" <+> TArgS "indices" indices <+> TArgS "depth" depth 

ones' :: SingI n => Sing n -> String -> String -> Tensor n t a 
ones' shape dtype name = TSym "tf.ones" <+> TArgSing "shape" shape <+> TArgS "dtype" dtype <+> TArgS "name" name 
ones :: SingI n => Sing n -> Tensor n t a 
ones shape = TSym "tf.ones" <+> TArgSing "shape" shape 

onesLike' :: Tensor n t a -> String -> String -> String -> Tensor n t a 
onesLike' tensor dtype name optimize = TSym "tf.ones_like" <+> TArgT "tensor" tensor <+> TArgS "dtype" dtype <+> TArgS "name" name <+> TArgS "optimize" optimize 
onesLike :: Tensor n t a -> Tensor n t a 
onesLike tensor = TSym "tf.ones_like" <+> TArgT "tensor" tensor 


opScope :: Tensor n t a 
opScope = TSym "tf.op_scope" 

pad' :: Tensor n t a -> String -> String -> String -> Tensor n t a 
pad' tensor paddings mode name = TSym "tf.pad" <+> TArgT "tensor" tensor <+> TArgS "paddings" paddings <+> TArgS "mode" mode <+> TArgS "name" name 
pad :: Tensor n t a -> String -> Tensor n t a 
pad tensor paddings = TSym "tf.pad" <+> TArgT "tensor" tensor <+> TArgS "paddings" paddings 

parallelStack' :: String -> String -> Tensor n t a 
parallelStack' values name = TSym "tf.parallel_stack" <+> TArgS "values" values <+> TArgS "name" name 
parallelStack :: String -> Tensor n t a 
parallelStack values = TSym "tf.parallel_stack" <+> TArgS "values" values 

parseExample' :: String -> String -> String -> String -> Tensor n t a 
parseExample' serialized features name example_names = TSym "tf.parse_example" <+> TArgS "serialized" serialized <+> TArgS "features" features <+> TArgS "name" name <+> TArgS "example_names" example_names 
parseExample :: String -> String -> Tensor n t a 
parseExample serialized features = TSym "tf.parse_example" <+> TArgS "serialized" serialized <+> TArgS "features" features 

parseSingleExample' :: String -> String -> String -> String -> Tensor n t a 
parseSingleExample' serialized features name example_names = TSym "tf.parse_single_example" <+> TArgS "serialized" serialized <+> TArgS "features" features <+> TArgS "name" name <+> TArgS "example_names" example_names 
parseSingleExample :: String -> String -> Tensor n t a 
parseSingleExample serialized features = TSym "tf.parse_single_example" <+> TArgS "serialized" serialized <+> TArgS "features" features 

parseSingleSequenceExample' :: String -> String -> String -> String -> String -> Tensor n t a 
parseSingleSequenceExample' serialized context_features sequence_features example_name name = TSym "tf.parse_single_sequence_example" <+> TArgS "serialized" serialized <+> TArgS "context_features" context_features <+> TArgS "sequence_features" sequence_features <+> TArgS "example_name" example_name <+> TArgS "name" name 
parseSingleSequenceExample :: String -> Tensor n t a 
parseSingleSequenceExample serialized = TSym "tf.parse_single_sequence_example" <+> TArgS "serialized" serialized 

parseTensor' :: String -> String -> String -> Tensor n t a 
parseTensor' serialized out_type name = TSym "tf.parse_tensor" <+> TArgS "serialized" serialized <+> TArgS "out_type" out_type <+> TArgS "name" name 
parseTensor :: String -> String -> Tensor n t a 
parseTensor serialized out_type = TSym "tf.parse_tensor" <+> TArgS "serialized" serialized <+> TArgS "out_type" out_type 

placeholder' :: SingI n => String -> Sing n -> String -> Tensor n t a 
placeholder' dtype shape name = TSym "tf.placeholder" <+> TArgS "dtype" dtype <+> TArgSing "shape" shape <+> TArgS "name" name 
placeholder :: String -> Tensor n t a 
placeholder dtype = TSym "tf.placeholder" <+> TArgS "dtype" dtype 

placeholderWithDefault' :: SingI n => String -> Sing n -> String -> Tensor n t a 
placeholderWithDefault' input shape name = TSym "tf.placeholder_with_default" <+> TArgS "input" input <+> TArgSing "shape" shape <+> TArgS "name" name 
placeholderWithDefault :: SingI n => String -> Sing n -> Tensor n t a 
placeholderWithDefault input shape = TSym "tf.placeholder_with_default" <+> TArgS "input" input <+> TArgSing "shape" shape 

polygamma' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
polygamma' a x name = TSym "tf.polygamma" <+> TArgT "a" a <+> TArgT "x" x <+> TArgS "name" name 
polygamma :: Tensor n t a -> Tensor n t a -> Tensor n t a 
polygamma a x = TSym "tf.polygamma" <+> TArgT "a" a <+> TArgT "x" x 

pow' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
pow' x y name = TSym "tf.pow" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
pow :: Tensor n t a -> Tensor n t a -> Tensor n t a 
pow x y = TSym "tf.pow" <+> TArgT "x" x <+> TArgT "y" y 

pyFunc' :: String -> String -> String -> String -> String -> Tensor n t a 
pyFunc' func inp tout stateful name = TSym "tf.py_func" <+> TArgS "func" func <+> TArgS "inp" inp <+> TArgS "Tout" tout <+> TArgS "stateful" stateful <+> TArgS "name" name 
pyFunc :: String -> String -> String -> Tensor n t a 
pyFunc func inp tout = TSym "tf.py_func" <+> TArgS "func" func <+> TArgS "inp" inp <+> TArgS "Tout" tout 

qr' :: String -> String -> String -> Tensor n t a 
qr' input full_matrices name = TSym "tf.qr" <+> TArgS "input" input <+> TArgS "full_matrices" full_matrices <+> TArgS "name" name 
qr :: String -> Tensor n t a 
qr input = TSym "tf.qr" <+> TArgS "input" input 

quantizeV2' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
quantizeV2' input min_range max_range t mode name = TSym "tf.quantize_v2" <+> TArgS "input" input <+> TArgS "min_range" min_range <+> TArgS "max_range" max_range <+> TArgS "T" t <+> TArgS "mode" mode <+> TArgS "name" name 
quantizeV2 :: String -> String -> String -> String -> Tensor n t a 
quantizeV2 input min_range max_range t = TSym "tf.quantize_v2" <+> TArgS "input" input <+> TArgS "min_range" min_range <+> TArgS "max_range" max_range <+> TArgS "T" t 

quantizedConcat' :: String -> String -> String -> String -> String -> Tensor n t a 
quantizedConcat' concat_dim values input_mins input_maxes name = TSym "tf.quantized_concat" <+> TArgS "concat_dim" concat_dim <+> TArgS "values" values <+> TArgS "input_mins" input_mins <+> TArgS "input_maxes" input_maxes <+> TArgS "name" name 
quantizedConcat :: String -> String -> String -> String -> Tensor n t a 
quantizedConcat concat_dim values input_mins input_maxes = TSym "tf.quantized_concat" <+> TArgS "concat_dim" concat_dim <+> TArgS "values" values <+> TArgS "input_mins" input_mins <+> TArgS "input_maxes" input_maxes 

randomCrop' :: String -> String -> String -> String -> Tensor n t a 
randomCrop' value size seed name = TSym "tf.random_crop" <+> TArgS "value" value <+> TArgS "size" size <+> TArgS "seed" seed <+> TArgS "name" name 
randomCrop :: String -> String -> Tensor n t a 
randomCrop value size = TSym "tf.random_crop" <+> TArgS "value" value <+> TArgS "size" size 

randomGamma' :: SingI n => Sing n -> String -> String -> String -> String -> String -> Tensor n t a 
randomGamma' shape alpha beta dtype seed name = TSym "tf.random_gamma" <+> TArgSing "shape" shape <+> TArgS "alpha" alpha <+> TArgS "beta" beta <+> TArgS "dtype" dtype <+> TArgS "seed" seed <+> TArgS "name" name 
randomGamma :: SingI n => Sing n -> String -> Tensor n t a 
randomGamma shape alpha = TSym "tf.random_gamma" <+> TArgSing "shape" shape <+> TArgS "alpha" alpha 

randomNormal' :: SingI n => Sing n -> String -> String -> String -> String -> String -> Tensor n t a 
randomNormal' shape mean stddev dtype seed name = TSym "tf.random_normal" <+> TArgSing "shape" shape <+> TArgS "mean" mean <+> TArgS "stddev" stddev <+> TArgS "dtype" dtype <+> TArgS "seed" seed <+> TArgS "name" name 
randomNormal :: SingI n => Sing n -> Tensor n t a 
randomNormal shape = TSym "tf.random_normal" <+> TArgSing "shape" shape 

randomPoisson' :: SingI n => String -> Sing n -> String -> String -> String -> Tensor n t a 
randomPoisson' lam shape dtype seed name = TSym "tf.random_poisson" <+> TArgS "lam" lam <+> TArgSing "shape" shape <+> TArgS "dtype" dtype <+> TArgS "seed" seed <+> TArgS "name" name 
randomPoisson :: SingI n => String -> Sing n -> Tensor n t a 
randomPoisson lam shape = TSym "tf.random_poisson" <+> TArgS "lam" lam <+> TArgSing "shape" shape 

randomShuffle' :: String -> String -> String -> Tensor n t a 
randomShuffle' value seed name = TSym "tf.random_shuffle" <+> TArgS "value" value <+> TArgS "seed" seed <+> TArgS "name" name 
randomShuffle :: String -> Tensor n t a 
randomShuffle value = TSym "tf.random_shuffle" <+> TArgS "value" value 

randomUniform' :: SingI n => Sing n -> String -> String -> String -> String -> String -> Tensor n t a 
randomUniform' shape minval maxval dtype seed name = TSym "tf.random_uniform" <+> TArgSing "shape" shape <+> TArgS "minval" minval <+> TArgS "maxval" maxval <+> TArgS "dtype" dtype <+> TArgS "seed" seed <+> TArgS "name" name 
randomUniform :: SingI n => Sing n -> Tensor n t a 
randomUniform shape = TSym "tf.random_uniform" <+> TArgSing "shape" shape 

range' :: String -> String -> String -> String -> String -> Tensor n t a 
range' start limit delta dtype name = TSym "tf.range" <+> TArgS "start" start <+> TArgS "limit" limit <+> TArgS "delta" delta <+> TArgS "dtype" dtype <+> TArgS "name" name 
range :: String -> Tensor n t a 
range start = TSym "tf.range" <+> TArgS "start" start 

rank' :: String -> String -> Tensor n t a 
rank' input name = TSym "tf.rank" <+> TArgS "input" input <+> TArgS "name" name 
rank :: String -> Tensor n t a 
rank input = TSym "tf.rank" <+> TArgS "input" input 

readFile' :: String -> String -> Tensor n t a 
readFile' filename name = TSym "tf.read_file" <+> TArgS "filename" filename <+> TArgS "name" name 
readFile :: String -> Tensor n t a 
readFile filename = TSym "tf.read_file" <+> TArgS "filename" filename 

real' :: String -> String -> Tensor n t a 
real' input name = TSym "tf.real" <+> TArgS "input" input <+> TArgS "name" name 
real :: String -> Tensor n t a 
real input = TSym "tf.real" <+> TArgS "input" input 

realdiv' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
realdiv' x y name = TSym "tf.realdiv" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
realdiv :: Tensor n t a -> Tensor n t a -> Tensor n t a 
realdiv x y = TSym "tf.realdiv" <+> TArgT "x" x <+> TArgT "y" y 

reciprocal' :: Tensor n t a -> String -> Tensor n t a 
reciprocal' x name = TSym "tf.reciprocal" <+> TArgT "x" x <+> TArgS "name" name 
reciprocal :: Tensor n t a -> Tensor n t a 
reciprocal x = TSym "tf.reciprocal" <+> TArgT "x" x 

reduceAll' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceAll' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_all" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceAll :: String -> Tensor n t a 
reduceAll input_tensor = TSym "tf.reduce_all" <+> TArgS "input_tensor" input_tensor 

reduceAny' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceAny' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_any" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceAny :: String -> Tensor n t a 
reduceAny input_tensor = TSym "tf.reduce_any" <+> TArgS "input_tensor" input_tensor 

reduceJoin' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
reduceJoin' inputs axis keep_dims separator name reduction_indices = TSym "tf.reduce_join" <+> TArgS "inputs" inputs <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "separator" separator <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceJoin :: String -> Tensor n t a 
reduceJoin inputs = TSym "tf.reduce_join" <+> TArgS "inputs" inputs 

reduceLogsumexp' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceLogsumexp' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_logsumexp" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceLogsumexp :: String -> Tensor n t a 
reduceLogsumexp input_tensor = TSym "tf.reduce_logsumexp" <+> TArgS "input_tensor" input_tensor 

reduceMax' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceMax' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_max" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceMax :: String -> Tensor n t a 
reduceMax input_tensor = TSym "tf.reduce_max" <+> TArgS "input_tensor" input_tensor 

reduceMean' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceMean' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_mean" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceMean :: String -> Tensor n t a 
reduceMean input_tensor = TSym "tf.reduce_mean" <+> TArgS "input_tensor" input_tensor 

reduceMin' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceMin' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_min" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceMin :: String -> Tensor n t a 
reduceMin input_tensor = TSym "tf.reduce_min" <+> TArgS "input_tensor" input_tensor 

reduceProd' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceProd' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_prod" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceProd :: String -> Tensor n t a 
reduceProd input_tensor = TSym "tf.reduce_prod" <+> TArgS "input_tensor" input_tensor 

reduceSum' :: String -> String -> String -> String -> String -> Tensor n t a 
reduceSum' input_tensor axis keep_dims name reduction_indices = TSym "tf.reduce_sum" <+> TArgS "input_tensor" input_tensor <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "name" name <+> TArgS "reduction_indices" reduction_indices 
reduceSum :: String -> Tensor n t a 
reduceSum input_tensor = TSym "tf.reduce_sum" <+> TArgS "input_tensor" input_tensor 

registerTensorConversionFunction' :: String -> String -> String -> Tensor n t a 
registerTensorConversionFunction' base_type conversion_func priority = TSym "tf.register_tensor_conversion_function" <+> TArgS "base_type" base_type <+> TArgS "conversion_func" conversion_func <+> TArgS "priority" priority 
registerTensorConversionFunction :: String -> String -> Tensor n t a 
registerTensorConversionFunction base_type conversion_func = TSym "tf.register_tensor_conversion_function" <+> TArgS "base_type" base_type <+> TArgS "conversion_func" conversion_func 


reportUninitializedVariables :: Tensor n t a 
reportUninitializedVariables = TSym "tf.report_uninitialized_variables" 

requiredSpaceToBatchPaddings' :: String -> String -> String -> String -> Tensor n t a 
requiredSpaceToBatchPaddings' input_shape block_shape base_paddings name = TSym "tf.required_space_to_batch_paddings" <+> TArgS "input_shape" input_shape <+> TArgS "block_shape" block_shape <+> TArgS "base_paddings" base_paddings <+> TArgS "name" name 
requiredSpaceToBatchPaddings :: String -> String -> Tensor n t a 
requiredSpaceToBatchPaddings input_shape block_shape = TSym "tf.required_space_to_batch_paddings" <+> TArgS "input_shape" input_shape <+> TArgS "block_shape" block_shape 


resetDefaultGraph :: Tensor n t a 
resetDefaultGraph = TSym "tf.reset_default_graph" 

reshape' :: SingI n => Tensor n t a -> Sing n -> String -> Tensor n t a 
reshape' tensor shape name = TSym "tf.reshape" <+> TArgT "tensor" tensor <+> TArgSing "shape" shape <+> TArgS "name" name 
reshape :: SingI n => Tensor n t a -> Sing n -> Tensor n t a 
reshape tensor shape = TSym "tf.reshape" <+> TArgT "tensor" tensor <+> TArgSing "shape" shape 

reverse' :: Tensor n t a -> String -> String -> Tensor n t a 
reverse' tensor axis name = TSym "tf.reverse" <+> TArgT "tensor" tensor <+> TArgS "axis" axis <+> TArgS "name" name 
reverse :: Tensor n t a -> String -> Tensor n t a 
reverse tensor axis = TSym "tf.reverse" <+> TArgT "tensor" tensor <+> TArgS "axis" axis 

reverseSequence' :: String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
reverseSequence' input seq_lengths seq_axis batch_axis name seq_dim batch_dim = TSym "tf.reverse_sequence" <+> TArgS "input" input <+> TArgS "seq_lengths" seq_lengths <+> TArgS "seq_axis" seq_axis <+> TArgS "batch_axis" batch_axis <+> TArgS "name" name <+> TArgS "seq_dim" seq_dim <+> TArgS "batch_dim" batch_dim 
reverseSequence :: String -> String -> Tensor n t a 
reverseSequence input seq_lengths = TSym "tf.reverse_sequence" <+> TArgS "input" input <+> TArgS "seq_lengths" seq_lengths 

reverseV2' :: Tensor n t a -> String -> String -> Tensor n t a 
reverseV2' tensor axis name = TSym "tf.reverse_v2" <+> TArgT "tensor" tensor <+> TArgS "axis" axis <+> TArgS "name" name 
reverseV2 :: Tensor n t a -> String -> Tensor n t a 
reverseV2 tensor axis = TSym "tf.reverse_v2" <+> TArgT "tensor" tensor <+> TArgS "axis" axis 

rint' :: Tensor n t a -> String -> Tensor n t a 
rint' x name = TSym "tf.rint" <+> TArgT "x" x <+> TArgS "name" name 
rint :: Tensor n t a -> Tensor n t a 
rint x = TSym "tf.rint" <+> TArgT "x" x 

round' :: Tensor n t a -> String -> Tensor n t a 
round' x name = TSym "tf.round" <+> TArgT "x" x <+> TArgS "name" name 
round :: Tensor n t a -> Tensor n t a 
round x = TSym "tf.round" <+> TArgT "x" x 

rsqrt' :: Tensor n t a -> String -> Tensor n t a 
rsqrt' x name = TSym "tf.rsqrt" <+> TArgT "x" x <+> TArgS "name" name 
rsqrt :: Tensor n t a -> Tensor n t a 
rsqrt x = TSym "tf.rsqrt" <+> TArgT "x" x 

saturateCast' :: String -> String -> String -> Tensor n t a 
saturateCast' value dtype name = TSym "tf.saturate_cast" <+> TArgS "value" value <+> TArgS "dtype" dtype <+> TArgS "name" name 
saturateCast :: String -> String -> Tensor n t a 
saturateCast value dtype = TSym "tf.saturate_cast" <+> TArgS "value" value <+> TArgS "dtype" dtype 


scalarMul :: String -> Tensor n t a -> Tensor n t a 
scalarMul scalar x = TSym "tf.scalar_mul" <+> TArgS "scalar" scalar <+> TArgT "x" x 

scan' :: String -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
scan' fn elems initializer parallel_iterations back_prop swap_memory infer_shape name = TSym "tf.scan" <+> TArgS "fn" fn <+> TArgS "elems" elems <+> TArgS "initializer" initializer <+> TArgS "parallel_iterations" parallel_iterations <+> TArgS "back_prop" back_prop <+> TArgS "swap_memory" swap_memory <+> TArgS "infer_shape" infer_shape <+> TArgS "name" name 
scan :: String -> String -> Tensor n t a 
scan fn elems = TSym "tf.scan" <+> TArgS "fn" fn <+> TArgS "elems" elems 

scatterAdd' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterAdd' ref indices updates use_locking name = TSym "tf.scatter_add" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterAdd :: String -> String -> String -> Tensor n t a 
scatterAdd ref indices updates = TSym "tf.scatter_add" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterDiv' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterDiv' ref indices updates use_locking name = TSym "tf.scatter_div" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterDiv :: String -> String -> String -> Tensor n t a 
scatterDiv ref indices updates = TSym "tf.scatter_div" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterMul' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterMul' ref indices updates use_locking name = TSym "tf.scatter_mul" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterMul :: String -> String -> String -> Tensor n t a 
scatterMul ref indices updates = TSym "tf.scatter_mul" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterNd' :: SingI n => String -> String -> Sing n -> String -> Tensor n t a 
scatterNd' indices updates shape name = TSym "tf.scatter_nd" <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgSing "shape" shape <+> TArgS "name" name 
scatterNd :: SingI n => String -> String -> Sing n -> Tensor n t a 
scatterNd indices updates shape = TSym "tf.scatter_nd" <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgSing "shape" shape 

scatterNdAdd' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterNdAdd' ref indices updates use_locking name = TSym "tf.scatter_nd_add" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterNdAdd :: String -> String -> String -> Tensor n t a 
scatterNdAdd ref indices updates = TSym "tf.scatter_nd_add" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterNdSub' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterNdSub' ref indices updates use_locking name = TSym "tf.scatter_nd_sub" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterNdSub :: String -> String -> String -> Tensor n t a 
scatterNdSub ref indices updates = TSym "tf.scatter_nd_sub" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterNdUpdate' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterNdUpdate' ref indices updates use_locking name = TSym "tf.scatter_nd_update" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterNdUpdate :: String -> String -> String -> Tensor n t a 
scatterNdUpdate ref indices updates = TSym "tf.scatter_nd_update" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterSub' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterSub' ref indices updates use_locking name = TSym "tf.scatter_sub" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterSub :: String -> String -> String -> Tensor n t a 
scatterSub ref indices updates = TSym "tf.scatter_sub" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

scatterUpdate' :: String -> String -> String -> String -> String -> Tensor n t a 
scatterUpdate' ref indices updates use_locking name = TSym "tf.scatter_update" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates <+> TArgS "use_locking" use_locking <+> TArgS "name" name 
scatterUpdate :: String -> String -> String -> Tensor n t a 
scatterUpdate ref indices updates = TSym "tf.scatter_update" <+> TArgS "ref" ref <+> TArgS "indices" indices <+> TArgS "updates" updates 

segmentMax' :: String -> String -> String -> Tensor n t a 
segmentMax' data' segment_ids name = TSym "tf.segment_max" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
segmentMax :: String -> String -> Tensor n t a 
segmentMax data' segment_ids = TSym "tf.segment_max" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids 

segmentMean' :: String -> String -> String -> Tensor n t a 
segmentMean' data' segment_ids name = TSym "tf.segment_mean" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
segmentMean :: String -> String -> Tensor n t a 
segmentMean data' segment_ids = TSym "tf.segment_mean" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids 

segmentMin' :: String -> String -> String -> Tensor n t a 
segmentMin' data' segment_ids name = TSym "tf.segment_min" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
segmentMin :: String -> String -> Tensor n t a 
segmentMin data' segment_ids = TSym "tf.segment_min" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids 

segmentProd' :: String -> String -> String -> Tensor n t a 
segmentProd' data' segment_ids name = TSym "tf.segment_prod" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
segmentProd :: String -> String -> Tensor n t a 
segmentProd data' segment_ids = TSym "tf.segment_prod" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids 

segmentSum' :: String -> String -> String -> Tensor n t a 
segmentSum' data' segment_ids name = TSym "tf.segment_sum" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
segmentSum :: String -> String -> Tensor n t a 
segmentSum data' segment_ids = TSym "tf.segment_sum" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids 

selfAdjointEig' :: Tensor n t a -> String -> Tensor n t a 
selfAdjointEig' tensor name = TSym "tf.self_adjoint_eig" <+> TArgT "tensor" tensor <+> TArgS "name" name 
selfAdjointEig :: Tensor n t a -> Tensor n t a 
selfAdjointEig tensor = TSym "tf.self_adjoint_eig" <+> TArgT "tensor" tensor 

selfAdjointEigvals' :: Tensor n t a -> String -> Tensor n t a 
selfAdjointEigvals' tensor name = TSym "tf.self_adjoint_eigvals" <+> TArgT "tensor" tensor <+> TArgS "name" name 
selfAdjointEigvals :: Tensor n t a -> Tensor n t a 
selfAdjointEigvals tensor = TSym "tf.self_adjoint_eigvals" <+> TArgT "tensor" tensor 

sequenceMask' :: String -> String -> String -> String -> Tensor n t a 
sequenceMask' lengths maxlen dtype name = TSym "tf.sequence_mask" <+> TArgS "lengths" lengths <+> TArgS "maxlen" maxlen <+> TArgS "dtype" dtype <+> TArgS "name" name 
sequenceMask :: String -> Tensor n t a 
sequenceMask lengths = TSym "tf.sequence_mask" <+> TArgS "lengths" lengths 

serializeManySparse' :: String -> String -> Tensor n t a 
serializeManySparse' sp_input name = TSym "tf.serialize_many_sparse" <+> TArgS "sp_input" sp_input <+> TArgS "name" name 
serializeManySparse :: String -> Tensor n t a 
serializeManySparse sp_input = TSym "tf.serialize_many_sparse" <+> TArgS "sp_input" sp_input 

serializeSparse' :: String -> String -> Tensor n t a 
serializeSparse' sp_input name = TSym "tf.serialize_sparse" <+> TArgS "sp_input" sp_input <+> TArgS "name" name 
serializeSparse :: String -> Tensor n t a 
serializeSparse sp_input = TSym "tf.serialize_sparse" <+> TArgS "sp_input" sp_input 


setRandomSeed :: String -> Tensor n t a 
setRandomSeed seed = TSym "tf.set_random_seed" <+> TArgS "seed" seed 

setdiff1d' :: Tensor n t a -> Tensor n t a -> String -> String -> Tensor n t a 
setdiff1d' x y index_dtype name = TSym "tf.setdiff1d" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "index_dtype" index_dtype <+> TArgS "name" name 
setdiff1d :: Tensor n t a -> Tensor n t a -> Tensor n t a 
setdiff1d x y = TSym "tf.setdiff1d" <+> TArgT "x" x <+> TArgT "y" y 

shape' :: String -> String -> String -> Tensor n t a 
shape' input name out_type = TSym "tf.shape" <+> TArgS "input" input <+> TArgS "name" name <+> TArgS "out_type" out_type 
shape :: String -> Tensor n t a 
shape input = TSym "tf.shape" <+> TArgS "input" input 

shapeN' :: String -> String -> String -> Tensor n t a 
shapeN' input out_type name = TSym "tf.shape_n" <+> TArgS "input" input <+> TArgS "out_type" out_type <+> TArgS "name" name 
shapeN :: String -> Tensor n t a 
shapeN input = TSym "tf.shape_n" <+> TArgS "input" input 

sigmoid' :: Tensor n t a -> String -> Tensor n t a 
sigmoid' x name = TSym "tf.sigmoid" <+> TArgT "x" x <+> TArgS "name" name 
sigmoid :: Tensor n t a -> Tensor n t a 
sigmoid x = TSym "tf.sigmoid" <+> TArgT "x" x 

sign' :: Tensor n t a -> String -> Tensor n t a 
sign' x name = TSym "tf.sign" <+> TArgT "x" x <+> TArgS "name" name 
sign :: Tensor n t a -> Tensor n t a 
sign x = TSym "tf.sign" <+> TArgT "x" x 

sin' :: Tensor n t a -> String -> Tensor n t a 
sin' x name = TSym "tf.sin" <+> TArgT "x" x <+> TArgS "name" name 


size' :: String -> String -> String -> Tensor n t a 
size' input name out_type = TSym "tf.size" <+> TArgS "input" input <+> TArgS "name" name <+> TArgS "out_type" out_type 
size :: String -> Tensor n t a 
size input = TSym "tf.size" <+> TArgS "input" input 

slice' :: String -> String -> String -> String -> Tensor n t a 
slice' input_ begin size name = TSym "tf.slice" <+> TArgS "input_" input_ <+> TArgS "begin" begin <+> TArgS "size" size <+> TArgS "name" name 
slice :: String -> String -> String -> Tensor n t a 
slice input_ begin size = TSym "tf.slice" <+> TArgS "input_" input_ <+> TArgS "begin" begin <+> TArgS "size" size 

spaceToBatch' :: String -> String -> String -> String -> Tensor n t a 
spaceToBatch' input paddings block_size name = TSym "tf.space_to_batch" <+> TArgS "input" input <+> TArgS "paddings" paddings <+> TArgS "block_size" block_size <+> TArgS "name" name 
spaceToBatch :: String -> String -> String -> Tensor n t a 
spaceToBatch input paddings block_size = TSym "tf.space_to_batch" <+> TArgS "input" input <+> TArgS "paddings" paddings <+> TArgS "block_size" block_size 

spaceToBatchNd' :: String -> String -> String -> String -> Tensor n t a 
spaceToBatchNd' input block_shape paddings name = TSym "tf.space_to_batch_nd" <+> TArgS "input" input <+> TArgS "block_shape" block_shape <+> TArgS "paddings" paddings <+> TArgS "name" name 
spaceToBatchNd :: String -> String -> String -> Tensor n t a 
spaceToBatchNd input block_shape paddings = TSym "tf.space_to_batch_nd" <+> TArgS "input" input <+> TArgS "block_shape" block_shape <+> TArgS "paddings" paddings 

spaceToDepth' :: String -> String -> String -> Tensor n t a 
spaceToDepth' input block_size name = TSym "tf.space_to_depth" <+> TArgS "input" input <+> TArgS "block_size" block_size <+> TArgS "name" name 
spaceToDepth :: String -> String -> Tensor n t a 
spaceToDepth input block_size = TSym "tf.space_to_depth" <+> TArgS "input" input <+> TArgS "block_size" block_size 

sparseAdd' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
sparseAdd' a b thresh = TSym "tf.sparse_add" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "thresh" thresh 
sparseAdd :: Tensor n t a -> Tensor n t a -> Tensor n t a 
sparseAdd a b = TSym "tf.sparse_add" <+> TArgT "a" a <+> TArgT "b" b 

sparseConcat' :: String -> String -> String -> String -> String -> Tensor n t a 
sparseConcat' axis sp_inputs name expand_nonconcat_dim concat_dim = TSym "tf.sparse_concat" <+> TArgS "axis" axis <+> TArgS "sp_inputs" sp_inputs <+> TArgS "name" name <+> TArgS "expand_nonconcat_dim" expand_nonconcat_dim <+> TArgS "concat_dim" concat_dim 
sparseConcat :: String -> String -> Tensor n t a 
sparseConcat axis sp_inputs = TSym "tf.sparse_concat" <+> TArgS "axis" axis <+> TArgS "sp_inputs" sp_inputs 

sparseFillEmptyRows' :: String -> String -> String -> Tensor n t a 
sparseFillEmptyRows' sp_input default_value name = TSym "tf.sparse_fill_empty_rows" <+> TArgS "sp_input" sp_input <+> TArgS "default_value" default_value <+> TArgS "name" name 
sparseFillEmptyRows :: String -> String -> Tensor n t a 
sparseFillEmptyRows sp_input default_value = TSym "tf.sparse_fill_empty_rows" <+> TArgS "sp_input" sp_input <+> TArgS "default_value" default_value 

sparseMask' :: Tensor n t a -> String -> String -> Tensor n t a 
sparseMask' a mask_indices name = TSym "tf.sparse_mask" <+> TArgT "a" a <+> TArgS "mask_indices" mask_indices <+> TArgS "name" name 
sparseMask :: Tensor n t a -> String -> Tensor n t a 
sparseMask a mask_indices = TSym "tf.sparse_mask" <+> TArgT "a" a <+> TArgS "mask_indices" mask_indices 

sparseMatmul' :: Tensor n t a -> Tensor n t a -> String -> String -> String -> String -> String -> Tensor n t a 
sparseMatmul' a b transpose_a transpose_b a_is_sparse b_is_sparse name = TSym "tf.sparse_matmul" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "transpose_a" transpose_a <+> TArgS "transpose_b" transpose_b <+> TArgS "a_is_sparse" a_is_sparse <+> TArgS "b_is_sparse" b_is_sparse <+> TArgS "name" name 
sparseMatmul :: Tensor n t a -> Tensor n t a -> Tensor n t a 
sparseMatmul a b = TSym "tf.sparse_matmul" <+> TArgT "a" a <+> TArgT "b" b 

sparseMaximum' :: String -> String -> String -> Tensor n t a 
sparseMaximum' sp_a sp_b name = TSym "tf.sparse_maximum" <+> TArgS "sp_a" sp_a <+> TArgS "sp_b" sp_b <+> TArgS "name" name 
sparseMaximum :: String -> String -> Tensor n t a 
sparseMaximum sp_a sp_b = TSym "tf.sparse_maximum" <+> TArgS "sp_a" sp_a <+> TArgS "sp_b" sp_b 

sparseMerge' :: String -> String -> String -> String -> String -> Tensor n t a 
sparseMerge' sp_ids sp_values vocab_size name already_sorted = TSym "tf.sparse_merge" <+> TArgS "sp_ids" sp_ids <+> TArgS "sp_values" sp_values <+> TArgS "vocab_size" vocab_size <+> TArgS "name" name <+> TArgS "already_sorted" already_sorted 
sparseMerge :: String -> String -> String -> Tensor n t a 
sparseMerge sp_ids sp_values vocab_size = TSym "tf.sparse_merge" <+> TArgS "sp_ids" sp_ids <+> TArgS "sp_values" sp_values <+> TArgS "vocab_size" vocab_size 

sparseMinimum' :: String -> String -> String -> Tensor n t a 
sparseMinimum' sp_a sp_b name = TSym "tf.sparse_minimum" <+> TArgS "sp_a" sp_a <+> TArgS "sp_b" sp_b <+> TArgS "name" name 
sparseMinimum :: String -> String -> Tensor n t a 
sparseMinimum sp_a sp_b = TSym "tf.sparse_minimum" <+> TArgS "sp_a" sp_a <+> TArgS "sp_b" sp_b 

sparsePlaceholder' :: SingI n => String -> Sing n -> String -> Tensor n t a 
sparsePlaceholder' dtype shape name = TSym "tf.sparse_placeholder" <+> TArgS "dtype" dtype <+> TArgSing "shape" shape <+> TArgS "name" name 
sparsePlaceholder :: String -> Tensor n t a 
sparsePlaceholder dtype = TSym "tf.sparse_placeholder" <+> TArgS "dtype" dtype 

sparseReduceSum' :: String -> String -> String -> String -> Tensor n t a 
sparseReduceSum' sp_input axis keep_dims reduction_axes = TSym "tf.sparse_reduce_sum" <+> TArgS "sp_input" sp_input <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "reduction_axes" reduction_axes 
sparseReduceSum :: String -> Tensor n t a 
sparseReduceSum sp_input = TSym "tf.sparse_reduce_sum" <+> TArgS "sp_input" sp_input 

sparseReduceSumSparse' :: String -> String -> String -> String -> Tensor n t a 
sparseReduceSumSparse' sp_input axis keep_dims reduction_axes = TSym "tf.sparse_reduce_sum_sparse" <+> TArgS "sp_input" sp_input <+> TArgS "axis" axis <+> TArgS "keep_dims" keep_dims <+> TArgS "reduction_axes" reduction_axes 
sparseReduceSumSparse :: String -> Tensor n t a 
sparseReduceSumSparse sp_input = TSym "tf.sparse_reduce_sum_sparse" <+> TArgS "sp_input" sp_input 

sparseReorder' :: String -> String -> Tensor n t a 
sparseReorder' sp_input name = TSym "tf.sparse_reorder" <+> TArgS "sp_input" sp_input <+> TArgS "name" name 
sparseReorder :: String -> Tensor n t a 
sparseReorder sp_input = TSym "tf.sparse_reorder" <+> TArgS "sp_input" sp_input 

sparseResetShape' :: String -> String -> Tensor n t a 
sparseResetShape' sp_input new_shape = TSym "tf.sparse_reset_shape" <+> TArgS "sp_input" sp_input <+> TArgS "new_shape" new_shape 
sparseResetShape :: String -> Tensor n t a 
sparseResetShape sp_input = TSym "tf.sparse_reset_shape" <+> TArgS "sp_input" sp_input 

sparseReshape' :: SingI n => String -> Sing n -> String -> Tensor n t a 
sparseReshape' sp_input shape name = TSym "tf.sparse_reshape" <+> TArgS "sp_input" sp_input <+> TArgSing "shape" shape <+> TArgS "name" name 
sparseReshape :: SingI n => String -> Sing n -> Tensor n t a 
sparseReshape sp_input shape = TSym "tf.sparse_reshape" <+> TArgS "sp_input" sp_input <+> TArgSing "shape" shape 


sparseRetain :: String -> String -> Tensor n t a 
sparseRetain sp_input to_retain = TSym "tf.sparse_retain" <+> TArgS "sp_input" sp_input <+> TArgS "to_retain" to_retain 

sparseSegmentMean' :: String -> String -> String -> String -> Tensor n t a 
sparseSegmentMean' data' indices segment_ids name = TSym "tf.sparse_segment_mean" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
sparseSegmentMean :: String -> String -> String -> Tensor n t a 
sparseSegmentMean data' indices segment_ids = TSym "tf.sparse_segment_mean" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids 

sparseSegmentSqrtN' :: String -> String -> String -> String -> Tensor n t a 
sparseSegmentSqrtN' data' indices segment_ids name = TSym "tf.sparse_segment_sqrt_n" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
sparseSegmentSqrtN :: String -> String -> String -> Tensor n t a 
sparseSegmentSqrtN data' indices segment_ids = TSym "tf.sparse_segment_sqrt_n" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids 

sparseSegmentSum' :: String -> String -> String -> String -> Tensor n t a 
sparseSegmentSum' data' indices segment_ids name = TSym "tf.sparse_segment_sum" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids <+> TArgS "name" name 
sparseSegmentSum :: String -> String -> String -> Tensor n t a 
sparseSegmentSum data' indices segment_ids = TSym "tf.sparse_segment_sum" <+> TArgS "data" data' <+> TArgS "indices" indices <+> TArgS "segment_ids" segment_ids 

sparseSoftmax' :: String -> String -> Tensor n t a 
sparseSoftmax' sp_input name = TSym "tf.sparse_softmax" <+> TArgS "sp_input" sp_input <+> TArgS "name" name 
sparseSoftmax :: String -> Tensor n t a 
sparseSoftmax sp_input = TSym "tf.sparse_softmax" <+> TArgS "sp_input" sp_input 


sparseSplit :: Tensor n t a 
sparseSplit = TSym "tf.sparse_split" 

sparseTensorDenseMatmul' :: String -> Tensor n t a -> String -> String -> String -> Tensor n t a 
sparseTensorDenseMatmul' sp_a b adjoint_a adjoint_b name = TSym "tf.sparse_tensor_dense_matmul" <+> TArgS "sp_a" sp_a <+> TArgT "b" b <+> TArgS "adjoint_a" adjoint_a <+> TArgS "adjoint_b" adjoint_b <+> TArgS "name" name 
sparseTensorDenseMatmul :: String -> Tensor n t a -> Tensor n t a 
sparseTensorDenseMatmul sp_a b = TSym "tf.sparse_tensor_dense_matmul" <+> TArgS "sp_a" sp_a <+> TArgT "b" b 

sparseTensorToDense' :: String -> String -> String -> String -> Tensor n t a 
sparseTensorToDense' sp_input default_value validate_indices name = TSym "tf.sparse_tensor_to_dense" <+> TArgS "sp_input" sp_input <+> TArgS "default_value" default_value <+> TArgS "validate_indices" validate_indices <+> TArgS "name" name 
sparseTensorToDense :: String -> Tensor n t a 
sparseTensorToDense sp_input = TSym "tf.sparse_tensor_to_dense" <+> TArgS "sp_input" sp_input 

sparseToDense' :: String -> String -> String -> String -> String -> String -> Tensor n t a 
sparseToDense' sparse_indices output_shape sparse_values default_value validate_indices name = TSym "tf.sparse_to_dense" <+> TArgS "sparse_indices" sparse_indices <+> TArgS "output_shape" output_shape <+> TArgS "sparse_values" sparse_values <+> TArgS "default_value" default_value <+> TArgS "validate_indices" validate_indices <+> TArgS "name" name 
sparseToDense :: String -> String -> String -> Tensor n t a 
sparseToDense sparse_indices output_shape sparse_values = TSym "tf.sparse_to_dense" <+> TArgS "sparse_indices" sparse_indices <+> TArgS "output_shape" output_shape <+> TArgS "sparse_values" sparse_values 

sparseToIndicator' :: String -> String -> String -> Tensor n t a 
sparseToIndicator' sp_input vocab_size name = TSym "tf.sparse_to_indicator" <+> TArgS "sp_input" sp_input <+> TArgS "vocab_size" vocab_size <+> TArgS "name" name 
sparseToIndicator :: String -> String -> Tensor n t a 
sparseToIndicator sp_input vocab_size = TSym "tf.sparse_to_indicator" <+> TArgS "sp_input" sp_input <+> TArgS "vocab_size" vocab_size 

sparseTranspose' :: String -> String -> String -> Tensor n t a 
sparseTranspose' sp_input perm name = TSym "tf.sparse_transpose" <+> TArgS "sp_input" sp_input <+> TArgS "perm" perm <+> TArgS "name" name 
sparseTranspose :: String -> Tensor n t a 
sparseTranspose sp_input = TSym "tf.sparse_transpose" <+> TArgS "sp_input" sp_input 

split' :: String -> String -> String -> String -> String -> Tensor n t a 
split' value num_or_size_splits axis num name = TSym "tf.split" <+> TArgS "value" value <+> TArgS "num_or_size_splits" num_or_size_splits <+> TArgS "axis" axis <+> TArgS "num" num <+> TArgS "name" name 
split :: String -> String -> Tensor n t a 
split value num_or_size_splits = TSym "tf.split" <+> TArgS "value" value <+> TArgS "num_or_size_splits" num_or_size_splits 

sqrt' :: Tensor n t a -> String -> Tensor n t a 
sqrt' x name = TSym "tf.sqrt" <+> TArgT "x" x <+> TArgS "name" name 
sqrt :: Tensor n t a -> Tensor n t a 
sqrt x = TSym "tf.sqrt" <+> TArgT "x" x 

square' :: Tensor n t a -> String -> Tensor n t a 
square' x name = TSym "tf.square" <+> TArgT "x" x <+> TArgS "name" name 
square :: Tensor n t a -> Tensor n t a 
square x = TSym "tf.square" <+> TArgT "x" x 

squaredDifference' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
squaredDifference' x y name = TSym "tf.squared_difference" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
squaredDifference :: Tensor n t a -> Tensor n t a -> Tensor n t a 
squaredDifference x y = TSym "tf.squared_difference" <+> TArgT "x" x <+> TArgT "y" y 

squeeze' :: String -> String -> String -> String -> Tensor n t a 
squeeze' input axis name squeeze_dims = TSym "tf.squeeze" <+> TArgS "input" input <+> TArgS "axis" axis <+> TArgS "name" name <+> TArgS "squeeze_dims" squeeze_dims 
squeeze :: String -> Tensor n t a 
squeeze input = TSym "tf.squeeze" <+> TArgS "input" input 

stack' :: String -> String -> String -> Tensor n t a 
stack' values axis name = TSym "tf.stack" <+> TArgS "values" values <+> TArgS "axis" axis <+> TArgS "name" name 
stack :: String -> Tensor n t a 
stack values = TSym "tf.stack" <+> TArgS "values" values 

stopGradient' :: String -> String -> Tensor n t a 
stopGradient' input name = TSym "tf.stop_gradient" <+> TArgS "input" input <+> TArgS "name" name 
stopGradient :: String -> Tensor n t a 
stopGradient input = TSym "tf.stop_gradient" <+> TArgS "input" input 

stridedSlice' :: SingI n => String -> String -> String -> Sing n -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
stridedSlice' input_ begin end strides begin_mask end_mask ellipsis_mask new_axis_mask shrink_axis_mask var name = TSym "tf.strided_slice" <+> TArgS "input_" input_ <+> TArgS "begin" begin <+> TArgS "end" end <+> TArgSing "strides" strides <+> TArgS "begin_mask" begin_mask <+> TArgS "end_mask" end_mask <+> TArgS "ellipsis_mask" ellipsis_mask <+> TArgS "new_axis_mask" new_axis_mask <+> TArgS "shrink_axis_mask" shrink_axis_mask <+> TArgS "var" var <+> TArgS "name" name 
stridedSlice :: String -> String -> String -> Tensor n t a 
stridedSlice input_ begin end = TSym "tf.strided_slice" <+> TArgS "input_" input_ <+> TArgS "begin" begin <+> TArgS "end" end 

stringJoin' :: String -> String -> String -> Tensor n t a 
stringJoin' inputs separator name = TSym "tf.string_join" <+> TArgS "inputs" inputs <+> TArgS "separator" separator <+> TArgS "name" name 
stringJoin :: String -> Tensor n t a 
stringJoin inputs = TSym "tf.string_join" <+> TArgS "inputs" inputs 

stringSplit' :: String -> String -> Tensor n t a 
stringSplit' source delimiter = TSym "tf.string_split" <+> TArgS "source" source <+> TArgS "delimiter" delimiter 
stringSplit :: String -> Tensor n t a 
stringSplit source = TSym "tf.string_split" <+> TArgS "source" source 

stringToHashBucket' :: String -> String -> String -> Tensor n t a 
stringToHashBucket' string_tensor num_buckets name = TSym "tf.string_to_hash_bucket" <+> TArgS "string_tensor" string_tensor <+> TArgS "num_buckets" num_buckets <+> TArgS "name" name 
stringToHashBucket :: String -> String -> Tensor n t a 
stringToHashBucket string_tensor num_buckets = TSym "tf.string_to_hash_bucket" <+> TArgS "string_tensor" string_tensor <+> TArgS "num_buckets" num_buckets 

stringToHashBucketFast' :: String -> String -> String -> Tensor n t a 
stringToHashBucketFast' input num_buckets name = TSym "tf.string_to_hash_bucket_fast" <+> TArgS "input" input <+> TArgS "num_buckets" num_buckets <+> TArgS "name" name 
stringToHashBucketFast :: String -> String -> Tensor n t a 
stringToHashBucketFast input num_buckets = TSym "tf.string_to_hash_bucket_fast" <+> TArgS "input" input <+> TArgS "num_buckets" num_buckets 

stringToHashBucketStrong' :: String -> String -> String -> String -> Tensor n t a 
stringToHashBucketStrong' input num_buckets key name = TSym "tf.string_to_hash_bucket_strong" <+> TArgS "input" input <+> TArgS "num_buckets" num_buckets <+> TArgS "key" key <+> TArgS "name" name 
stringToHashBucketStrong :: String -> String -> String -> Tensor n t a 
stringToHashBucketStrong input num_buckets key = TSym "tf.string_to_hash_bucket_strong" <+> TArgS "input" input <+> TArgS "num_buckets" num_buckets <+> TArgS "key" key 

stringToNumber' :: String -> String -> String -> Tensor n t a 
stringToNumber' string_tensor out_type name = TSym "tf.string_to_number" <+> TArgS "string_tensor" string_tensor <+> TArgS "out_type" out_type <+> TArgS "name" name 
stringToNumber :: String -> Tensor n t a 
stringToNumber string_tensor = TSym "tf.string_to_number" <+> TArgS "string_tensor" string_tensor 

substr' :: String -> String -> String -> String -> Tensor n t a 
substr' input pos len name = TSym "tf.substr" <+> TArgS "input" input <+> TArgS "pos" pos <+> TArgS "len" len <+> TArgS "name" name 
substr :: String -> String -> String -> Tensor n t a 
substr input pos len = TSym "tf.substr" <+> TArgS "input" input <+> TArgS "pos" pos <+> TArgS "len" len 

subtract' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
subtract' x y name = TSym "tf.subtract" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
subtract :: Tensor n t a -> Tensor n t a -> Tensor n t a 
subtract x y = TSym "tf.subtract" <+> TArgT "x" x <+> TArgT "y" y 

svd' :: Tensor n t a -> String -> String -> String -> Tensor n t a 
svd' tensor full_matrices compute_uv name = TSym "tf.svd" <+> TArgT "tensor" tensor <+> TArgS "full_matrices" full_matrices <+> TArgS "compute_uv" compute_uv <+> TArgS "name" name 
svd :: Tensor n t a -> Tensor n t a 
svd tensor = TSym "tf.svd" <+> TArgT "tensor" tensor 


tablesInitializer :: Tensor n t a 
tablesInitializer = TSym "tf.tables_initializer" 

tan' :: Tensor n t a -> String -> Tensor n t a 
tan' x name = TSym "tf.tan" <+> TArgT "x" x <+> TArgS "name" name 


tanh' :: Tensor n t a -> String -> Tensor n t a 
tanh' x name = TSym "tf.tanh" <+> TArgT "x" x <+> TArgS "name" name 
tanh :: Tensor n t a -> Tensor n t a 
tanh x = TSym "tf.tanh" <+> TArgT "x" x 

tensordot' :: Tensor n t a -> Tensor n t a -> String -> String -> Tensor n t a 
tensordot' a b axes name = TSym "tf.tensordot" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "axes" axes <+> TArgS "name" name 
tensordot :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
tensordot a b axes = TSym "tf.tensordot" <+> TArgT "a" a <+> TArgT "b" b <+> TArgS "axes" axes 

tile' :: String -> String -> String -> Tensor n t a 
tile' input multiples name = TSym "tf.tile" <+> TArgS "input" input <+> TArgS "multiples" multiples <+> TArgS "name" name 
tile :: String -> String -> Tensor n t a 
tile input multiples = TSym "tf.tile" <+> TArgS "input" input <+> TArgS "multiples" multiples 

toBfloat16' :: Tensor n t a -> String -> Tensor n t a 
toBfloat16' x name = TSym "tf.to_bfloat16" <+> TArgT "x" x <+> TArgS "name" name 
toBfloat16 :: Tensor n t a -> Tensor n t a 
toBfloat16 x = TSym "tf.to_bfloat16" <+> TArgT "x" x 

toDouble' :: Tensor n t a -> String -> Tensor n t a 
toDouble' x name = TSym "tf.to_double" <+> TArgT "x" x <+> TArgS "name" name 
toDouble :: Tensor n t a -> Tensor n t a 
toDouble x = TSym "tf.to_double" <+> TArgT "x" x 

toFloat' :: Tensor n t a -> String -> Tensor n t a 
toFloat' x name = TSym "tf.to_float" <+> TArgT "x" x <+> TArgS "name" name 
toFloat :: Tensor n t a -> Tensor n t a 
toFloat x = TSym "tf.to_float" <+> TArgT "x" x 

toInt32' :: Tensor n t a -> String -> Tensor n t a 
toInt32' x name = TSym "tf.to_int32" <+> TArgT "x" x <+> TArgS "name" name 
toInt32 :: Tensor n t a -> Tensor n t a 
toInt32 x = TSym "tf.to_int32" <+> TArgT "x" x 

toInt64' :: Tensor n t a -> String -> Tensor n t a 
toInt64' x name = TSym "tf.to_int64" <+> TArgT "x" x <+> TArgS "name" name 
toInt64 :: Tensor n t a -> Tensor n t a 
toInt64 x = TSym "tf.to_int64" <+> TArgT "x" x 

trace' :: Tensor n t a -> String -> Tensor n t a 
trace' x name = TSym "tf.trace" <+> TArgT "x" x <+> TArgS "name" name 
trace :: Tensor n t a -> Tensor n t a 
trace x = TSym "tf.trace" <+> TArgT "x" x 


trainableVariables :: Tensor n t a 
trainableVariables = TSym "tf.trainable_variables" 

transpose' :: Tensor n t a -> String -> String -> Tensor n t a 
transpose' a perm name = TSym "tf.transpose" <+> TArgT "a" a <+> TArgS "perm" perm <+> TArgS "name" name 
transpose :: Tensor n t a -> Tensor n t a 
transpose a = TSym "tf.transpose" <+> TArgT "a" a 

truediv' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
truediv' x y name = TSym "tf.truediv" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
truediv :: Tensor n t a -> Tensor n t a -> Tensor n t a 
truediv x y = TSym "tf.truediv" <+> TArgT "x" x <+> TArgT "y" y 

truncatedNormal' :: SingI n => Sing n -> String -> String -> String -> String -> String -> Tensor n t a 
truncatedNormal' shape mean stddev dtype seed name = TSym "tf.truncated_normal" <+> TArgSing "shape" shape <+> TArgS "mean" mean <+> TArgS "stddev" stddev <+> TArgS "dtype" dtype <+> TArgS "seed" seed <+> TArgS "name" name 
truncatedNormal :: SingI n => Sing n -> Tensor n t a 
truncatedNormal shape = TSym "tf.truncated_normal" <+> TArgSing "shape" shape 

truncatediv' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
truncatediv' x y name = TSym "tf.truncatediv" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
truncatediv :: Tensor n t a -> Tensor n t a -> Tensor n t a 
truncatediv x y = TSym "tf.truncatediv" <+> TArgT "x" x <+> TArgT "y" y 

truncatemod' :: Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
truncatemod' x y name = TSym "tf.truncatemod" <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
truncatemod :: Tensor n t a -> Tensor n t a -> Tensor n t a 
truncatemod x y = TSym "tf.truncatemod" <+> TArgT "x" x <+> TArgT "y" y 

tuple' :: String -> String -> String -> Tensor n t a 
tuple' tensors name control_inputs = TSym "tf.tuple" <+> TArgS "tensors" tensors <+> TArgS "name" name <+> TArgS "control_inputs" control_inputs 
tuple :: String -> Tensor n t a 
tuple tensors = TSym "tf.tuple" <+> TArgS "tensors" tensors 

unique' :: Tensor n t a -> String -> String -> Tensor n t a 
unique' x out_idx name = TSym "tf.unique" <+> TArgT "x" x <+> TArgS "out_idx" out_idx <+> TArgS "name" name 
unique :: Tensor n t a -> Tensor n t a 
unique x = TSym "tf.unique" <+> TArgT "x" x 

uniqueWithCounts' :: Tensor n t a -> String -> String -> Tensor n t a 
uniqueWithCounts' x out_idx name = TSym "tf.unique_with_counts" <+> TArgT "x" x <+> TArgS "out_idx" out_idx <+> TArgS "name" name 
uniqueWithCounts :: Tensor n t a -> Tensor n t a 
uniqueWithCounts x = TSym "tf.unique_with_counts" <+> TArgT "x" x 

unsortedSegmentMax' :: String -> String -> String -> String -> Tensor n t a 
unsortedSegmentMax' data' segment_ids num_segments name = TSym "tf.unsorted_segment_max" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "num_segments" num_segments <+> TArgS "name" name 
unsortedSegmentMax :: String -> String -> String -> Tensor n t a 
unsortedSegmentMax data' segment_ids num_segments = TSym "tf.unsorted_segment_max" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "num_segments" num_segments 

unsortedSegmentSum' :: String -> String -> String -> String -> Tensor n t a 
unsortedSegmentSum' data' segment_ids num_segments name = TSym "tf.unsorted_segment_sum" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "num_segments" num_segments <+> TArgS "name" name 
unsortedSegmentSum :: String -> String -> String -> Tensor n t a 
unsortedSegmentSum data' segment_ids num_segments = TSym "tf.unsorted_segment_sum" <+> TArgS "data" data' <+> TArgS "segment_ids" segment_ids <+> TArgS "num_segments" num_segments 

unstack' :: String -> String -> String -> String -> Tensor n t a 
unstack' value num axis name = TSym "tf.unstack" <+> TArgS "value" value <+> TArgS "num" num <+> TArgS "axis" axis <+> TArgS "name" name 
unstack :: String -> Tensor n t a 
unstack value = TSym "tf.unstack" <+> TArgS "value" value 

variableAxisSizePartitioner' :: String -> String -> String -> String -> Tensor n t a 
variableAxisSizePartitioner' max_shard_bytes axis bytes_per_string_element max_shards = TSym "tf.variable_axis_size_partitioner" <+> TArgS "max_shard_bytes" max_shard_bytes <+> TArgS "axis" axis <+> TArgS "bytes_per_string_element" bytes_per_string_element <+> TArgS "max_shards" max_shards 
variableAxisSizePartitioner :: String -> Tensor n t a 
variableAxisSizePartitioner max_shard_bytes = TSym "tf.variable_axis_size_partitioner" <+> TArgS "max_shard_bytes" max_shard_bytes 


variableOpScope :: Tensor n t a 
variableOpScope = TSym "tf.variable_op_scope" 


variableScope :: Tensor n t a 
variableScope = TSym "tf.variable_scope" 

variablesInitializer' :: String -> String -> Tensor n t a 
variablesInitializer' var_list name = TSym "tf.variables_initializer" <+> TArgS "var_list" var_list <+> TArgS "name" name 
variablesInitializer :: String -> Tensor n t a 
variablesInitializer var_list = TSym "tf.variables_initializer" <+> TArgS "var_list" var_list 

verifyTensorAllFinite' :: String -> String -> String -> Tensor n t a 
verifyTensorAllFinite' t msg name = TSym "tf.verify_tensor_all_finite" <+> TArgS "t" t <+> TArgS "msg" msg <+> TArgS "name" name 
verifyTensorAllFinite :: String -> String -> Tensor n t a 
verifyTensorAllFinite t msg = TSym "tf.verify_tensor_all_finite" <+> TArgS "t" t <+> TArgS "msg" msg 

tfwhere' :: String -> Tensor n t a -> Tensor n t a -> String -> Tensor n t a 
tfwhere' condition x y name = TSym "tf.where" <+> TArgS "condition" condition <+> TArgT "x" x <+> TArgT "y" y <+> TArgS "name" name 
tfwhere :: String -> Tensor n t a 
tfwhere condition = TSym "tf.where" <+> TArgS "condition" condition 

whileLoop' :: String -> String -> String -> String -> String -> String -> String -> String -> Tensor n t a 
whileLoop' cond body loop_vars shape_invariants parallel_iterations back_prop swap_memory name = TSym "tf.while_loop" <+> TArgS "cond" cond <+> TArgS "body" body <+> TArgS "loop_vars" loop_vars <+> TArgS "shape_invariants" shape_invariants <+> TArgS "parallel_iterations" parallel_iterations <+> TArgS "back_prop" back_prop <+> TArgS "swap_memory" swap_memory <+> TArgS "name" name 
whileLoop :: String -> String -> String -> Tensor n t a 
whileLoop cond body loop_vars = TSym "tf.while_loop" <+> TArgS "cond" cond <+> TArgS "body" body <+> TArgS "loop_vars" loop_vars 

writeFile' :: String -> String -> String -> Tensor n t a 
writeFile' filename contents name = TSym "tf.write_file" <+> TArgS "filename" filename <+> TArgS "contents" contents <+> TArgS "name" name 
writeFile :: String -> String -> Tensor n t a 
writeFile filename contents = TSym "tf.write_file" <+> TArgS "filename" filename <+> TArgS "contents" contents 

zeros' :: SingI n => Sing n -> String -> String -> Tensor n t a 
zeros' shape dtype name = TSym "tf.zeros" <+> TArgSing "shape" shape <+> TArgS "dtype" dtype <+> TArgS "name" name 
zeros :: SingI n => Sing n -> Tensor n t a 
zeros shape = TSym "tf.zeros" <+> TArgSing "shape" shape 

zerosLike' :: Tensor n t a -> String -> String -> String -> Tensor n t a 
zerosLike' tensor dtype name optimize = TSym "tf.zeros_like" <+> TArgT "tensor" tensor <+> TArgS "dtype" dtype <+> TArgS "name" name <+> TArgS "optimize" optimize 
zerosLike :: Tensor n t a -> Tensor n t a 
zerosLike tensor = TSym "tf.zeros_like" <+> TArgT "tensor" tensor 

zeta' :: Tensor n t a -> String -> String -> Tensor n t a 
zeta' x q name = TSym "tf.zeta" <+> TArgT "x" x <+> TArgS "q" q <+> TArgS "name" name 
zeta :: Tensor n t a -> String -> Tensor n t a 
zeta x q = TSym "tf.zeta" <+> TArgT "x" x <+> TArgS "q" q