hasktorch-indef-0.0.1.0: Core Hasktorch abstractions wrapping FFI bindings

Copyright(c) Sam Stites 2017
LicenseBSD3
Maintainersam@stites.io
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Torch.Indef.Static.Tensor.Math.Reduce

Description

 
Synopsis

Documentation

minall :: Tensor d -> HsReal Source #

Static call to minall

maxall :: Tensor d -> HsReal Source #

Static call to maxall

medianall :: Tensor d -> HsReal Source #

Static call to medianall

sumall :: Tensor d -> HsAccReal Source #

Static call to sumall

prodall :: Tensor d -> HsAccReal Source #

Static call to prodall

min :: forall d n ix rs ls. All Dimensions '[d, rs ++ ('[1] ++ ls)] => All KnownNat '[n, ix] => All KnownDim '[n, ix] => (Length d > ix) ~ True => '(rs, n :+ ls) ~ SplitAt ix d => Tensor d -> Dim ix -> KeepDim -> (Tensor (rs ++ ('[1] ++ ls)), Maybe (IndexTensor (rs ++ ('[1] ++ ls)))) Source #

Static call to min

max :: forall d n ix rs ls. All Dimensions '[d, rs ++ ('[1] ++ ls)] => All KnownNat '[n, ix] => All KnownDim '[n, ix] => (Length d > ix) ~ True => '(rs, n :+ ls) ~ SplitAt ix d => Tensor d -> Dim ix -> KeepDim -> (Tensor (rs ++ ('[1] ++ ls)), Maybe (IndexTensor (rs ++ ('[1] ++ ls)))) Source #

Static call to max

median :: forall d n ix rs ls. All Dimensions '[d, rs ++ ('[1] ++ ls)] => All KnownNat '[n, ix] => All KnownDim '[n, ix] => (Length d > ix) ~ True => '(rs, n :+ ls) ~ SplitAt ix d => Tensor d -> Dim ix -> KeepDim -> (Tensor (rs ++ ('[1] ++ ls)), Maybe (IndexTensor (rs ++ ('[1] ++ ls)))) Source #

Static call to median

minIndex1d :: (KnownNat n, KnownDim n) => Tensor (n ': ([] :: [Nat])) -> IndexTensor (1 ': ([] :: [Nat])) Source #

Convenience method for min

min1d :: (KnownNat n, KnownDim n) => Tensor '[n] -> KeepDim -> (Tensor '[1], Maybe (IndexTensor '[1])) Source #

Convenience method for min

maxIndex1d :: (KnownNat n, KnownDim n) => Tensor (n ': ([] :: [Nat])) -> IndexTensor (1 ': ([] :: [Nat])) Source #

Convenience method for max

max1d :: (KnownNat n, KnownDim n) => Tensor '[n] -> KeepDim -> (Tensor '[1], Maybe (IndexTensor '[1])) Source #

Convenience method for max over vectors

max2d0 :: (KnownDim m, KnownNat n, KnownDim n) => Tensor '[n, m] -> KeepDim -> (Tensor '[1, m], Maybe (IndexTensor '[1, m])) Source #

Convenience method for max over matricies

max2d1 :: (KnownDim n, KnownDim m, KnownNat m) => Tensor '[n, m] -> KeepDim -> (Tensor '[n, 1], Maybe (IndexTensor '[n, 1])) Source #

Convenience method for max over matricies

medianIndex1d :: (KnownNat n, KnownDim n) => Tensor (n ': ([] :: [Nat])) -> IndexTensor (1 ': ([] :: [Nat])) Source #

Convenience method for median

median1d :: (KnownNat n, KnownDim n) => Tensor '[n] -> KeepDim -> (Tensor '[1], Maybe (IndexTensor '[1])) Source #

Convenience method for median

sum :: Dimensions d' => Tensor d -> Word -> KeepDim -> Tensor d' Source #

Static call to sum

rowsum :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[1, c] Source #

convenience function for sum

colsum :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[r, 1] Source #

convenience function for sum

_prod :: Tensor d -> Tensor d -> Word -> Maybe KeepDim -> IO () Source #

Static call to _prod