hasktorch-0.2.1.3: Haskell bindings to libtorch, supporting both typed and untyped tensors.
Safe HaskellNone
LanguageHaskell2010

Torch.Typed

Synopsis

Documentation

module Torch.Data

newtype Parameter (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) Source #

Instances

Instances details
KnownDType dtype' => HasToDType (dtype' :: DType) (dtype :: DType) (Parameter device dtype shape) (Parameter device dtype' shape) Source # 
Instance details

Defined in Torch.Typed.DType

Methods

toDType :: Parameter device dtype shape -> Parameter device dtype' shape Source #

KnownDevice device' => HasToDevice device' device (Parameter device dtype shape) (Parameter device' dtype shape) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

toDevice :: Parameter device dtype shape -> Parameter device' dtype shape Source #

Apply' MakeIndependent (Tensor device dtype shape) (IO (Parameter device dtype shape)) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: MakeIndependent -> Tensor device dtype shape -> IO (Parameter device dtype shape) Source #

Apply' ToParameter (Tensor dev dtype shape) (Parameter dev dtype shape) Source # 
Instance details

Defined in Torch.Typed.Optim.CppOptim

Methods

apply' :: ToParameter -> Tensor dev dtype shape -> Parameter dev dtype shape Source #

Apply' ToDependent (Parameter device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: ToDependent -> Parameter device dtype shape -> Tensor device dtype shape Source #

Show (Parameter device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

showsPrec :: Int -> Parameter device dtype shape -> ShowS #

show :: Parameter device dtype shape -> String #

showList :: [Parameter device dtype shape] -> ShowS #

Parameterized (Parameter device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (Parameter device dtype shape) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Parameter device dtype shape) = '[Parameter device dtype shape]

Methods

flattenParameters :: Parameter device dtype shape -> HList (Parameters (Parameter device dtype shape)) Source #

replaceParameters :: Parameter device dtype shape -> HList (Parameters (Parameter device dtype shape)) -> Parameter device dtype shape Source #

HasGrad (Parameter device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Autograd

Methods

grad :: forall (dtype0 :: DType) (device0 :: (DeviceType, Nat)). Tensor device0 dtype0 ('[] :: [Nat]) -> Parameter device dtype shape -> Tensor device dtype shape Source #

toDependent :: Parameter device dtype shape -> Tensor device dtype shape

type Parameters (Parameter device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Parameter device dtype shape) = '[Parameter device dtype shape]

class Randomizable spec f | spec -> f where Source #

Methods

sample :: spec -> IO f Source #

Instances

Instances details
Randomizable BatchNormSpec BatchNorm Source # 
Instance details

Defined in Torch.NN

Randomizable Conv1dSpec Conv1d Source # 
Instance details

Defined in Torch.NN

Randomizable Conv2dSpec Conv2d Source # 
Instance details

Defined in Torch.NN

Randomizable Conv3dSpec Conv3d Source # 
Instance details

Defined in Torch.NN

Randomizable ConvTranspose1dSpec ConvTranspose1d Source # 
Instance details

Defined in Torch.NN

Randomizable ConvTranspose2dSpec ConvTranspose2d Source # 
Instance details

Defined in Torch.NN

Randomizable ConvTranspose3dSpec ConvTranspose3d Source # 
Instance details

Defined in Torch.NN

Randomizable InstanceNormSpec InstanceNorm Source # 
Instance details

Defined in Torch.NN

Randomizable LinearSpec Linear Source # 
Instance details

Defined in Torch.NN

Randomizable UpSampleSpec UpSample Source # 
Instance details

Defined in Torch.NN

Randomizable ElmanSpec ElmanCell Source # 
Instance details

Defined in Torch.NN.Recurrent.Cell.Elman

Randomizable GRUSpec GRUCell Source # 
Instance details

Defined in Torch.NN.Recurrent.Cell.GRU

Randomizable LSTMSpec LSTMCell Source # 
Instance details

Defined in Torch.NN.Recurrent.Cell.LSTM

Randomizable DropoutSpec Dropout Source # 
Instance details

Defined in Torch.Typed.NN.Dropout

(Randomizable xSpec x, Randomizable (HList xsSpec) (HList xs)) => Randomizable (HList (xSpec ': xsSpec)) (HList (x ': xs)) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

sample :: HList (xSpec ': xsSpec) -> IO (HList (x ': xs)) Source #

Randomizable (HList ('[] :: [Type])) (HList ('[] :: [Type])) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

sample :: HList ('[] :: [Type]) -> IO (HList ('[] :: [Type])) Source #

(TensorOptions normalizedShape dtype device, RandDTypeIsValid device dtype) => Randomizable (LayerNormSpec normalizedShape dtype device) (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Methods

sample :: LayerNormSpec normalizedShape dtype device -> IO (LayerNorm normalizedShape dtype device) Source #

(KnownNat inputFeatures, KnownNat outputFeatures, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (LinearSpec inputFeatures outputFeatures dtype device) (Linear inputFeatures outputFeatures dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Linear

Methods

sample :: LinearSpec inputFeatures outputFeatures dtype device -> IO (Linear inputFeatures outputFeatures dtype device) Source #

(KnownDevice device, KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim, RandDTypeIsValid device dtype) => Randomizable (GRUCellSpec inputDim hiddenDim dtype device) (GRUCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.GRU

Methods

sample :: GRUCellSpec inputDim hiddenDim dtype device -> IO (GRUCell inputDim hiddenDim dtype device) Source #

(KnownDevice device, KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim, RandDTypeIsValid device dtype) => Randomizable (LSTMCellSpec inputDim hiddenDim dtype device) (LSTMCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.LSTM

Methods

sample :: LSTMCellSpec inputDim hiddenDim dtype device -> IO (LSTMCell inputDim hiddenDim dtype device) Source #

(All KnownNat '[embedDim, ffnDim], KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (TransformerMLPSpec embedDim ffnDim dtype device) (TransformerMLP embedDim ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

sample :: TransformerMLPSpec embedDim ffnDim dtype device -> IO (TransformerMLP embedDim ffnDim dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device) (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> IO (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device) (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> IO (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source #

(RandDTypeIsValid device dtype, KnownNat inputSize, KnownNat hiddenSize, KnownDType dtype, KnownDevice device) => Randomizable (GRULayerSpec inputSize hiddenSize 'Bidirectional dtype device) (GRULayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRULayerSpec inputSize hiddenSize 'Bidirectional dtype device -> IO (GRULayer inputSize hiddenSize 'Bidirectional dtype device) Source #

(RandDTypeIsValid device dtype, KnownNat inputSize, KnownNat hiddenSize, KnownDType dtype, KnownDevice device) => Randomizable (GRULayerSpec inputSize hiddenSize 'Unidirectional dtype device) (GRULayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRULayerSpec inputSize hiddenSize 'Unidirectional dtype device -> IO (GRULayer inputSize hiddenSize 'Unidirectional dtype device) Source #

(RandDTypeIsValid device dtype, KnownNat inputSize, KnownNat hiddenSize, KnownDType dtype, KnownDevice device) => Randomizable (LSTMLayerSpec inputSize hiddenSize 'Bidirectional dtype device) (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMLayerSpec inputSize hiddenSize 'Bidirectional dtype device -> IO (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) Source #

(RandDTypeIsValid device dtype, KnownNat inputSize, KnownNat hiddenSize, KnownDType dtype, KnownDevice device) => Randomizable (LSTMLayerSpec inputSize hiddenSize 'Unidirectional dtype device) (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMLayerSpec inputSize hiddenSize 'Unidirectional dtype device -> IO (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> IO (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> IO (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source #

(1 <= numLayers, (2 <=? numLayers) ~ flag, RandDTypeIsValid device dtype, KnownDType dtype, KnownDevice device, GRULayerStackRandomizable flag inputSize hiddenSize numLayers directionality dtype device) => Randomizable (GRULayerStackSpec inputSize hiddenSize numLayers directionality dtype device) (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRULayerStackSpec inputSize hiddenSize numLayers directionality dtype device -> IO (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) Source #

(KnownDType dtype, KnownDevice device, KnownNat inputSize, KnownNat hiddenSize, KnownNat (NumberOfDirections directionality), RandDTypeIsValid device dtype, Randomizable (GRULayerStackSpec inputSize hiddenSize numLayers directionality dtype device) (GRULayerStack inputSize hiddenSize numLayers directionality dtype device), 1 <= numLayers) => Randomizable (GRUSpec inputSize hiddenSize numLayers directionality dtype device) (GRU inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRUSpec inputSize hiddenSize numLayers directionality dtype device -> IO (GRU inputSize hiddenSize numLayers directionality dtype device) Source #

(1 <= numLayers, (2 <=? numLayers) ~ flag, RandDTypeIsValid device dtype, KnownDType dtype, KnownDevice device, LSTMLayerStackRandomizable flag inputSize hiddenSize numLayers directionality dtype device) => Randomizable (LSTMLayerStackSpec inputSize hiddenSize numLayers directionality dtype device) (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMLayerStackSpec inputSize hiddenSize numLayers directionality dtype device -> IO (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) Source #

(KnownDType dtype, KnownDevice device, KnownNat inputSize, KnownNat hiddenSize, KnownNat (NumberOfDirections directionality), RandDTypeIsValid device dtype, Randomizable (LSTMLayerStackSpec inputSize hiddenSize numLayers directionality dtype device) (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device), 1 <= numLayers) => Randomizable (LSTMSpec inputSize hiddenSize numLayers directionality dtype device) (LSTM inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMSpec inputSize hiddenSize numLayers directionality dtype device -> IO (LSTM inputSize hiddenSize numLayers directionality dtype device) Source #

(paddingIdx <= numEmbeds, 1 <= (numEmbeds - paddingIdx), (((numEmbeds - paddingIdx) - 1) + (1 + paddingIdx)) ~ numEmbeds, KnownNat paddingIdx, KnownNat numEmbeds, KnownNat embedSize, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (EmbeddingSpec ('Just paddingIdx) numEmbeds embedSize 'Learned dtype device) (Embedding ('Just paddingIdx) numEmbeds embedSize 'Learned dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

sample :: EmbeddingSpec ('Just paddingIdx) numEmbeds embedSize 'Learned dtype device -> IO (Embedding ('Just paddingIdx) numEmbeds embedSize 'Learned dtype device) Source #

(KnownNat numEmbeds, KnownNat embedSize, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (EmbeddingSpec ('Nothing :: Maybe Nat) numEmbeds embedSize 'Learned dtype device) (Embedding ('Nothing :: Maybe Nat) numEmbeds embedSize 'Learned dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

sample :: EmbeddingSpec ('Nothing :: Maybe Nat) numEmbeds embedSize 'Learned dtype device -> IO (Embedding ('Nothing :: Maybe Nat) numEmbeds embedSize 'Learned dtype device) Source #

Randomizable (EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device) (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

sample :: EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device -> IO (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source #

(All KnownNat '[embedDim, kEmbedDim, vEmbedDim, numHeads], KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (MultiheadAttentionSpec embedDim kEmbedDim vEmbedDim numHeads dtype device) (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

sample :: MultiheadAttentionSpec embedDim kEmbedDim vEmbedDim numHeads dtype device -> IO (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat kernelSize2, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> IO (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source #

(KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat kernelSize2, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

sample :: ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> IO (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source #

(KnownNat hiddenSize, KnownNat numLayers, KnownNat (NumberOfDirections directionality), KnownDType dtype, KnownDevice device, Randomizable (GRUSpec inputSize hiddenSize numLayers directionality dtype device) (GRU inputSize hiddenSize numLayers directionality dtype device)) => Randomizable (GRUWithInitSpec inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRUWithInitSpec inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> IO (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source #

(KnownNat hiddenSize, KnownNat numLayers, KnownNat (NumberOfDirections directionality), KnownDType dtype, KnownDevice device, Randomizable (GRUSpec inputSize hiddenSize numLayers directionality dtype device) (GRU inputSize hiddenSize numLayers directionality dtype device)) => Randomizable (GRUWithInitSpec inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Methods

sample :: GRUWithInitSpec inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> IO (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source #

(KnownNat hiddenSize, KnownNat numLayers, KnownNat (NumberOfDirections directionality), KnownDType dtype, KnownDevice device, Randomizable (LSTMSpec inputSize hiddenSize numLayers directionality dtype device) (LSTM inputSize hiddenSize numLayers directionality dtype device)) => Randomizable (LSTMWithInitSpec inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMWithInitSpec inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> IO (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source #

(KnownNat hiddenSize, KnownNat numLayers, KnownNat (NumberOfDirections directionality), KnownDType dtype, KnownDevice device, Randomizable (LSTMSpec inputSize hiddenSize numLayers directionality dtype device) (LSTM inputSize hiddenSize numLayers directionality dtype device)) => Randomizable (LSTMWithInitSpec inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Methods

sample :: LSTMWithInitSpec inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> IO (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source #

(All KnownNat '[embedDim, kEmbedDim, vEmbedDim, numHeads, ffnDim], KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (TransformerLayerSpec embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

sample :: TransformerLayerSpec embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device -> IO (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) Source #

(paddingIdx <= numEmbeds, 1 <= (numEmbeds - paddingIdx), 1 <= Div embedDim 2, (((numEmbeds - paddingIdx) - 1) + (1 + paddingIdx)) ~ numEmbeds, (Div embedDim 2 * 2) ~ embedDim, All KnownNat '[ffnDim, paddingIdx, numEmbeds, embedDim], HReplicate numAttnLayers (TransformerLayerSpec embedDim embedDim embedDim numHeads ffnDim dtype device), Randomizable (HList (HReplicateR numAttnLayers (TransformerLayerSpec embedDim embedDim embedDim numHeads ffnDim dtype device))) (HList (HReplicateR numAttnLayers (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device))), KnownDType dtype, RandDTypeIsValid device dtype, StandardFloatingPointDTypeValidation device 'Float, BasicArithmeticDTypeIsValid device 'Float, KnownDevice device) => Randomizable (TransformerLMSpec numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

sample :: TransformerLMSpec numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device -> IO (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) Source #

makeIndependent :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). Tensor device dtype shape -> IO (Parameter device dtype shape) Source #

toDependent :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). Parameter device dtype shape -> Tensor device dtype shape Source #

class Parameterized f where Source #

Minimal complete definition

Nothing

Associated Types

type Parameters f :: [Type] Source #

Instances

Instances details
Parameterized Dropout Source # 
Instance details

Defined in Torch.Typed.NN.Dropout

Associated Types

type Parameters Dropout 
Instance details

Defined in Torch.Typed.NN.Dropout

Parameterized GD Source # 
Instance details

Defined in Torch.Typed.Optim

Associated Types

type Parameters GD 
Instance details

Defined in Torch.Typed.Optim

type Parameters GD = '[] :: [Type]
Parameterized Double Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters Double 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Double = '[] :: [Type]
Parameterized Float Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters Float 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Float = '[] :: [Type]
Parameterized Int Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters Int 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Int = '[] :: [Type]
HAppendFD momenta momenta (momenta ++ momenta) => Parameterized (Adam momenta) Source # 
Instance details

Defined in Torch.Typed.Optim

Associated Types

type Parameters (Adam momenta) 
Instance details

Defined in Torch.Typed.Optim

type Parameters (Adam momenta) = AdamIter ': (momenta ++ momenta)

Methods

flattenParameters :: Adam momenta -> HList (Parameters (Adam momenta)) Source #

replaceParameters :: Adam momenta -> HList (Parameters (Adam momenta)) -> Adam momenta Source #

Parameterized (GDM momenta) Source # 
Instance details

Defined in Torch.Typed.Optim

Associated Types

type Parameters (GDM momenta) 
Instance details

Defined in Torch.Typed.Optim

type Parameters (GDM momenta) = momenta

Methods

flattenParameters :: GDM momenta -> HList (Parameters (GDM momenta)) Source #

replaceParameters :: GDM momenta -> HList (Parameters (GDM momenta)) -> GDM momenta Source #

(Parameterized f, Parameterized (HList fs), HAppendFD (Parameters f) (Parameters (HList fs)) (Parameters f ++ Parameters (HList fs))) => Parameterized (HList (f ': fs)) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (HList (f ': fs)) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (HList (f ': fs)) = Parameters f ++ Parameters (HList fs)

Methods

flattenParameters :: HList (f ': fs) -> HList (Parameters (HList (f ': fs))) Source #

replaceParameters :: HList (f ': fs) -> HList (Parameters (HList (f ': fs))) -> HList (f ': fs) Source #

Parameterized (HList ('[] :: [k])) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (HList ('[] :: [k])) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (HList ('[] :: [k])) = '[] :: [Type]

Methods

flattenParameters :: HList ('[] :: [k]) -> HList (Parameters (HList ('[] :: [k]))) Source #

replaceParameters :: HList ('[] :: [k]) -> HList (Parameters (HList ('[] :: [k]))) -> HList ('[] :: [k]) Source #

Parameterized (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Associated Types

type Parameters (LayerNorm normalizedShape dtype device) 
Instance details

Defined in Torch.Typed.NN.Normalization

type Parameters (LayerNorm normalizedShape dtype device) = GParameters (Rep (LayerNorm normalizedShape dtype device))

Methods

flattenParameters :: LayerNorm normalizedShape dtype device -> HList (Parameters (LayerNorm normalizedShape dtype device)) Source #

replaceParameters :: LayerNorm normalizedShape dtype device -> HList (Parameters (LayerNorm normalizedShape dtype device)) -> LayerNorm normalizedShape dtype device Source #

Parameterized (Parameter device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (Parameter device dtype shape) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Parameter device dtype shape) = '[Parameter device dtype shape]

Methods

flattenParameters :: Parameter device dtype shape -> HList (Parameters (Parameter device dtype shape)) Source #

replaceParameters :: Parameter device dtype shape -> HList (Parameters (Parameter device dtype shape)) -> Parameter device dtype shape Source #

Parameterized (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Tensor device dtype shape) = '[] :: [Type]

Methods

flattenParameters :: Tensor device dtype shape -> HList (Parameters (Tensor device dtype shape)) Source #

replaceParameters :: Tensor device dtype shape -> HList (Parameters (Tensor device dtype shape)) -> Tensor device dtype shape Source #

Parameterized (Linear inputFeatures outputFeatures dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Linear

Associated Types

type Parameters (Linear inputFeatures outputFeatures dtype device) 
Instance details

Defined in Torch.Typed.NN.Linear

type Parameters (Linear inputFeatures outputFeatures dtype device) = GParameters (Rep (Linear inputFeatures outputFeatures dtype device))

Methods

flattenParameters :: Linear inputFeatures outputFeatures dtype device -> HList (Parameters (Linear inputFeatures outputFeatures dtype device)) Source #

replaceParameters :: Linear inputFeatures outputFeatures dtype device -> HList (Parameters (Linear inputFeatures outputFeatures dtype device)) -> Linear inputFeatures outputFeatures dtype device Source #

Parameterized (GRUCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.GRU

Associated Types

type Parameters (GRUCell inputDim hiddenDim dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.GRU

type Parameters (GRUCell inputDim hiddenDim dtype device) = GParameters (Rep (GRUCell inputDim hiddenDim dtype device))

Methods

flattenParameters :: GRUCell inputDim hiddenDim dtype device -> HList (Parameters (GRUCell inputDim hiddenDim dtype device)) Source #

replaceParameters :: GRUCell inputDim hiddenDim dtype device -> HList (Parameters (GRUCell inputDim hiddenDim dtype device)) -> GRUCell inputDim hiddenDim dtype device Source #

Parameterized (LSTMCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.LSTM

Associated Types

type Parameters (LSTMCell inputDim hiddenDim dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.LSTM

type Parameters (LSTMCell inputDim hiddenDim dtype device) = GParameters (Rep (LSTMCell inputDim hiddenDim dtype device))

Methods

flattenParameters :: LSTMCell inputDim hiddenDim dtype device -> HList (Parameters (LSTMCell inputDim hiddenDim dtype device)) Source #

replaceParameters :: LSTMCell inputDim hiddenDim dtype device -> HList (Parameters (LSTMCell inputDim hiddenDim dtype device)) -> LSTMCell inputDim hiddenDim dtype device Source #

Parameterized (TransformerMLP embedDim ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Associated Types

type Parameters (TransformerMLP embedDim ffnDim dtype device) 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerMLP embedDim ffnDim dtype device) = GParameters (Rep (TransformerMLP embedDim ffnDim dtype device))

Methods

flattenParameters :: TransformerMLP embedDim ffnDim dtype device -> HList (Parameters (TransformerMLP embedDim ffnDim dtype device)) Source #

replaceParameters :: TransformerMLP embedDim ffnDim dtype device -> HList (Parameters (TransformerMLP embedDim ffnDim dtype device)) -> TransformerMLP embedDim ffnDim dtype device Source #

Parameterized (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device))

Methods

flattenParameters :: Conv1d inputChannelSize outputChannelSize kernelSize dtype device -> HList (Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device)) Source #

replaceParameters :: Conv1d inputChannelSize outputChannelSize kernelSize dtype device -> HList (Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device)) -> Conv1d inputChannelSize outputChannelSize kernelSize dtype device Source #

Parameterized (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device))

Methods

flattenParameters :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> HList (Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device)) Source #

replaceParameters :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> HList (Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device)) -> ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device Source #

Parameterized (GRULayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device) = '[Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize), Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize)]

Methods

flattenParameters :: GRULayer inputSize hiddenSize 'Bidirectional dtype device -> HList (Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device)) Source #

replaceParameters :: GRULayer inputSize hiddenSize 'Bidirectional dtype device -> HList (Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device)) -> GRULayer inputSize hiddenSize 'Bidirectional dtype device Source #

Parameterized (GRULayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device) = '[Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize)]

Methods

flattenParameters :: GRULayer inputSize hiddenSize 'Unidirectional dtype device -> HList (Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device)) Source #

replaceParameters :: GRULayer inputSize hiddenSize 'Unidirectional dtype device -> HList (Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device)) -> GRULayer inputSize hiddenSize 'Unidirectional dtype device Source #

Parameterized (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) = '[Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize), Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize)]

Methods

flattenParameters :: LSTMLayer inputSize hiddenSize 'Bidirectional dtype device -> HList (Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device)) Source #

replaceParameters :: LSTMLayer inputSize hiddenSize 'Bidirectional dtype device -> HList (Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device)) -> LSTMLayer inputSize hiddenSize 'Bidirectional dtype device Source #

Parameterized (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) = '[Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize)]

Methods

flattenParameters :: LSTMLayer inputSize hiddenSize 'Unidirectional dtype device -> HList (Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device)) Source #

replaceParameters :: LSTMLayer inputSize hiddenSize 'Unidirectional dtype device -> HList (Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device)) -> LSTMLayer inputSize hiddenSize 'Unidirectional dtype device Source #

Parameterized (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device))

Methods

flattenParameters :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> HList (Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) Source #

replaceParameters :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> HList (Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) -> Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device Source #

Parameterized (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device))

Methods

flattenParameters :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> HList (Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) Source #

replaceParameters :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> HList (Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) -> ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device Source #

(1 <= numLayers, Parameterized (GRULayerStack inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device)) (Parameters Dropout) (Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) ++ Parameters Dropout)) => Parameterized (GRU inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) = GParameters (Rep (GRU inputSize hiddenSize numLayers directionality dtype device))

Methods

flattenParameters :: GRU inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device)) Source #

replaceParameters :: GRU inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device)) -> GRU inputSize hiddenSize numLayers directionality dtype device Source #

(1 <= numLayers, (2 <=? numLayers) ~ flag, GRULayerStackParameterized flag inputSize hiddenSize numLayers directionality dtype device) => Parameterized (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) = GRULayerStackParameters (2 <=? numLayers) inputSize hiddenSize numLayers directionality dtype device

Methods

flattenParameters :: GRULayerStack inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device)) Source #

replaceParameters :: GRULayerStack inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device)) -> GRULayerStack inputSize hiddenSize numLayers directionality dtype device Source #

(1 <= numLayers, Parameterized (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device)) (Parameters Dropout) (Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) ++ Parameters Dropout)) => Parameterized (LSTM inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) = GParameters (Rep (LSTM inputSize hiddenSize numLayers directionality dtype device))

Methods

flattenParameters :: LSTM inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device)) Source #

replaceParameters :: LSTM inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device)) -> LSTM inputSize hiddenSize numLayers directionality dtype device Source #

(1 <= numLayers, (2 <=? numLayers) ~ flag, LSTMLayerStackParameterized flag inputSize hiddenSize numLayers directionality dtype device) => Parameterized (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) = LSTMLayerStackParameters (2 <=? numLayers) inputSize hiddenSize numLayers directionality dtype device

Methods

flattenParameters :: LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device)) Source #

replaceParameters :: LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device -> HList (Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device)) -> LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device Source #

Parameterized (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Associated Types

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) 
Instance details

Defined in Torch.Typed.NN.Sparse

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) = GParameters (Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device))

Methods

flattenParameters :: Embedding paddingIdx numEmbeds embedSize 'Constant dtype device -> HList (Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device)) Source #

replaceParameters :: Embedding paddingIdx numEmbeds embedSize 'Constant dtype device -> HList (Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device)) -> Embedding paddingIdx numEmbeds embedSize 'Constant dtype device Source #

Parameterized (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Associated Types

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) 
Instance details

Defined in Torch.Typed.NN.Sparse

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) = GParameters (Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device))

Methods

flattenParameters :: Embedding paddingIdx numEmbeds embedSize 'Learned dtype device -> HList (Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device)) Source #

replaceParameters :: Embedding paddingIdx numEmbeds embedSize 'Learned dtype device -> HList (Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device)) -> Embedding paddingIdx numEmbeds embedSize 'Learned dtype device Source #

Parameterized (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Associated Types

type Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) = GParameters (Rep (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device))

Methods

flattenParameters :: MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device -> HList (Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device)) Source #

replaceParameters :: MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device -> HList (Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device)) -> MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device Source #

Parameterized (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = GParameters (Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device))

Methods

flattenParameters :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> HList (Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device)) Source #

replaceParameters :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> HList (Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device)) -> Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device Source #

Parameterized (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Associated Types

type Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = GParameters (Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device))

Methods

flattenParameters :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> HList (Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device)) Source #

replaceParameters :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> HList (Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device)) -> ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device Source #

(Parameterized (GRU inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device)) ('[] :: [Type]) (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) ++ ('[] :: [Type]))) => Parameterized (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) = GParameters (Rep (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device))

Methods

flattenParameters :: GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> HList (Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device)) Source #

replaceParameters :: GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> HList (Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device)) -> GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device Source #

(Parameterized (GRU inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device)) '[Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize]] (Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) ++ '[Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize]])) => Parameterized (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

Associated Types

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) = GParameters (Rep (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device))

Methods

flattenParameters :: GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> HList (Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device)) Source #

replaceParameters :: GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> HList (Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device)) -> GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device Source #

(Parameterized (LSTM inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device)) ('[] :: [Type]) (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) ++ ('[] :: [Type]))) => Parameterized (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) = GParameters (Rep (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device))

Methods

flattenParameters :: LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> HList (Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device)) Source #

replaceParameters :: LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device -> HList (Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device)) -> LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device Source #

(Parameterized (LSTM inputSize hiddenSize numLayers directionality dtype device), HAppendFD (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device)) '[Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize], Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize]] (Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) ++ '[Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize], Parameter device dtype '[numLayers * NumberOfDirections directionality, hiddenSize]])) => Parameterized (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

Associated Types

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) = GParameters (Rep (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device))

Methods

flattenParameters :: LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> HList (Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device)) Source #

replaceParameters :: LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device -> HList (Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device)) -> LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device Source #

Parameterized (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Associated Types

type Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) = GParameters (Rep (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device))

Methods

flattenParameters :: TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device -> HList (Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device)) Source #

replaceParameters :: TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device -> HList (Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device)) -> TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device Source #

(layers ~ HReplicateR numAttnLayers (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device), Parameterized (HList layers), HAppendFD (Parameters (HList layers)) '[Parameter device dtype '[numEmbeds, embedDim], Parameter device dtype '[numEmbeds]] (Parameters (HList layers) ++ '[Parameter device dtype '[numEmbeds, embedDim], Parameter device dtype '[numEmbeds]])) => Parameterized (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Associated Types

type Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) = GParameters (Rep (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device))

