Copyright | (c) Jean-Philippe Bernardy 2017 |
---|---|
License | LGPL-3 |
Maintainer | jean-philippe.bernardy@gu.se |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module provides direct access to the most commonly used TensorFlow functions. Higher-level functions are not defined here.
- parameter' :: forall shape t. (KnownTyp t, KnownShape shape) => String -> T shape t -> Gen (T shape t)
- parameter :: forall p. KnownTensors p => String -> p -> Gen p
- parameterDefault :: forall p. ParamWithDefault p => String -> Gen p
- class KnownTensors p => ParamWithDefault p where
- getParameters :: Gen UntypedExpression
- persistent :: forall shape t. (KnownTyp t, KnownShape shape) => Bool -> String -> T shape t -> Gen (T shape t)
- modifyPersistent :: T s t -> T s t -> T s t
- placeholder :: forall t s. (KnownShape s, KnownTyp t) => String -> Gen (T s t)
- peekAt :: String -> Tensor s t -> Gen ()
- peekAtMany :: String -> HTV t xs -> Gen ()
- zeros :: forall t shape. KnownShape shape => KnownTyp t => T shape t
- ones :: forall t shape. KnownShape shape => KnownTyp t => T shape t
- constant :: forall s w. KnownShape s => KnownBits w => Float -> T s (Typ Float w)
- round :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- sigmoid :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- tanh :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- log :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- relu :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- floor :: forall s t. Tensor s (Typ Float t) -> Tensor s (Typ Float t)
- negate :: forall s t. T s t -> T s t
- add :: forall s d t. Tensor (d ++ s) t -> Tensor d t -> Tensor (d ++ s) t
- (+) :: forall d s t. Tensor (d ++ s) t -> Tensor d t -> Tensor (d ++ s) t
- (⊕) :: forall s t. Tensor s t -> Tensor s t -> Tensor s t
- (⊝) :: forall s t. Tensor s t -> Tensor s t -> Tensor s t
- (⊙) :: forall s t. Tensor s t -> Tensor s t -> Tensor s t
- (⊘) :: forall s t. Tensor s t -> Tensor s t -> Tensor s t
- equal :: Tensor d t -> Tensor d t -> Tensor d TFBool
- (∙) :: Tensor '[cols, rows] t -> Tensor '[cols, batchSize] t -> Tensor '[rows, batchSize] t
- · :: forall cols batchSize t. Tensor '[cols, batchSize] t -> Tensor '[cols, batchSize] t -> Tensor '[batchSize] t
- matmul :: Tensor (o ': (n ': s)) t -> Tensor (m ': (o ': s)) t -> Tensor (m ': (n ': s)) t
- reduceMeanAll :: forall s t. Tensor s t -> Tensor '[] t
- reduceSumAll :: forall s t. Tensor s t -> Tensor '[] t
- reduceSum :: forall n s t. (KnownLen s, KnownPeano n) => T s t -> T (Take n s ++ Drop (Succ n) s) t
- reduceMean :: forall n s t. (KnownLen s, KnownPeano n) => T s t -> T (Take n s ++ Drop (Succ n) s) t
- argmax :: forall n u m s t. (KnownLen s, KnownPeano n, KnownBits u) => Tensor (Take n s ++ (m ': Drop n s)) t -> Tensor s (Typ Int u)
- argmax0 :: forall u n s t. (KnownLen s, KnownBits u) => T (n ': s) t -> T s (Typ Int u)
- argmax1 :: forall u m n s t. (KnownLen s, KnownBits u) => T (m ': (n ': s)) t -> T (m ': s) (Typ Int u)
- softmax0 :: T (n ': s) (Typ Float w) -> T (n ': s) (Typ Float w)
- softmax1 :: forall n m s w. KnownLen s => T (m ': (n ': s)) (Typ Float w) -> T (m ': (n ': s)) (Typ Float w)
- grad :: T s Float32 -> UntypedExpression -> UntypedExpression
- clipByGlobalNorm :: Float -> UntypedExpression -> UntypedExpression
- clipByValue :: Float -> Float -> T s (Flt t) -> T s (Flt t)
- last0 :: forall n s t. KnownNat n => KnownLen s => T (n ': s) t -> Tensor s t
- nth0 :: forall n s t. KnownLen s => Integer -> T (n ': s) t -> Tensor s t
- nth0' :: forall n m s t. KnownNat n => KnownLen s => n < m => T (m ': s) t -> Tensor s t
- gather :: forall s n indexShape t. T (s ++ '[n]) t -> T indexShape Int32 -> T (s ++ indexShape) t
- split0 :: forall n m batchShape t. (KnownNat n, KnownNat m, KnownLen batchShape) => Tensor ((n + m) ': batchShape) t -> Gen (Tensor (n ': batchShape) t, Tensor (m ': batchShape) t)
- slice :: forall n i j s t. KnownNat j => KnownNat i => (i < j, j <= At n s, KnownPeano n, KnownLen s) => Tensor s t -> Tensor (Take n s ++ ((j - i) ': Drop (Succ n) s)) t
- slice1 :: forall i j m n s t. KnownNat j => KnownNat i => (i < j, j <= m, KnownLen s) => Tensor (n ': (m ': s)) t -> Tensor (n ': ((j - i) ': s)) t
- stack0 :: forall s n t. KnownLen s => V n (T s t) -> Tensor (n ': s) t
- unstack0 :: forall s n t. (KnownLen s, KnownNat n) => Tensor (n ': s) t -> Gen (V n (T s t))
- stackN :: forall s n t. V n (T s t) -> Tensor (s ++ '[n]) t
- stack1 :: forall s n m t. KnownLen s => V n (T (m ': s) t) -> Tensor (m ': (n ': s)) t
- concatT :: forall n d1 d2 s t. (KnownPeano n, KnownLen s, (d1 + d2) ~ At n s) => T (Take n s ++ (d1 ': Drop (Succ n) s)) t -> T (Take n s ++ (d2 ': Drop (Succ n) s)) t -> T s t
- concat0 :: forall ys d1 d2 t. KnownLen ys => T (d1 ': ys) t -> T (d2 ': ys) t -> T ((d1 + d2) ': ys) t
- concat1 :: forall n ys d1 d2 t. KnownLen ys => T (n ': (d1 ': ys)) t -> T (n ': (d2 ': ys)) t -> T (n ': ((d1 + d2) ': ys)) t
- expandDim :: forall n s t. (KnownLen s, KnownPeano n) => Tensor s t -> Tensor (Take n s ++ (1 ': Drop n s)) t
- expandDim0 :: forall s t. KnownLen s => Tensor s t -> Tensor (1 ': s) t
- squeeze0 :: forall s t. KnownLen s => Tensor (1 ': s) t -> Tensor s t
- expandDim1 :: forall n s t. KnownShape s => Tensor (n ': s) t -> Tensor (n ': (1 ': s)) t
- squeeze1 :: forall n s t. KnownLen s => Tensor (n ': (1 ': s)) t -> Tensor (n ': s) t
- flatten2 :: forall m n s t. (KnownNat m, KnownNat n, KnownShape s) => Tensor (m ': (n ': s)) t -> Tensor ((m * n) ': s) t
- inflate2 :: forall m n s t. (KnownNat m, KnownNat n, KnownShape s) => Tensor ((m * n) ': s) t -> Tensor (m ': (n ': s)) t
- flattenN2 :: forall s m n t. (KnownNat m, KnownNat n, KnownShape s) => Tensor (s ++ '[m, n]) t -> Tensor (s ++ '[m * n]) t
- flatten3 :: forall m n o s t. (KnownNat m, KnownNat n, KnownNat o, KnownShape s) => Tensor (m ': (n ': (o ': s))) t -> Tensor (((m * n) * o) ': s) t
- inflate3 :: forall m n o s t. (KnownNat m, KnownNat n, KnownNat o, KnownShape s) => Tensor (((m * n) * o) ': s) t -> Tensor (m ': (n ': (o ': s))) t
- reshape :: forall s2 s1 t. KnownShape s2 => Product s1 ~ Product s2 => Tensor s1 t -> Tensor s2 t
- flattenAll :: forall s t. KnownShape s => Tensor s t -> Tensor '[Product s] t
- inflateAll :: forall s t. KnownShape s => Tensor '[Product s] t -> Tensor s t
- transpose :: forall s t. T (Reverse s) t -> T s t
- transposeN :: forall s n t. KnownLen s => T (n ': s) t -> T (s ++ '[n]) t
- transposeN' :: forall s n t. KnownLen s => T (s ++ '[n]) t -> T (n ': s) t
- transpose01 :: forall s m n t. KnownLen s => T (m ': (n ': s)) t -> T (n ': (m ': s)) t
- transposeN01 :: forall s m n t. T (s ++ '[m, n]) t -> T (s ++ '[n, m]) t
- reverseSequences :: forall bs n x t. KnownLen x => LastEqual bs x => T '[bs] Int32 -> T (n ': x) t -> T (n ': x) t
- sequenceMask :: forall maxlen bs. KnownNat maxlen => Tensor '[bs] Int32 -> Tensor '[maxlen, bs] TFBool
- cast :: forall u s t. KnownTyp u => T s t -> T s u
- convolution :: forall outputChannels filterSpatialShape inChannels s t. KnownLen filterSpatialShape => Length filterSpatialShape <= 3 => (1 + Length filterSpatialShape) ~ Length s => T ('[inChannels] ++ s) t -> T ('[outputChannels, inChannels] ++ filterSpatialShape) t -> T ('[outputChannels] ++ s) t
- oneHot :: forall n numClasses s w t. KnownNat numClasses => KnownBits t => (KnownLen s, KnownPeano n) => Tensor s (Typ Int w) -> Tensor (Take n s ++ (numClasses ': Drop n s)) (Flt t)
- oneHot0 :: forall numClasses w batchSize t. KnownNat numClasses => KnownBits t => Tensor '[batchSize] (Typ Int w) -> Tensor '[numClasses, batchSize] (Flt t)
- oneHot1 :: forall numClasses w batchSize m t. KnownNat numClasses => KnownBits t => Tensor '[m, batchSize] (Typ Int w) -> Tensor '[m, numClasses, batchSize] (Flt t)
- if_ :: Scalar TFBool -> T s t -> T s t -> T s t
- where_ :: T s TFBool -> T s t -> T s t -> T s t
- mapT :: forall s t r u n. KnownTyp u => KnownLen r => KnownLen s => (T s t -> T r u) -> T (n ': s) t -> Gen (T (n ': r) u)
- mapTN :: forall n s t r u. KnownTyp u => (T s t -> T r u) -> T (s ++ '[n]) t -> Gen (T (r ++ '[n]) u)
- zipWithT :: forall s t s1 t1 s2 n t2. KnownNat n => (KnownLen s, KnownLen s2, KnownLen s1) => KnownTyp t2 => (T s t -> T s1 t1 -> T s2 t2) -> Tensor (n ': s) t -> Tensor (n ': s1) t1 -> Gen (Tensor (n ': s2) t2)
- zipWithTN :: forall n s t s1 t1 s2 t2. KnownTyp t2 => (T s t -> T s1 t1 -> T s2 t2) -> Tensor (s ++ '[n]) t -> Tensor (s1 ++ '[n]) t1 -> Gen (Tensor (s2 ++ '[n]) t2)
- sigmoidCrossEntropyWithLogits :: Tensor s (Flt w) -> Tensor s (Flt w) -> Tensor s (Flt w)
- softmaxCrossEntropyWithLogits :: Tensor '[numClasses, batchSize] Float32 -> Tensor '[numClasses, batchSize] Float32 -> Tensor '[batchSize] Float32
- sparseSoftmaxCrossEntropyWithLogits :: Tensor s Int32 -> Tensor (numClasses ': s) (Flt t) -> Tensor s (Flt t)
- truncatedNormal :: forall s w. KnownShape s => KnownBits w => Float -> T s (Typ Float w)
- randomUniform :: forall s t. (KnownShape s, KnownTyp t) => Float -> Float -> T s t
- randomOrthogonal :: forall n s t. (KnownBits t, KnownNat n, KnownShape s) => T (n ': s) (Typ Float t)
- varianceScaling :: forall inDim outDim t. KnownNat inDim => (KnownNat outDim, KnownBits t) => Float -> VarianceScaleMode -> Distrib -> Tensor '[inDim, outDim] (Typ Float t)
- glorotUniform :: forall inDim outDim t. KnownNat inDim => (KnownNat outDim, KnownBits t) => Tensor '[inDim, outDim] (Typ Float t)
- repeatT :: forall ss t. All KnownShape ss => KnownLen ss => (forall s. KnownShape s => T s t) -> HTV t ss
- flattenHTV :: KnownTyp t => All KnownShape xs => HTV t xs -> Tensor '[Sum (Ap (FMap CProduct) xs)] t
- inflateHTV :: forall xs s t. (All KnownShape xs, KnownLen s, KnownLen xs) => Tensor '[Sum (Ap (FMap CProduct) xs)] t -> Gen (HTV t xs)
- class KnownTensors p where
- class LastEqual x xs
Variables, Parameters
Parameters
parameter' :: forall shape t. (KnownTyp t, KnownShape shape) => String -> T shape t -> Gen (T shape t) Source #
Declare a parameter to optimize. The shape of parameter should not depend on dimensions which can change between runs, such as the batch size.
parameterDefault :: forall p. ParamWithDefault p => String -> Gen p Source #
Create a parameter and initialize it with a suitable default for its type. Control the exact initializer using parameter
.
class KnownTensors p => ParamWithDefault p where Source #
defaultInitializer :: p Source #
(KnownNat numObjects, KnownBits NBits b, KnownNat embeddingSize) => ParamWithDefault (EmbeddingP numObjects embeddingSize b) Source # | |
(KnownNat n, KnownNat m, KnownBits NBits b) => ParamWithDefault (DenseP b n m) Source # | |
(KnownNat n, KnownNat x, KnownBits NBits t) => ParamWithDefault (GRUP t n x) Source # | |
(KnownNat n, KnownNat x, KnownBits NBits t) => ParamWithDefault (LSTMP t n x) Source # | |
(KnownNat outChannels, KnownNat inChannels, KnownShape filterSpatialShape, KnownBits NBits t) => ParamWithDefault (ConvP t outChannels inChannels filterSpatialShape) Source # | |
(KnownNat n, KnownNat k, KnownNat v, KnownBits NBits t) => ParamWithDefault (AdditiveScoringP k v n t) Source # | |
getParameters :: Gen UntypedExpression Source #
Return a list of parameters.
Persistent variables
persistent :: forall shape t. (KnownTyp t, KnownShape shape) => Bool -> String -> T shape t -> Gen (T shape t) Source #
Declare variable which persists between calls to session.run.
modifyPersistent :: T s t -> T s t -> T s t Source #
Modify a mutable tensor. Attention: for the assignment to happen, the resulting tensor must be evaluated!
Placeholders and outputs
placeholder :: forall t s. (KnownShape s, KnownTyp t) => String -> Gen (T s t) Source #
Placeholder (to fill)
peekAt :: String -> Tensor s t -> Gen () Source #
Name a tensor so that it is made available for session.run.
Operations
Constants
indexwise unary operators
Indexwise binary operators
add :: forall s d t. Tensor (d ++ s) t -> Tensor d t -> Tensor (d ++ s) t Source #
Add two tensors, broacasting along shape s
(+) :: forall d s t. Tensor (d ++ s) t -> Tensor d t -> Tensor (d ++ s) t infixl 6 Source #
Add two tensors, broacasting along shape s
Products
(∙) :: Tensor '[cols, rows] t -> Tensor '[cols, batchSize] t -> Tensor '[rows, batchSize] t infixl 7 Source #
Product of a matrix of weight with a (batched) vector .
· :: forall cols batchSize t. Tensor '[cols, batchSize] t -> Tensor '[cols, batchSize] t -> Tensor '[batchSize] t infixl 7 Source #
Dot product between two batched vectors.
matmul :: Tensor (o ': (n ': s)) t -> Tensor (m ': (o ': s)) t -> Tensor (m ': (n ': s)) t Source #
Matrix multiplication (note that shape s
is preserved)
Reducers
reduceMeanAll :: forall s t. Tensor s t -> Tensor '[] t Source #
Mean value of the input tensor.
reduceSumAll :: forall s t. Tensor s t -> Tensor '[] t Source #
Mean value of the input tensor.
reduceSum :: forall n s t. (KnownLen s, KnownPeano n) => T s t -> T (Take n s ++ Drop (Succ n) s) t Source #
Sum along a given dimension
reduceMean :: forall n s t. (KnownLen s, KnownPeano n) => T s t -> T (Take n s ++ Drop (Succ n) s) t Source #
Sum along a given dimension
argmax :: forall n u m s t. (KnownLen s, KnownPeano n, KnownBits u) => Tensor (Take n s ++ (m ': Drop n s)) t -> Tensor s (Typ Int u) Source #
Argmax along dimension n
argmax0 :: forall u n s t. (KnownLen s, KnownBits u) => T (n ': s) t -> T s (Typ Int u) Source #
Argmax along the first dimension
argmax1 :: forall u m n s t. (KnownLen s, KnownBits u) => T (m ': (n ': s)) t -> T (m ': s) (Typ Int u) Source #
Argmax along the second dimension
softmax0 :: T (n ': s) (Typ Float w) -> T (n ': s) (Typ Float w) Source #
Softmax along the first dimension
softmax1 :: forall n m s w. KnownLen s => T (m ': (n ': s)) (Typ Float w) -> T (m ': (n ': s)) (Typ Float w) Source #
Softmax along the second dimension
Gradients
grad :: T s Float32 -> UntypedExpression -> UntypedExpression Source #
Gradient of wrt. given parameters.
clipByGlobalNorm :: Float -> UntypedExpression -> UntypedExpression Source #
Clip a gradient
Indexing
last0 :: forall n s t. KnownNat n => KnownLen s => T (n ': s) t -> Tensor s t Source #
Access the last element in a tensor (in the 0th dimension)
nth0 :: forall n s t. KnownLen s => Integer -> T (n ': s) t -> Tensor s t Source #
Access the nth element in a tensor (in the 0th dimension)
nth0' :: forall n m s t. KnownNat n => KnownLen s => n < m => T (m ': s) t -> Tensor s t Source #
Access the nth element in a tensor (in the 0th dimension), with a static index
gather :: forall s n indexShape t. T (s ++ '[n]) t -> T indexShape Int32 -> T (s ++ indexShape) t Source #
(gather x ix)[k] = x[ix[k]]
. See https://www.tensorflow.org/api_docs/python/tf/gather
Split and concatenate
split0 :: forall n m batchShape t. (KnownNat n, KnownNat m, KnownLen batchShape) => Tensor ((n + m) ': batchShape) t -> Gen (Tensor (n ': batchShape) t, Tensor (m ': batchShape) t) Source #
Split a tensor on the first dimension
slice :: forall n i j s t. KnownNat j => KnownNat i => (i < j, j <= At n s, KnownPeano n, KnownLen s) => Tensor s t -> Tensor (Take n s ++ ((j - i) ': Drop (Succ n) s)) t Source #
Take a slice at dimension n from i to j.
slice1 :: forall i j m n s t. KnownNat j => KnownNat i => (i < j, j <= m, KnownLen s) => Tensor (n ': (m ': s)) t -> Tensor (n ': ((j - i) ': s)) t Source #
stack0 :: forall s n t. KnownLen s => V n (T s t) -> Tensor (n ': s) t Source #
Concatenate n
tensors along the first dimension
unstack0 :: forall s n t. (KnownLen s, KnownNat n) => Tensor (n ': s) t -> Gen (V n (T s t)) Source #
Split a tensors into n
tensors along the first dimension
stackN :: forall s n t. V n (T s t) -> Tensor (s ++ '[n]) t Source #
Concatenate n
tensors along the last dimension
stack1 :: forall s n m t. KnownLen s => V n (T (m ': s) t) -> Tensor (m ': (n ': s)) t Source #
Concatenate n
tensors along the first dimension
concatT :: forall n d1 d2 s t. (KnownPeano n, KnownLen s, (d1 + d2) ~ At n s) => T (Take n s ++ (d1 ': Drop (Succ n) s)) t -> T (Take n s ++ (d2 ': Drop (Succ n) s)) t -> T s t Source #
Concatenate tensors on dimension n
concat0 :: forall ys d1 d2 t. KnownLen ys => T (d1 ': ys) t -> T (d2 ': ys) t -> T ((d1 + d2) ': ys) t Source #
Concatenate tensors on the first dimension
concat1 :: forall n ys d1 d2 t. KnownLen ys => T (n ': (d1 ': ys)) t -> T (n ': (d2 ': ys)) t -> T (n ': ((d1 + d2) ': ys)) t Source #
Concatenate tensors on the second dimension
Reshaping
expandDim :: forall n s t. (KnownLen s, KnownPeano n) => Tensor s t -> Tensor (Take n s ++ (1 ': Drop n s)) t Source #
Add an extra dimension at axis (n
) of size 1.
expandDim0 :: forall s t. KnownLen s => Tensor s t -> Tensor (1 ': s) t Source #
Add an extra dimension at axis (0) of size 1.
squeeze0 :: forall s t. KnownLen s => Tensor (1 ': s) t -> Tensor s t Source #
Remove the first dimension if its size is 1.
expandDim1 :: forall n s t. KnownShape s => Tensor (n ': s) t -> Tensor (n ': (1 ': s)) t Source #
Add an extra dimension at axis (1) of size 1.
squeeze1 :: forall n s t. KnownLen s => Tensor (n ': (1 ': s)) t -> Tensor (n ': s) t Source #
Remove the second dimension if its size is 1.
flatten2 :: forall m n s t. (KnownNat m, KnownNat n, KnownShape s) => Tensor (m ': (n ': s)) t -> Tensor ((m * n) ': s) t Source #
Reshape a tensor so that the first two dimensions are collapsed
inflate2 :: forall m n s t. (KnownNat m, KnownNat n, KnownShape s) => Tensor ((m * n) ': s) t -> Tensor (m ': (n ': s)) t Source #
Reshape a tensor so that the first dimension is expanded into two.
flattenN2 :: forall s m n t. (KnownNat m, KnownNat n, KnownShape s) => Tensor (s ++ '[m, n]) t -> Tensor (s ++ '[m * n]) t Source #
Reshape a tensor so that the last two dimensions are collapsed
flatten3 :: forall m n o s t. (KnownNat m, KnownNat n, KnownNat o, KnownShape s) => Tensor (m ': (n ': (o ': s))) t -> Tensor (((m * n) * o) ': s) t Source #
Reshape a tensor so that the first three dimensions are collapsed
inflate3 :: forall m n o s t. (KnownNat m, KnownNat n, KnownNat o, KnownShape s) => Tensor (((m * n) * o) ': s) t -> Tensor (m ': (n ': (o ': s))) t Source #
Reshape a tensor so that the first dimension is expanded into three.
reshape :: forall s2 s1 t. KnownShape s2 => Product s1 ~ Product s2 => Tensor s1 t -> Tensor s2 t Source #
flattenAll :: forall s t. KnownShape s => Tensor s t -> Tensor '[Product s] t Source #
Flatten all the dimensions of the tensor
inflateAll :: forall s t. KnownShape s => Tensor '[Product s] t -> Tensor s t Source #
Transposition
transpose :: forall s t. T (Reverse s) t -> T s t Source #
Transposition. See the type for the permutation of dimensions.
transposeN :: forall s n t. KnownLen s => T (n ': s) t -> T (s ++ '[n]) t Source #
Transposition. See the type for the permutation of dimensions.
transposeN' :: forall s n t. KnownLen s => T (s ++ '[n]) t -> T (n ': s) t Source #
Transposition. See the type for the permutation of dimensions.
transpose01 :: forall s m n t. KnownLen s => T (m ': (n ': s)) t -> T (n ': (m ': s)) t Source #
Transposition. See the type for the permutation of dimensions.
transposeN01 :: forall s m n t. T (s ++ '[m, n]) t -> T (s ++ '[n, m]) t Source #
Transposition. See the type for the permutation of dimensions.
Sequences
reverseSequences :: forall bs n x t. KnownLen x => LastEqual bs x => T '[bs] Int32 -> T (n ': x) t -> T (n ': x) t Source #
Reverse sequences. See https://www.tensorflow.org/api_docs/python/tf/reverse_sequence
sequenceMask :: forall maxlen bs. KnownNat maxlen => Tensor '[bs] Int32 -> Tensor '[maxlen, bs] TFBool Source #
Generate a mask of given length for each sequence.
Misc
:: KnownLen filterSpatialShape | |
=> Length filterSpatialShape <= 3 | |
=> (1 + Length filterSpatialShape) ~ Length s | |
=> T ('[inChannels] ++ s) t | input tensor (batched) |
-> T ('[outputChannels, inChannels] ++ filterSpatialShape) t | filters |
-> T ('[outputChannels] ++ s) t |
Size-preserving convolution operation.
oneHot :: forall n numClasses s w t. KnownNat numClasses => KnownBits t => (KnownLen s, KnownPeano n) => Tensor s (Typ Int w) -> Tensor (Take n s ++ (numClasses ': Drop n s)) (Flt t) Source #
One hot vector along axis n
oneHot0 :: forall numClasses w batchSize t. KnownNat numClasses => KnownBits t => Tensor '[batchSize] (Typ Int w) -> Tensor '[numClasses, batchSize] (Flt t) Source #
One hot vector along axis 0
oneHot1 :: forall numClasses w batchSize m t. KnownNat numClasses => KnownBits t => Tensor '[m, batchSize] (Typ Int w) -> Tensor '[m, numClasses, batchSize] (Flt t) Source #
One hot vector along axis 1
Testing conditions
if_ :: Scalar TFBool -> T s t -> T s t -> T s t Source #
Selection of a tensor (note: this is a strict operation)
where_ :: T s TFBool -> T s t -> T s t -> T s t Source #
(where_ c x y)[i] = if c[i] then x[i] else y[i]
Contrib
Mapping
mapT :: forall s t r u n. KnownTyp u => KnownLen r => KnownLen s => (T s t -> T r u) -> T (n ': s) t -> Gen (T (n ': r) u) Source #
Map a function along the first dimension of a tensor
mapTN :: forall n s t r u. KnownTyp u => (T s t -> T r u) -> T (s ++ '[n]) t -> Gen (T (r ++ '[n]) u) Source #
Map a function along the last dimension of a tensor
zipWithT :: forall s t s1 t1 s2 n t2. KnownNat n => (KnownLen s, KnownLen s2, KnownLen s1) => KnownTyp t2 => (T s t -> T s1 t1 -> T s2 t2) -> Tensor (n ': s) t -> Tensor (n ': s1) t1 -> Gen (Tensor (n ': s2) t2) Source #
zipWithTN :: forall n s t s1 t1 s2 t2. KnownTyp t2 => (T s t -> T s1 t1 -> T s2 t2) -> Tensor (s ++ '[n]) t -> Tensor (s1 ++ '[n]) t1 -> Gen (Tensor (s2 ++ '[n]) t2) Source #
Losses
sigmoidCrossEntropyWithLogits Source #
Computes sigmoid cross entropy given logits. Measures the probability error in discrete classification tasks in which each class is independent and not mutually exclusive. For instance, one could perform multilabel classification where a picture can contain both an elephant and a dog at the same time. See https://www.tensorflow.org/api_docs/python/tf/nn/sigmoid_cross_entropy_with_logits
softmaxCrossEntropyWithLogits Source #
:: Tensor '[numClasses, batchSize] Float32 | labels |
-> Tensor '[numClasses, batchSize] Float32 | logits |
-> Tensor '[batchSize] Float32 |
(dense) softmax cross entropy with logits.
sparseSoftmaxCrossEntropyWithLogits Source #
sparse softmax cross entropy with logits.
Initializers
truncatedNormal :: forall s w. KnownShape s => KnownBits w => Float -> T s (Typ Float w) Source #
Generate a random tensor where each individual element is picked in a normal distribution with given standard deviation.
randomUniform :: forall s t. (KnownShape s, KnownTyp t) => Float -> Float -> T s t Source #
Generate a random tensor where each individual element is picked in a uniform distribution with given bounds.
randomOrthogonal :: forall n s t. (KnownBits t, KnownNat n, KnownShape s) => T (n ': s) (Typ Float t) Source #
Generate an orthorgonal matrix. If the output has more dimensions than 2 the matrix is reshaped.
varianceScaling :: forall inDim outDim t. KnownNat inDim => (KnownNat outDim, KnownBits t) => Float -> VarianceScaleMode -> Distrib -> Tensor '[inDim, outDim] (Typ Float t) Source #
Random tensor with variance scaling according to deeplearning lore.
glorotUniform :: forall inDim outDim t. KnownNat inDim => (KnownNat outDim, KnownBits t) => Tensor '[inDim, outDim] (Typ Float t) Source #
Heterogeneous vectors
repeatT :: forall ss t. All KnownShape ss => KnownLen ss => (forall s. KnownShape s => T s t) -> HTV t ss Source #
Repeat a flexible-shape constant vector to form a heterogeneous tensor vector.
flattenHTV :: KnownTyp t => All KnownShape xs => HTV t xs -> Tensor '[Sum (Ap (FMap CProduct) xs)] t Source #
inflateHTV :: forall xs s t. (All KnownShape xs, KnownLen s, KnownLen xs) => Tensor '[Sum (Ap (FMap CProduct) xs)] t -> Gen (HTV t xs) Source #
class KnownTensors p where Source #
travTensor :: (forall s t. (KnownTyp t, KnownShape s) => String -> T s t -> Gen (T s t)) -> String -> p -> Gen p Source #
traverse all the tensors over tuples of tensors