Safe Haskell | None |
---|---|
Language | Haskell2010 |
Torch.Typed.NN.Sparse
Documentation
data EmbeddingType Source #
Instances
Generic EmbeddingType Source # | |||||
Defined in Torch.Typed.NN.Sparse Associated Types
| |||||
Show EmbeddingType Source # | |||||
Defined in Torch.Typed.NN.Sparse Methods showsPrec :: Int -> EmbeddingType -> ShowS # show :: EmbeddingType -> String # showList :: [EmbeddingType] -> ShowS # | |||||
type Rep EmbeddingType Source # | |||||
data EmbeddingSpec (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (embeddingType :: EmbeddingType) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
ConstEmbeddingSpec :: forall (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). Tensor device dtype '[numEmbeds, embedSize] -> EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device | |
LearnedEmbeddingWithRandomInitSpec :: forall (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). EmbeddingSpec paddingIdx numEmbeds embedSize 'Learned dtype device | |
LearnedEmbeddingWithCustomInitSpec :: forall (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). Tensor device dtype '[numEmbeds, embedSize] -> EmbeddingSpec paddingIdx numEmbeds embedSize 'Learned dtype device |
Instances
Show (EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device) Source # | |
Defined in Torch.Typed.NN.Sparse Methods showsPrec :: Int -> EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device -> ShowS # show :: EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device -> String # showList :: [EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device] -> ShowS # | |
(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 # | |
(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 # | |
Randomizable (EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device) (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |
Defined in Torch.Typed.NN.Sparse |
data Embedding (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (embeddingType :: EmbeddingType) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
ConstEmbedding | |
LearnedEmbedding | |
Instances
Generic (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |||||
Defined in Torch.Typed.NN.Sparse Methods from :: Embedding paddingIdx numEmbeds embedSize 'Constant dtype device -> Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) x # to :: Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) x -> Embedding paddingIdx numEmbeds embedSize 'Constant dtype device # | |||||
Generic (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) Source # | |||||
Defined in Torch.Typed.NN.Sparse | |||||
Show (Embedding paddingIdx numEmbeds embedSize embeddingType dtype device) Source # | |||||
Defined in Torch.Typed.NN.Sparse | |||||
Parameterized (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |||||
Defined in Torch.Typed.NN.Sparse Associated Types
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 # | |||||
Defined in Torch.Typed.NN.Sparse Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
(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 # | |||||
Randomizable (EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device) (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |||||
Defined in Torch.Typed.NN.Sparse | |||||
type Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |||||
type Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) Source # | |||||
type Parameters (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) Source # | |||||
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 # | |||||
Defined in Torch.Typed.NN.Sparse type Parameters (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) = GParameters (Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device)) |
embed :: forall (paddingIdx :: Maybe Nat) (shape :: [Nat]) (numEmbeds :: Nat) (embedSize :: Nat) (embeddingType :: EmbeddingType) (dtype :: DType) (device :: (DeviceType, Nat)) (shape' :: [Nat]). (KnownMaybeNat paddingIdx, PaddingIdxCheck paddingIdx numEmbeds, shape' ~ Reverse (embedSize ': Reverse shape)) => Embedding paddingIdx numEmbeds embedSize embeddingType dtype device -> Tensor device 'Int64 shape -> Tensor device dtype shape' Source #