Methods

flattenParameters :: TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device -> HList (Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device)) Source #

replaceParameters :: TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device -> HList (Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device)) -> TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device Source #

class GParameterized (f :: Type -> Type) where Source #

Associated Types

type GParameters (f :: Type -> Type) :: [Type] Source #

Instances

Instances details
GParameterized (U1 :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type GParameters (U1 :: Type -> Type) 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (U1 :: Type -> Type) = '[] :: [Type]
(GParameterized l, GParameterized r, HAppendFD (GParameters l) (GParameters r) (GParameters l ++ GParameters r)) => GParameterized (l :*: r) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type GParameters (l :*: r) 
Instance details

Defined in Torch.Typed.Parameter

Methods

gFlattenParameters :: (l :*: r) a -> HList (GParameters (l :*: r)) Source #

gReplaceParameters :: (l :*: r) a -> HList (GParameters (l :*: r)) -> (l :*: r) a Source #

Parameterized f => GParameterized (K1 i f :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type GParameters (K1 i f :: Type -> Type) 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (K1 i f :: Type -> Type) = Parameters f

Methods

gFlattenParameters :: K1 i f a -> HList (GParameters (K1 i f :: Type -> Type)) Source #

gReplaceParameters :: K1 i f a -> HList (GParameters (K1 i f :: Type -> Type)) -> K1 i f a Source #

GParameterized f => GParameterized (M1 i t f) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type GParameters (M1 i t f) 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (M1 i t f) = GParameters f

Methods

gFlattenParameters :: M1 i t f a -> HList (GParameters (M1 i t f)) Source #

gReplaceParameters :: M1 i t f a -> HList (GParameters (M1 i t f)) -> M1 i t f a Source #

untypeParam :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). Parameter device dtype shape -> Parameter Source #

data ToDependent Source #

Constructors

ToDependent 

Instances

Instances details
Apply' ToDependent (Parameter device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: ToDependent -> Parameter device dtype shape -> Tensor device dtype shape Source #

data MakeIndependent Source #

Constructors

MakeIndependent 

Instances

Instances details
Apply' MakeIndependent (Tensor device dtype shape) (IO (Parameter device dtype shape)) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: MakeIndependent -> Tensor device dtype shape -> IO (Parameter device dtype shape) Source #

type family Parameters f :: [Type] Source #

Instances

Instances details
type Parameters Dropout Source # 
Instance details

Defined in Torch.Typed.NN.Dropout

type Parameters GD Source # 
Instance details

Defined in Torch.Typed.Optim

type Parameters GD = '[] :: [Type]
type Parameters Double Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Double = '[] :: [Type]
type Parameters Float Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Float = '[] :: [Type]
type Parameters Int Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters Int = '[] :: [Type]
type Parameters (Adam momenta) Source # 
Instance details

Defined in Torch.Typed.Optim

type Parameters (Adam momenta) = AdamIter ': (momenta ++ momenta)
type Parameters (GDM momenta) Source # 
Instance details

Defined in Torch.Typed.Optim

type Parameters (GDM momenta) = momenta
type Parameters (HList (f ': fs)) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (HList (f ': fs)) = Parameters f ++ Parameters (HList fs)
type Parameters (HList ('[] :: [k])) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (HList ('[] :: [k])) = '[] :: [Type]
type Parameters (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

type Parameters (LayerNorm normalizedShape dtype device) = GParameters (Rep (LayerNorm normalizedShape dtype device))
type Parameters (Parameter device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Parameter device dtype shape) = '[Parameter device dtype shape]
type Parameters (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Tensor device dtype shape) = '[] :: [Type]
type Parameters (Linear inputFeatures outputFeatures dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Linear

type Parameters (Linear inputFeatures outputFeatures dtype device) = GParameters (Rep (Linear inputFeatures outputFeatures dtype device))
type Parameters (GRUCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.GRU

type Parameters (GRUCell inputDim hiddenDim dtype device) = GParameters (Rep (GRUCell inputDim hiddenDim dtype device))
type Parameters (LSTMCell inputDim hiddenDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.Cell.LSTM

type Parameters (LSTMCell inputDim hiddenDim dtype device) = GParameters (Rep (LSTMCell inputDim hiddenDim dtype device))
type Parameters (TransformerMLP embedDim ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerMLP embedDim ffnDim dtype device) = GParameters (Rep (TransformerMLP embedDim ffnDim dtype device))
type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device))
type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device))
type Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayer inputSize hiddenSize 'Bidirectional dtype device) = '[Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize), Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize)]
type Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayer inputSize hiddenSize 'Unidirectional dtype device) = '[Parameter device dtype (GRUWIShape hiddenSize inputSize), Parameter device dtype (GRUWHShape hiddenSize inputSize), Parameter device dtype (GRUBIShape hiddenSize inputSize), Parameter device dtype (GRUBHShape hiddenSize inputSize)]
type Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayer inputSize hiddenSize 'Bidirectional dtype device) = '[Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize), Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize)]
type Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayer inputSize hiddenSize 'Unidirectional dtype device) = '[Parameter device dtype (LSTMWIShape hiddenSize inputSize), Parameter device dtype (LSTMWHShape hiddenSize inputSize), Parameter device dtype (LSTMBIShape hiddenSize inputSize), Parameter device dtype (LSTMBHShape hiddenSize inputSize)]
type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device))
type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device))
type Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRU inputSize hiddenSize numLayers directionality dtype device) = GParameters (Rep (GRU inputSize hiddenSize numLayers directionality dtype device))
type Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRULayerStack inputSize hiddenSize numLayers directionality dtype device) = GRULayerStackParameters (2 <=? numLayers) inputSize hiddenSize numLayers directionality dtype device
type Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTM inputSize hiddenSize numLayers directionality dtype device) = GParameters (Rep (LSTM inputSize hiddenSize numLayers directionality dtype device))
type Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMLayerStack inputSize hiddenSize numLayers directionality dtype device) = LSTMLayerStackParameters (2 <=? numLayers) inputSize hiddenSize numLayers directionality dtype device
type Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) = GParameters (Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device))
type Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

type Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) = GParameters (Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device))
type Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device) = GParameters (Rep (MultiheadAttention embedDim kEmbedDim vEmbedDim numHeads dtype device))
type Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = GParameters (Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device))
type Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

type Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = GParameters (Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device))
type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) = GParameters (Rep (GRUWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device))
type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.GRU

type Parameters (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) = GParameters (Rep (GRUWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device))
type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device) = GParameters (Rep (LSTMWithInit inputSize hiddenSize numLayers directionality 'ConstantInitialization dtype device))
type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Recurrent.LSTM

type Parameters (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device) = GParameters (Rep (LSTMWithInit inputSize hiddenSize numLayers directionality 'LearnedInitialization dtype device))
type Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device) = GParameters (Rep (TransformerLayer embedDim kEmbedDim vEmbedDim numHeads ffnDim dtype device))
type Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

type Parameters (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) = GParameters (Rep (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device))

type family GParameters (f :: Type -> Type) :: [Type] Source #

Instances

Instances details
type GParameters (U1 :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (U1 :: Type -> Type) = '[] :: [Type]
type GParameters (l :*: r) Source # 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (K1 i f :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (K1 i f :: Type -> Type) = Parameters f
type GParameters (M1 i t f) Source # 
Instance details

Defined in Torch.Typed.Parameter

type GParameters (M1 i t f) = GParameters f

div :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (dtype'' :: DType) (device :: (DeviceType, Nat)). (dtype'' ~ DTypePromotion dtype dtype', shape'' ~ Broadcast shape shape', BasicArithmeticDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype', BasicArithmeticDTypeIsValid device dtype'') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device dtype'' shape'' Source #

type family All (pred :: a -> Constraint) (l :: [a]) where ... Source #

Equations

All (_1 :: a -> Constraint) ('[] :: [a]) = () 
All (pred :: a -> Constraint) (h ': t :: [a]) = (pred h, All pred t) 

toBool :: forall (device :: (DeviceType, Nat)). Tensor device 'Bool ('[] :: [Nat]) -> Bool Source #

type Size = Type -> Type Source #

eq :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

add :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (dtype'' :: DType) (device :: (DeviceType, Nat)). (dtype'' ~ DTypePromotion dtype dtype', shape'' ~ Broadcast shape shape', BasicArithmeticDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype', BasicArithmeticDTypeIsValid device dtype'') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device dtype'' shape'' Source #

sub :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (dtype'' :: DType) (device :: (DeviceType, Nat)). (dtype'' ~ DTypePromotion dtype dtype', shape'' ~ Broadcast shape shape', BasicArithmeticDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype', BasicArithmeticDTypeIsValid device dtype'') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device dtype'' shape'' Source #

select :: forall (dim :: Nat) (idx :: Nat) (shape' :: [Nat]) (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (KnownNat dim, KnownNat idx, InRange shape dim idx, shape' ~ Remove shape dim) => Tensor device dtype shape -> Tensor device dtype shape' Source #

(<.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

mul :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (dtype'' :: DType) (device :: (DeviceType, Nat)). (dtype'' ~ DTypePromotion dtype dtype', shape'' ~ Broadcast shape shape', BasicArithmeticDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype', BasicArithmeticDTypeIsValid device dtype'') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device dtype'' shape'' Source #

data Tensor (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) where Source #

Constructors

UnsafeMkTensor :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). Tensor -> Tensor device dtype shape 

Instances

Instances details
KnownDType dtype' => HasToDType (dtype' :: DType) (dtype :: DType) (Tensor device dtype shape) (Tensor device dtype' shape) Source # 
Instance details

Defined in Torch.Typed.DType

Methods

toDType :: Tensor device dtype shape -> Tensor device dtype' shape Source #

(KnownNat batchSize, KnownDevice device, Applicative m) => Dataset (m :: Type -> Type) (MNIST m device batchSize) Int ((Tensor device 'Float '[batchSize, 784], Tensor device 'Int64 '[batchSize]) :: Type) Source # 
Instance details

Defined in Torch.Typed.Vision

Methods

getItem :: MNIST m device batchSize -> Int -> m (Tensor device 'Float '[batchSize, 784], Tensor device 'Int64 '[batchSize]) Source #

keys :: MNIST m device batchSize -> Set Int Source #

KnownDevice device' => HasToDevice device' device (Tensor device dtype shape) (Tensor device' dtype shape) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

toDevice :: Tensor device dtype shape -> Tensor device' dtype shape Source #

(HasGrad (HList parameters) (HList gradients), Castable (HList gradients) [ATenTensor]) => Apply' GradConcurrentlyF (HList parameters, Loss device dtype) (Concurrently (HList gradients)) Source # 
Instance details

Defined in Torch.Typed.NN.DataParallel

Methods

apply' :: GradConcurrentlyF -> (HList parameters, Loss device dtype) -> Concurrently (HList gradients) Source #

Apply' MakeIndependent (Tensor device dtype shape) (IO (Parameter device dtype shape)) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: MakeIndependent -> Tensor device dtype shape -> IO (Parameter device dtype shape) Source #

Apply' ToParameter (Tensor dev dtype shape) (Parameter dev dtype shape) Source # 
Instance details

Defined in Torch.Typed.Optim.CppOptim

Methods

apply' :: ToParameter -> Tensor dev dtype shape -> Parameter dev dtype shape Source #

Apply' ToDependent (Parameter device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Methods

apply' :: ToDependent -> Parameter device dtype shape -> Tensor device dtype shape Source #

HasForward Dropout (Tensor device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.NN.Dropout

Methods

forward :: Dropout -> Tensor device dtype shape -> Tensor device dtype shape Source #

forwardStoch :: Dropout -> Tensor device dtype shape -> IO (Tensor device dtype shape) Source #

(TensorLike [ComputeItemType (ComputeHaskellType dtype) shape], KnownDevice device, KnownShape shape) => IsList (Maybe (Tensor device dtype shape)) Source # 
Instance details

Defined in Torch.Typed.Tensor

Associated Types

type Item (Maybe (Tensor device dtype shape)) 
Instance details

Defined in Torch.Typed.Tensor

type Item (Maybe (Tensor device dtype shape)) = ComputeItemType (ComputeHaskellType dtype) shape

Methods

fromList :: [Item (Maybe (Tensor device dtype shape))] -> Maybe (Tensor device dtype shape) #

fromListN :: Int -> [Item (Maybe (Tensor device dtype shape))] -> Maybe (Tensor device dtype shape) #

toList :: Maybe (Tensor device dtype shape) -> [Item (Maybe (Tensor device dtype shape))] #

Castable [Tensor device dtype shape] (ForeignPtr TensorList) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

cast :: [Tensor device dtype shape] -> (ForeignPtr TensorList -> IO r) -> IO r

uncast :: ForeignPtr TensorList -> ([Tensor device dtype shape] -> IO r) -> IO r

(chunks ~ ListLength devices', tensorChunks ~ (Chunk chunks 0 shape dtype device :: [Type]), Castable (HList tensorChunks) [ATenTensor], devices ~ HReplicateR chunks device, HasToDevices devices' devices tensorChunks gs, KnownNat chunks) => HasScatter (devices' :: [(DeviceType, Nat)]) (device :: (DeviceType, Nat)) (Tensor device dtype shape) (gs :: [Type]) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

scatter :: Tensor device dtype shape -> HList gs Source #

KnownNat n => Castable (Vector n (Tensor device dtype shape)) (ForeignPtr TensorList) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

cast :: Vector n (Tensor device dtype shape) -> (ForeignPtr TensorList -> IO r) -> IO r

uncast :: ForeignPtr TensorList -> (Vector n (Tensor device dtype shape) -> IO r) -> IO r

(chunks ~ ListLength fs, devices ~ GetDevices fs, devices' ~ HReplicateR chunks device', HasToDevices devices' devices fs tensorChunks, '(shape, dtype, device') ~ Cat 0 tensorChunks, Castable (HList tensorChunks) [ATenTensor]) => HasGather (device' :: (DeviceType, Nat)) (devices :: [(DeviceType, Nat)]) (fs :: [Type]) (Tensor device' dtype shape) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

gather :: HList fs -> Tensor device' dtype shape Source #

TensorOptions shape dtype device => Default (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Factories

Methods

def :: Tensor device dtype shape #

KnownDevice device => Num (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

(+) :: Tensor device dtype shape -> Tensor device dtype shape -> Tensor device dtype shape #

(-) :: Tensor device dtype shape -> Tensor device dtype shape -> Tensor device dtype shape #

(*) :: Tensor device dtype shape -> Tensor device dtype shape -> Tensor device dtype shape #

negate :: Tensor device dtype shape -> Tensor device dtype shape #

abs :: Tensor device dtype shape -> Tensor device dtype shape #

signum :: Tensor device dtype shape -> Tensor device dtype shape #

fromInteger :: Integer -> Tensor device dtype shape #

KnownDevice device => Fractional (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

(/) :: Tensor device dtype shape -> Tensor device dtype shape -> Tensor device dtype shape #

recip :: Tensor device dtype shape -> Tensor device dtype shape #

fromRational :: Rational -> Tensor device dtype shape #

Show (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

showsPrec :: Int -> Tensor device dtype shape -> ShowS #

show :: Tensor device dtype shape -> String #

showList :: [Tensor device dtype shape] -> ShowS #

Parameterized (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

Associated Types

type Parameters (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Tensor device dtype shape) = '[] :: [Type]

Methods

flattenParameters :: Tensor device dtype shape -> HList (Parameters (Tensor device dtype shape)) Source #

replaceParameters :: Tensor device dtype shape -> HList (Parameters (Tensor device dtype shape)) -> Tensor device dtype shape Source #

Unnamed (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Associated Types

type UTShape (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (Tensor device dtype shape) = shape
type UTDevice (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (Tensor device dtype shape) = device
type UTDType (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (Tensor device dtype shape) = dtype

Methods

toUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (Tensor device dtype shape) device0 dtype0 shape0 => Tensor device dtype shape -> Tensor device0 dtype0 shape0 Source #

fromUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (Tensor device dtype shape) device0 dtype0 shape0 => Tensor device0 dtype0 shape0 -> Tensor device dtype shape Source #

toDynamic :: Tensor device dtype shape -> Tensor Source #

Castable (Tensor device dtype shape) ATenTensor Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

cast :: Tensor device dtype shape -> (ATenTensor -> IO r) -> IO r

uncast :: ATenTensor -> (Tensor device dtype shape -> IO r) -> IO r

HasGrad (Parameter device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Autograd

Methods

grad :: forall (dtype0 :: DType) (device0 :: (DeviceType, Nat)). Tensor device0 dtype0 ('[] :: [Nat]) -> Parameter device dtype shape -> Tensor device dtype shape Source #

toDependent :: Parameter device dtype shape -> Tensor device dtype shape

(IsSuffixOf normalizedShape shape, KnownShape normalizedShape) => HasForward (LayerNorm normalizedShape dtype device) (Tensor device dtype shape) (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Methods

forward :: LayerNorm normalizedShape dtype device -> Tensor device dtype shape -> Tensor device dtype shape Source #

forwardStoch :: LayerNorm normalizedShape dtype device -> Tensor device dtype shape -> IO (Tensor device dtype shape) Source #

(1 <= numHeads, embedDim ~ (headDim * numHeads), All KnownNat '[embedDim, numHeads, seqLen, batchSize, headDim], IsSuffixOf '[embedDim] '[batchSize, seqLen, embedDim], KnownDType dtype, StandardFloatingPointDTypeValidation device dtype, MatMulDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype, dtype ~ SumDType dtype, SumDTypeIsValid device dtype, KnownDevice device) => Apply' (FoldLayers batchSize seqLen dtype device) (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device, IO (Tensor device dtype '[batchSize, seqLen, embedDim])) (IO (Tensor device dtype '[batchSize, seqLen, embedDim])) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

apply' :: FoldLayers batchSize seqLen dtype device -> (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device, IO (Tensor device dtype '[batchSize, seqLen, embedDim])) -> IO (Tensor device dtype '[batchSize, seqLen, embedDim]) Source #

(shape'' ~ MatMul shape '[inputFeatures, outputFeatures], shape' ~ Broadcast shape'' shape'') => HasForward (Linear inputFeatures outputFeatures dtype device) (Tensor device dtype shape) (Tensor device dtype shape') Source # 
Instance details

Defined in Torch.Typed.NN.Linear

Methods

forward :: Linear inputFeatures outputFeatures dtype device -> Tensor device dtype shape -> Tensor device dtype shape' Source #

forwardStoch :: Linear inputFeatures outputFeatures dtype device -> Tensor device dtype shape -> IO (Tensor device dtype shape') Source #

(All KnownNat '[stride, padding, inputChannelSize, outputChannelSize, kernelSize, inputSize, batchSize, outputSize], ConvSideCheck inputSize kernelSize stride padding outputSize) => HasForward (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: Conv1d inputChannelSize outputChannelSize kernelSize dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize] Source #

forwardStoch :: Conv1d inputChannelSize outputChannelSize kernelSize dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize]) Source #

(All KnownNat '[stride, padding, inputChannelSize, outputChannelSize, kernelSize, inputSize, batchSize, outputSize], ConvSideCheck inputSize kernelSize stride padding outputSize) => HasForward (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize] Source #

forwardStoch :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize]) Source #

(All KnownNat '[Fst stride, Snd stride, Fst padding, Snd padding, inputChannelSize, outputChannelSize, kernelSize0, kernelSize1, inputSize0, inputSize1, batchSize, outputSize0, outputSize1], ConvSideCheck inputSize0 kernelSize0 (Fst stride) (Fst padding) outputSize0, ConvSideCheck inputSize1 kernelSize1 (Snd stride) (Snd padding) outputSize1) => HasForward (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1] Source #

forwardStoch :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1]) Source #

(All KnownNat '[Fst stride, Snd stride, Fst padding, Snd padding, inputChannelSize, outputChannelSize, kernelSize0, kernelSize1, inputSize0, inputSize1, batchSize, outputSize0, outputSize1], ConvSideCheck inputSize0 kernelSize0 (Fst stride) (Fst padding) outputSize0, ConvSideCheck inputSize1 kernelSize1 (Snd stride) (Snd padding) outputSize1) => HasForward (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1] Source #

forwardStoch :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1]) Source #

(KnownMaybeNat paddingIdx, PaddingIdxCheck paddingIdx numEmbeds, shape' ~ Reverse (embedSize ': Reverse shape)) => HasForward (Embedding paddingIdx numEmbeds embedSize embeddingType dtype device) (Tensor device 'Int64 shape) (Tensor device dtype shape') Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

forward :: Embedding paddingIdx numEmbeds embedSize embeddingType dtype device -> Tensor device 'Int64 shape -> Tensor device dtype shape' Source #

forwardStoch :: Embedding paddingIdx numEmbeds embedSize embeddingType dtype device -> Tensor device 'Int64 shape -> IO (Tensor device dtype shape') Source #

(All KnownNat '[Fst3 stride, Snd3 stride, Trd3 stride, Fst3 padding, Snd3 padding, Trd3 padding, inputChannelSize, outputChannelSize, kernelSize0, kernelSize1, kernelSize2, inputSize0, inputSize1, inputSize2, batchSize], ConvSideCheck inputSize0 kernelSize0 (Fst3 stride) (Fst3 padding) outputSize0, ConvSideCheck inputSize1 kernelSize1 (Snd3 stride) (Snd3 padding) outputSize1, ConvSideCheck inputSize2 kernelSize2 (Trd3 stride) (Trd3 padding) outputSize2) => HasForward (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2] Source #

forwardStoch :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2]) Source #

(All KnownNat '[Fst3 stride, Snd3 stride, Trd3 stride, Fst3 padding, Snd3 padding, Trd3 padding, inputChannelSize, outputChannelSize, kernelSize0, kernelSize1, kernelSize2, inputSize0, inputSize1, inputSize2, batchSize], ConvSideCheck inputSize0 kernelSize0 (Fst3 stride) (Fst3 padding) outputSize0, ConvSideCheck inputSize1 kernelSize1 (Snd3 stride) (Snd3 padding) outputSize1, ConvSideCheck inputSize2 kernelSize2 (Trd3 stride) (Trd3 padding) outputSize2) => HasForward (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2]) Source # 
Instance details

Defined in Torch.Typed.NN.Convolution

Methods

forward :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) -> Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2] Source #

forwardStoch :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> (Tensor device dtype '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2], Proxy stride, Proxy padding) -> IO (Tensor device dtype '[batchSize, outputChannelSize, outputSize0, outputSize1, outputSize2]) Source #

(All KnownNat '[paddingIdx, embedDim, seqLen, batchSize], (paddingIdx + 1) <= numEmbeds, 1 <= seqLen, HFoldrM IO (FoldLayers batchSize seqLen dtype device) (Tensor device dtype '[batchSize, seqLen, embedDim]) (HReplicateR numAttnLayers (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device)) (Tensor device dtype '[batchSize, seqLen, embedDim]), BasicArithmeticDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device 'Int64, KnownDType dtype, KnownDevice device) => HasForward (TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device) (Tensor device 'Int64 '[batchSize, seqLen]) (Tensor device dtype '[batchSize, seqLen, numEmbeds]) Source # 
Instance details

Defined in Torch.Typed.NN.Transformer

Methods

forward :: TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device -> Tensor device 'Int64 '[batchSize, seqLen] -> Tensor device dtype '[batchSize, seqLen, numEmbeds] Source #

forwardStoch :: TransformerLM numAttnLayers numHeads ffnDim paddingIdx numEmbeds embedDim dtype device -> Tensor device 'Int64 '[batchSize, seqLen] -> IO (Tensor device dtype '[batchSize, seqLen, numEmbeds]) Source #

type Item (Maybe (Tensor device dtype shape)) Source # 
Instance details

Defined in Torch.Typed.Tensor

type Item (Maybe (Tensor device dtype shape)) = ComputeItemType (ComputeHaskellType dtype) shape
type Parameters (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Parameter

type Parameters (Tensor device dtype shape) = '[] :: [Type]
type UTDType (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (Tensor device dtype shape) = dtype
type UTDevice (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (Tensor device dtype shape) = device
type UTShape (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (Tensor device dtype shape) = shape

class TensorOptions (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #

Instances

Instances details
(KnownDType dtype, KnownDevice device) => TensorOptions ('[] :: [Nat]) dtype device Source # 
Instance details

Defined in Torch.Typed.Tensor

(KnownNat h, TensorOptions t dtype device) => TensorOptions (h ': t) dtype device Source # 
Instance details

Defined in Torch.Typed.Tensor

dtype :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) t. (TensorOptions shape dtype device, IsUnnamed t device dtype shape) => t -> DType Source #

returns tensor data type uses compile-time information only

device :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) t. (TensorOptions shape dtype device, IsUnnamed t device dtype shape) => t -> Device Source #

returns tensor device uses compile-time information only

data NamedTensor (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: Shape) where Source #

Constructors

FromTensor :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: Shape) (shape1 :: [Nat]). shape1 ~ ToNats shape => Tensor device dtype shape1 -> NamedTensor device dtype shape 

Instances

Instances details
(TensorOptions shape' dtype device, shape' ~ ToNats shape) => Default (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Factories

Methods

def :: NamedTensor device dtype shape #

KnownDevice device => Num (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

(+) :: NamedTensor device dtype shape -> NamedTensor device dtype shape -> NamedTensor device dtype shape #

(-) :: NamedTensor device dtype shape -> NamedTensor device dtype shape -> NamedTensor device dtype shape #

(*) :: NamedTensor device dtype shape -> NamedTensor device dtype shape -> NamedTensor device dtype shape #

negate :: NamedTensor device dtype shape -> NamedTensor device dtype shape #

abs :: NamedTensor device dtype shape -> NamedTensor device dtype shape #

signum :: NamedTensor device dtype shape -> NamedTensor device dtype shape #

fromInteger :: Integer -> NamedTensor device dtype shape #

KnownDevice device => Fractional (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

(/) :: NamedTensor device dtype shape -> NamedTensor device dtype shape -> NamedTensor device dtype shape #

recip :: NamedTensor device dtype shape -> NamedTensor device dtype shape #

fromRational :: Rational -> NamedTensor device dtype shape #

Show (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

showsPrec :: Int -> NamedTensor device dtype shape -> ShowS #

show :: NamedTensor device dtype shape -> String #

showList :: [NamedTensor device dtype shape] -> ShowS #

Unnamed (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Associated Types

type UTShape (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (NamedTensor device dtype shape) = ToNats shape
type UTDevice (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (NamedTensor device dtype shape) = device
type UTDType (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (NamedTensor device dtype shape) = dtype

Methods

toUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (NamedTensor device dtype shape) device0 dtype0 shape0 => NamedTensor device dtype shape -> Tensor device0 dtype0 shape0 Source #

fromUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (NamedTensor device dtype shape) device0 dtype0 shape0 => Tensor device0 dtype0 shape0 -> NamedTensor device dtype shape Source #

toDynamic :: NamedTensor device dtype shape -> Tensor Source #

Castable (NamedTensor device dtype shape) ATenTensor Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

cast :: NamedTensor device dtype shape -> (ATenTensor -> IO r) -> IO r

uncast :: ATenTensor -> (NamedTensor device dtype shape -> IO r) -> IO r

type UTDType (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (NamedTensor device dtype shape) = dtype
type UTDevice (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (NamedTensor device dtype shape) = device
type UTShape (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (NamedTensor device dtype shape) = ToNats shape

lt :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

gt :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

class Unnamed t where Source #

Associated Types

type UTShape t :: [Nat] Source #

type UTDevice t :: (DeviceType, Nat) Source #

type UTDType t :: DType Source #

Methods

toUnnamed :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). IsUnnamed t device dtype shape => t -> Tensor device dtype shape Source #

fromUnnamed :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). IsUnnamed t device dtype shape => Tensor device dtype shape -> t Source #

toDynamic :: t -> Tensor Source #

Instances

Instances details
Unnamed (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Associated Types

type UTShape (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (NamedTensor device dtype shape) = ToNats shape
type UTDevice (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (NamedTensor device dtype shape) = device
type UTDType (NamedTensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (NamedTensor device dtype shape) = dtype

Methods

toUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (NamedTensor device dtype shape) device0 dtype0 shape0 => NamedTensor device dtype shape -> Tensor device0 dtype0 shape0 Source #

fromUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (NamedTensor device dtype shape) device0 dtype0 shape0 => Tensor device0 dtype0 shape0 -> NamedTensor device dtype shape Source #

toDynamic :: NamedTensor device dtype shape -> Tensor Source #

Unnamed (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

Associated Types

type UTShape (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (Tensor device dtype shape) = shape
type UTDevice (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (Tensor device dtype shape) = device
type UTDType (Tensor device dtype shape) 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (Tensor device dtype shape) = dtype

Methods

toUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (Tensor device dtype shape) device0 dtype0 shape0 => Tensor device dtype shape -> Tensor device0 dtype0 shape0 Source #

fromUnnamed :: forall (device0 :: (DeviceType, Nat)) (dtype0 :: DType) (shape0 :: [Nat]). IsUnnamed (Tensor device dtype shape) device0 dtype0 shape0 => Tensor device0 dtype0 shape0 -> Tensor device dtype shape Source #

toDynamic :: Tensor device dtype shape -> Tensor Source #

dim :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) t. (TensorOptions shape dtype device, IsUnnamed t device dtype shape) => t -> Int Source #

returns tensor dimension uses compile-time information only

shape :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) t. (TensorOptions shape dtype device, IsUnnamed t device dtype shape) => t -> [Int] Source #

returns tensor shape as list uses compile-time information only

withTensor :: Tensor -> (forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (KnownDevice device, KnownDType dtype, KnownShape shape) => Tensor device dtype shape -> r) -> r Source #

toDouble :: forall (device :: (DeviceType, Nat)). Tensor device 'Double ('[] :: [Nat]) -> Double Source #

toInt :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). Tensor device dtype shape -> Int Source #

reshape :: forall (shape' :: [Nat]) (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (KnownShape shape', Numel shape ~ Numel shape') => Tensor device dtype shape -> Tensor device dtype shape' Source #

reshape >>> t :: CPUTensor 'D.Int64 '[2,3,4] = fromJust [[[111,112,113,114],[121,122,123,124],[131,132,133,134]],[[211,212,213,214],[221,222,223,224],[231,232,233,234]]] >>> t' = reshape '[24] t >>> toList . Just $ t' [111,112,113,114,121,122,123,124,131,132,133,134,211,212,213,214,221,222,223,224,231,232,233,234] >>> toList . Just $ reshape '[2,3,4] t' [[[111,112,113,114],[121,122,123,124],[131,132,133,134]],[[211,212,213,214],[221,222,223,224],[231,232,233,234]]]

toSparse :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). Tensor device dtype shape -> Tensor device dtype shape Source #

toDense :: forall (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]). Tensor device dtype shape -> Tensor device dtype shape Source #

toCPU :: forall (device :: (DeviceType, Nat)) (shape :: [Nat]) (dtype :: DType). Tensor device dtype shape -> CPUTensor dtype shape Source #

move tensor to CPU TODO: can this fail?

toCUDA :: forall {k} (device' :: k) (device :: (DeviceType, Nat)) (shape :: [Nat]) (dtype :: DType). Tensor device dtype shape -> CUDATensor 0 dtype shape Source #

move tensor to the first CUDA device TODO: what if this fails?

toMPS :: forall {k} (device' :: k) (device :: (DeviceType, Nat)) (shape :: [Nat]) (dtype :: DType). Tensor device dtype shape -> MPSTensor 0 dtype shape Source #

move tensor to the first MPS device TODO: what if this fails?

matmul :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (shape'' ~ MatMul shape shape', MatMulDTypeIsValid device dtype) => Tensor device dtype shape -> Tensor device dtype shape' -> Tensor device dtype shape'' Source #

ne :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

ge :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

le :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

(>.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

(>=.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

(<=.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

(==.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

(/=.) :: forall (shape'' :: [Nat]) (shape :: [Nat]) (shape' :: [Nat]) (dtype :: DType) (dtype' :: DType) (device :: (DeviceType, Nat)). (shape'' ~ Broadcast shape shape', ComparisonDTypeIsValid device dtype, ComparisonDTypeIsValid device dtype') => Tensor device dtype shape -> Tensor device dtype' shape' -> Tensor device 'Bool shape'' Source #

type Shape = [Type -> Type] Source #

class KnownShape (shape :: [Nat]) where Source #

Methods

shapeVal :: [Int] Source #

Instances

Instances details
KnownShape ('[] :: [Nat]) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

shapeVal :: [Int] Source #

(KnownNat h, KnownShape t) => KnownShape (h ': t) Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

shapeVal :: [Int] Source #

getFiniteI :: forall (n :: Nat). Finite n -> Int Source #

class KnownDType (dtype :: DType) where Source #

Instances

Instances details
KnownDType 'Bool Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'ComplexDouble Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'ComplexFloat Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'ComplexHalf Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Double Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Float Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Half Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Int16 Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Int32 Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Int64 Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'Int8 Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownDType 'UInt8 Source # 
Instance details

Defined in Torch.Typed.Tensor

class KnownDevice (device :: (DeviceType, Nat)) where Source #

Instances

Instances details
KnownNat n => KnownDevice '('CPU, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownNat n => KnownDevice '('CUDA, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownNat n => KnownDevice '('MPS, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

type family ToNat (shape :: Size) :: Nat where ... Source #

Equations

ToNat (S1 ('MetaSel _1 _2 _3 _4) f) = ToNat f 
ToNat (D1 _1 f) = ToNat f 
ToNat (C1 _1 f) = ToNat f 
ToNat (l :*: r) = ToNat l + ToNat r 
ToNat (l :+: r) = If (ToNat l <=? ToNat r) (ToNat r) (ToNat l) 
ToNat (K1 R (Vector n _1) :: Type -> Type) = n 
ToNat (K1 _1 _2 :: Type -> Type) = 1 
ToNat (U1 :: Type -> Type) = 1 
ToNat (Vector n) = n 
ToNat a = ToNat (Rep (a ())) 

type family ToNats (shape :: Shape) :: [Nat] where ... Source #

Equations

ToNats ('[] :: [Type -> Type]) = '[] :: [Nat] 
ToNats (x ': xs) = ToNat x ': ToNats xs 

type family FromNat (shape :: Nat) :: Size where ... Source #

Equations

FromNat n = Vector n 

type family FromNats (shape :: [Nat]) :: Shape where ... Source #

Equations

FromNats ('[] :: [Nat]) = '[] :: [Type -> Type] 
FromNats (x ': xs) = FromNat x ': FromNats xs 

type family UTShape t :: [Nat] Source #

Instances

Instances details
type UTShape (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (NamedTensor device dtype shape) = ToNats shape
type UTShape (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTShape (Tensor device dtype shape) = shape

type family UTDevice t :: (DeviceType, Nat) Source #

Instances

Instances details
type UTDevice (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (NamedTensor device dtype shape) = device
type UTDevice (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDevice (Tensor device dtype shape) = device

type family UTDType t :: DType Source #

Instances

Instances details
type UTDType (NamedTensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (NamedTensor device dtype shape) = dtype
type UTDType (Tensor device dtype shape) Source # 
Instance details

Defined in Torch.Typed.Tensor

type UTDType (Tensor device dtype shape) = dtype

type family IsUnnamed t (device :: (DeviceType, Nat)) (dtype :: DType) (shape :: [Nat]) where ... Source #

Equations

IsUnnamed t device dtype shape = (Unnamed t, device ~ UTDevice t, dtype ~ UTDType t, shape ~ UTShape t) 

type CPUTensor = Tensor '('CPU, 0) Source #

type CUDATensor (deviceIndex :: Nat) = Tensor '('CUDA, deviceIndex) Source #

type MPSTensor (deviceIndex :: k) = Tensor '('MPS, 0) Source #

data UnknownShapeTensor (device :: (DeviceType, Nat)) (dtype :: DType) Source #

Constructors

UnknownShapeTensor (Tensor device dtype shape) 

type family ComputeHaskellType (dtype :: DType) where ... Source #

type family ComputeItemType ty (shape :: [Nat]) where ... Source #

Equations

ComputeItemType _1 ('[] :: [Nat]) = TypeError ('Text "Scalars are not supported") :: Type 
ComputeItemType ty '[_1] = ty 
ComputeItemType ty (_1 ': (h ': t)) = [ComputeItemType ty (h ': t)] 

data SomeShape where Source #

Constructors

SomeShape :: forall (shape :: [Nat]). KnownShape shape => Proxy shape -> SomeShape 

data SomeDType where Source #

Constructors

SomeDType :: forall (dtype :: DType). KnownDType dtype => Proxy dtype -> SomeDType 

data SomeDevice where Source #

Constructors

SomeDevice :: forall (device :: (DeviceType, Nat)). KnownDevice device => Proxy device -> SomeDevice 

withTensorShape :: forall (device :: (DeviceType, Nat)) (dtype :: DType) r. (KnownDevice device, KnownDType dtype) => Tensor -> (forall (shape :: [Nat]). KnownShape shape => Tensor device dtype shape -> r) -> r Source #

type family ComputeBroadcast (reversedShape :: [Nat]) (reversedShape' :: [Nat]) :: Maybe [Nat] where ... Source #

Equations

ComputeBroadcast ('[] :: [Nat]) reversedShape = 'Just reversedShape 
ComputeBroadcast reversedShape ('[] :: [Nat]) = 'Just reversedShape 
ComputeBroadcast (h ': t) (h ': t2) = AppendToMaybe h (ComputeBroadcast t t2) 
ComputeBroadcast (h ': t) (1 ': t2) = AppendToMaybe h (ComputeBroadcast t t2) 
ComputeBroadcast (1 ': t) (h ': t2) = AppendToMaybe h (ComputeBroadcast t t2) 
ComputeBroadcast _1 _2 = 'Nothing :: Maybe [Nat] 

type family CheckBroadcast (shape :: [Nat]) (shape' :: [Nat]) (result :: Maybe [Nat]) :: [Nat] where ... Source #

Equations

CheckBroadcast shape shape' ('Nothing :: Maybe [Nat]) = TypeError (((('Text "The shapes " ':<>: 'ShowType shape) ':<>: 'Text " and ") ':<>: 'ShowType shape') ':<>: 'Text " cannot be broadcast") :: [Nat] 
CheckBroadcast _1 _2 ('Just result) = Reverse result 

type Broadcast (shape :: [Nat]) (shape' :: [Nat]) = CheckBroadcast shape shape' (ComputeBroadcast (Reverse shape) (Reverse shape')) Source #

type family BasicArithmeticDTypeIsValid (device :: (DeviceType, Nat)) (dtype :: DType) where ... Source #

Equations

BasicArithmeticDTypeIsValid '('CPU, 0) dtype = (DTypeIsNotBool '('CPU, 0) dtype, DTypeIsNotHalf '('CPU, 0) dtype) 
BasicArithmeticDTypeIsValid '('CUDA, _1) dtype = () 
BasicArithmeticDTypeIsValid '('MPS, 0) dtype = () 
BasicArithmeticDTypeIsValid '(deviceType, _1) dtype = UnsupportedDTypeForDevice deviceType dtype 

type family ComparisonDTypeIsValid (device :: (DeviceType, Nat)) (dtype :: DType) where ... Source #

Equations

ComparisonDTypeIsValid '('CPU, 0) dtype = (DTypeIsNotBool '('CPU, 0) dtype, DTypeIsNotHalf '('CPU, 0) dtype) 
ComparisonDTypeIsValid '('CUDA, _1) dtype = () 
ComparisonDTypeIsValid '('MPS, 0) dtype = () 
ComparisonDTypeIsValid '(deviceType, _1) dtype = UnsupportedDTypeForDevice deviceType dtype 

type family ComputeMatMul (reversedShape :: [Nat]) (reversedShape' :: [Nat]) :: Maybe [Nat] where ... Source #

Equations

ComputeMatMul '[k] '[k] = 'Just ('[] :: [Nat]) 
ComputeMatMul '[k] (m ': (k ': reversedBroadcastShape')) = AppendToMaybe m (ComputeBroadcast ('[] :: [Nat]) reversedBroadcastShape') 
ComputeMatMul (k ': (n ': reversedBroadcastShape)) '[k] = AppendToMaybe n (ComputeBroadcast ('[] :: [Nat]) reversedBroadcastShape) 
ComputeMatMul (k ': (n ': reversedBroadcastShape)) (m ': (k ': reversedBroadcastShape')) = AppendToMaybe m (AppendToMaybe n (ComputeBroadcast reversedBroadcastShape reversedBroadcastShape')) 

type family CheckMatMul (shape :: [Nat]) (shape' :: [Nat]) (result :: Maybe [Nat]) :: [Nat] where ... Source #

Equations

CheckMatMul shape shape' ('Nothing :: Maybe [Nat]) = TypeError (((('Text "The shapes " ':<>: 'ShowType shape) ':<>: 'Text " and ") ':<>: 'ShowType shape') ':<>: 'Text " are not compatible with matrix multiplication") :: [Nat] 
CheckMatMul _1 _2 ('Just result) = Reverse result 

type MatMul (shape :: [Nat]) (shape' :: [Nat]) = CheckMatMul shape shape' (ComputeMatMul (Reverse shape) (Reverse shape')) Source #

type family MatMulDTypeIsValid (device :: (DeviceType, Nat)) (dtype :: DType) where ... Source #

Equations

MatMulDTypeIsValid '('CPU, 0) dtype = (DTypeIsNotBool '('CPU, 0) dtype, DTypeIsNotHalf '('CPU, 0) dtype) 
MatMulDTypeIsValid '('CUDA, deviceIndex) dtype = DTypeIsFloatingPoint '('CUDA, deviceIndex) dtype 
MatMulDTypeIsValid '('MPS, 0) dtype = DTypeIsFloatingPoint '('MPS, 0) dtype 
MatMulDTypeIsValid '(deviceType, _1) dtype = UnsupportedDTypeForDevice deviceType dtype 

selectIdx :: forall (dim :: Nat) (n :: Nat) (shape' :: [Nat]) (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (KnownNat dim, n ~ Index shape dim, shape' ~ Remove shape dim) => Tensor device dtype shape -> Finite n -> Tensor device dtype shape' Source #

type family Numel (shape :: [Nat]) :: Nat where ... Source #

Equations

Numel ('[] :: [Nat]) = 1 
Numel (h ': t) = h * Numel t 

newtype Wrap a Source #

To avoid overlapped instance for (Unnamed t => Castable t D.ATenTensor)

Constructors

Wrap 

Fields

Instances

Instances details
Unnamed t => Castable (Wrap t) ATenTensor Source # 
Instance details

Defined in Torch.Typed.Tensor

Methods

cast :: Wrap t -> (ATenTensor -> IO r) -> IO r

uncast :: ATenTensor -> (Wrap t -> IO r) -> IO r

data TensorListFold Source #

Constructors

TensorListFold 

Instances

Instances details
Castable x ATenTensor => Apply' TensorListFold (x, IO [ATenTensor]) (IO [ATenTensor]) Source # 
Instance details

Defined in Torch.Typed.Tensor

data TensorListUnfold Source #

Constructors

TensorListUnfold 

Instances

Instances details
Castable x ATenTensor => Apply TensorListUnfold [ATenTensor] (IO (HJust (x, [ATenTensor]))) Source # 
Instance details

Defined in Torch.Typed.Tensor

Apply TensorListUnfold [ATenTensor] (IO HNothing) Source # 
Instance details

Defined in Torch.Typed.Tensor

type family ReplaceDevice'' (tensor :: t) (device :: (DeviceType, Nat)) :: t where ... Source #

Equations

ReplaceDevice'' (Tensor device0 dtype shape :: Type) device1 = Tensor device1 dtype shape 
ReplaceDevice'' (NamedTensor device0 dtype shape :: Type) device1 = NamedTensor device1 dtype shape 

type family ReplaceDType'' (tensor :: t) (dtype :: DType) :: t where ... Source #

Equations

ReplaceDType'' (Tensor device dtype0 shape :: Type) dtype1 = Tensor device dtype1 shape 
ReplaceDType'' (NamedTensor device dtype0 shape :: Type) dtype1 = NamedTensor device dtype1 shape 

toFloat :: forall (device :: (DeviceType, Nat)). Tensor device 'Float ('[] :: [Nat]) -> Float Source #

type family ToDType a :: DType where ... Source #

type family ToShape a :: Shape where ... Source #

Equations

ToShape Bool = '[] :: [Type -> Type] 
ToShape Int = '[] :: [Type -> Type] 
ToShape Float = '[] :: [Type -> Type] 
ToShape Double = '[] :: [Type -> Type] 
ToShape (f a) = f ': ToShape a 

type family FindDim (a :: Size) (shape :: Shape) :: Nat where ... Source #

Equations

FindDim a (a ': _1) = 0 
FindDim a (b ': ax) = 1 + FindDim a ax 
FindDim a _1 = TypeError (('Text "Not find a type:" ':<>: 'ShowType a) ':<>: 'Text " in the shape.") :: Nat 

data Device Source #

Constructors

Device 

Instances

Instances details
Show Device Source # 
Instance details

Defined in Torch.Device

Eq Device Source # 
Instance details

Defined in Torch.Device

Methods

(==) :: Device -> Device -> Bool #

(/=) :: Device -> Device -> Bool #

Ord Device Source # 
Instance details

Defined in Torch.Device

Show (TVar (Either (Word64, Device) (ForeignPtr Generator))) Source # 
Instance details

Defined in Torch.Random

Methods

showsPrec :: Int -> TVar (Either (Word64, Device) (ForeignPtr Generator)) -> ShowS #

show :: TVar (Either (Word64, Device) (ForeignPtr Generator)) -> String #

showList :: [TVar (Either (Word64, Device) (ForeignPtr Generator))] -> ShowS #

data DeviceType Source #

Constructors

CPU 
CUDA 
MPS 

Instances

Instances details
Show DeviceType Source # 
Instance details

Defined in Torch.Device

Eq DeviceType Source # 
Instance details

Defined in Torch.Device

Ord DeviceType Source # 
Instance details

Defined in Torch.Device

Castable DeviceType DeviceType Source # 
Instance details

Defined in Torch.Device

Methods

cast :: DeviceType -> (DeviceType -> IO r) -> IO r

uncast :: DeviceType -> (DeviceType -> IO r) -> IO r

HasToDevice device' device (HList xs) (HList ys) => ReduceGradients device' '[device] ('[HList xs] :: [Type]) (ys :: [k]) Source # 
Instance details

Defined in Torch.Typed.NN.DataParallel

Methods

reduceGradients :: HList '[HList xs] -> HList ys Source #

(HasToDevice device' device (HList xs) (HList ys), ReduceGradients device' devices xxs ys, HZipWith SumF ys ys ys, 1 <= ListLength xxs) => ReduceGradients device' (device ': devices) (HList xs ': xxs :: [Type]) (ys :: [k]) Source # 
Instance details

Defined in Torch.Typed.NN.DataParallel

Methods

reduceGradients :: HList (HList xs ': xxs) -> HList ys Source #

HasReplicate ('[] :: [(DeviceType, Nat)]) device f ('[] :: [Type]) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

replicate :: f -> HList ('[] :: [Type]) Source #

HasToDevices ('[] :: [(DeviceType, Nat)]) ('[] :: [(DeviceType, Nat)]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

toDevices :: HList ('[] :: [Type]) -> HList ('[] :: [Type]) Source #

(chunks ~ ListLength devices', tensorChunks ~ (Chunk chunks 0 shape dtype device :: [Type]), Castable (HList tensorChunks) [ATenTensor], devices ~ HReplicateR chunks device, HasToDevices devices' devices tensorChunks gs, KnownNat chunks) => HasScatter (devices' :: [(DeviceType, Nat)]) (device :: (DeviceType, Nat)) (Tensor device dtype shape) (gs :: [Type]) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

scatter :: Tensor device dtype shape -> HList gs Source #

(HZipWithM Concurrently GradConcurrentlyF parameters losses gradients', ReduceGradients device' devices gradients' gradients) => HasGradConcurrently (device' :: (DeviceType, Nat)) (devices :: [(DeviceType, Nat)]) (parameters :: [k1]) (losses :: [k1]) (gradients :: [k2]) Source # 
Instance details

Defined in Torch.Typed.NN.DataParallel

Methods

gradConcurrently :: HList parameters -> HList losses -> Concurrently (HList gradients) Source #

(chunks ~ ListLength fs, devices ~ GetDevices fs, devices' ~ HReplicateR chunks device', HasToDevices devices' devices fs tensorChunks, '(shape, dtype, device') ~ Cat 0 tensorChunks, Castable (HList tensorChunks) [ATenTensor]) => HasGather (device' :: (DeviceType, Nat)) (devices :: [(DeviceType, Nat)]) (fs :: [Type]) (Tensor device' dtype shape) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

gather :: HList fs -> Tensor device' dtype shape Source #

(HasReplicate devices' device f gs, HasToDevice device' device f g) => HasReplicate (device' ': devices') device f (g ': gs) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

replicate :: f -> HList (g ': gs) Source #

(HasToDevices devices' devices fs gs, HasToDevice device' device f g) => HasToDevices (device' ': devices') (device ': devices) (f ': fs) (g ': gs) Source # 
Instance details

Defined in Torch.Typed.Device

Methods

toDevices :: HList (f ': fs) -> HList (g ': gs) Source #

KnownNat n => KnownDevice '('CPU, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownNat n => KnownDevice '('CUDA, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

KnownNat n => KnownDevice '('MPS, n) Source # 
Instance details

Defined in Torch.Typed.Tensor

data DType Source #

Constructors

Bool

Bool

UInt8

Byte

Int8

Char

Int16

Short

Int32

Int

Int64

Long

Half

Half

Float

Float

Double

Double

ComplexHalf

ComplexHalf

ComplexFloat

ComplexFloat

ComplexDouble

ComplexDouble

QInt8

QInt8

QUInt8

QUInt8

QInt32

QInt32

BFloat16

BFloat16

Instances

Instances details
Read DType Source # 
Instance details

Defined in Torch.DType

Show DType Source # 
Instance details

Defined in Torch.DType

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

Eq DType Source # 
Instance details

Defined in Torch.DType

Methods

(==) :: DType -> DType -> Bool #

(/=) :: DType -> DType -> Bool #

Castable DType ScalarType Source # 
Instance details

Defined in Torch.DType

Methods

cast :: DType -> (ScalarType -> IO r) -> IO r

uncast :: ScalarType -> (DType -> IO r) -> IO r

Reifies 'Bool DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Bool -> DType #

Reifies 'ComplexDouble DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'ComplexDouble -> DType #

Reifies 'ComplexFloat DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'ComplexFloat -> DType #

Reifies 'ComplexHalf DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'ComplexHalf -> DType #

Reifies 'Double DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Double -> DType #

Reifies 'Float DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Float -> DType #

Reifies 'Half DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Half -> DType #

Reifies 'Int16 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Int16 -> DType #

Reifies 'Int32 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Int32 -> DType #

Reifies 'Int64 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Int64 -> DType #

Reifies 'Int8 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy 'Int8 -> DType #

Reifies Int16 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Int16 -> DType #

Reifies Int32 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Int32 -> DType #

Reifies Int64 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Int64 -> DType #

Reifies Int8 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Int8 -> DType #

Reifies Word8 DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Word8 -> DType #

Reifies Half DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Half -> DType #

Reifies Bool DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Bool -> DType #

Reifies Double DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Double -> DType #

Reifies Float DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Float -> DType #

Reifies Int DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy Int -> DType #

(g ~ ReplaceDType f dtype' dtype, f ~ ReplaceDType g dtype dtype', Generic f, Generic g, GHasToDType dtype' dtype (Rep f) (Rep g)) => HasToDType (dtype' :: DType) (dtype :: DType) f g Source # 
Instance details

Defined in Torch.Typed.DType

Methods

toDType :: f -> g Source #

KnownDType dtype' => HasToDType (dtype' :: DType) (dtype :: DType) (Parameter device dtype shape) (Parameter device dtype' shape) Source # 
Instance details

Defined in Torch.Typed.DType

Methods

toDType :: Parameter device dtype shape -> Parameter device dtype' shape Source #

KnownDType dtype' => HasToDType (dtype' :: DType) (dtype :: DType) (Tensor device dtype shape) (Tensor device dtype' shape) Source # 
Instance details

Defined in Torch.Typed.DType

Methods

toDType :: Tensor device dtype shape -> Tensor device dtype' shape Source #

Reifies (Complex Half) DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy (Complex Half) -> DType #

Reifies (Complex Double) DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy (Complex Double) -> DType #

Reifies (Complex Float) DType Source # 
Instance details

Defined in Torch.DType

Methods

reflect :: proxy (Complex Float) -> DType #

class Castable a (ForeignPtr Scalar) => Scalar a Source #

Instances

Instances details
Scalar Bool Source # 
Instance details

Defined in Torch.Scalar

Scalar Double Source # 
Instance details

Defined in Torch.Scalar

Scalar Float Source # 
Instance details

Defined in Torch.Scalar

Scalar Int Source # 
Instance details

Defined in Torch.Scalar

data Reduction Source #

Instances

Instances details
Show Reduction Source # 
Instance details

Defined in Torch.Functional

Eq Reduction Source # 
Instance details

Defined in Torch.Functional

KnownReduction 'ReduceMean Source # 
Instance details

Defined in Torch.Typed.Functional

KnownReduction 'ReduceNone Source # 
Instance details

Defined in Torch.Typed.Functional

KnownReduction 'ReduceSum Source # 
Instance details

Defined in Torch.Typed.Functional

Castable Reduction Int64 Source # 
Instance details

Defined in Torch.Functional

Methods

cast :: Reduction -> (Int64 -> IO r) -> IO r

uncast :: Int64 -> (Reduction -> IO r) -> IO r

data Tri Source #

Constructors

Upper 
Lower 

Instances

Instances details
Show Tri Source # 
Instance details

Defined in Torch.Functional

Methods

showsPrec :: Int -> Tri -> ShowS #

show :: Tri -> String #

showList :: [Tri] -> ShowS #

Eq Tri Source # 
Instance details

Defined in Torch.Functional

Methods

(==) :: Tri -> Tri -> Bool #

(/=) :: Tri -> Tri -> Bool #