hasktorch-0.2.0.0: Functional differentiable programming in Haskell
Safe HaskellNone
LanguageHaskell2010

Torch.Typed.NN.Sparse

Documentation

data EmbeddingType Source #

Constructors

Constant 
Learned 

Instances

Instances details
Generic EmbeddingType Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Associated Types

type Rep EmbeddingType :: Type -> Type Source #

Show EmbeddingType Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

type Rep EmbeddingType Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

type Rep EmbeddingType = D1 ('MetaData "EmbeddingType" "Torch.Typed.NN.Sparse" "hasktorch-0.2.0.0-F6yFRaDiRF49lpq95SVuR8" 'False) (C1 ('MetaCons "Constant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Learned" 'PrefixI 'False) (U1 :: Type -> Type))

data EmbeddingSpec (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (embeddingType :: EmbeddingType) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #

Constructors

ConstEmbeddingSpec :: forall paddingIdx numEmbeds embedSize dtype device. Tensor device dtype '[numEmbeds, embedSize] -> EmbeddingSpec paddingIdx numEmbeds embedSize 'Constant dtype device 
LearnedEmbeddingWithRandomInitSpec :: forall paddingIdx numEmbeds embedSize dtype device. EmbeddingSpec paddingIdx numEmbeds embedSize 'Learned dtype device 
LearnedEmbeddingWithCustomInitSpec :: forall paddingIdx numEmbeds embedSize dtype device. Tensor device dtype '[numEmbeds, embedSize] -> EmbeddingSpec paddingIdx numEmbeds embedSize 'Learned dtype device 

Instances

Instances details
Show (EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

showsPrec :: Int -> EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device -> ShowS Source #

show :: EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device -> String Source #

showList :: [EmbeddingSpec paddingIdx numEmbeds embedSize embeddingType dtype device] -> ShowS 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 numEmbeds embedSize 'Learned dtype device -> IO (Embedding 'Nothing 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 #

data Embedding (paddingIdx :: Maybe Nat) (numEmbeds :: Nat) (embedSize :: Nat) (embeddingType :: EmbeddingType) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #

Constructors

ConstEmbedding 

Fields

LearnedEmbedding 

Fields

Instances

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

Defined in Torch.Typed.NN.Sparse

Associated Types

type Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) :: Type -> Type Source #

Methods

from :: Embedding paddingIdx numEmbeds embedSize 'Constant dtype device -> Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) x Source #

to :: Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) x -> Embedding paddingIdx numEmbeds embedSize 'Constant dtype device Source #

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

Defined in Torch.Typed.NN.Sparse

Associated Types

type Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) :: Type -> Type Source #

Methods

from :: Embedding paddingIdx numEmbeds embedSize 'Learned dtype device -> Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) x Source #

to :: Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) x -> Embedding paddingIdx numEmbeds embedSize 'Learned dtype device Source #

Show (Embedding paddingIdx numEmbeds embedSize embeddingType dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

Methods

showsPrec :: Int -> Embedding paddingIdx numEmbeds embedSize embeddingType dtype device -> ShowS Source #

show :: Embedding paddingIdx numEmbeds embedSize embeddingType dtype device -> String Source #

showList :: [Embedding paddingIdx numEmbeds embedSize embeddingType dtype device] -> ShowS 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) :: [Type] Source #

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) :: [Type] Source #

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 # 
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 #

(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 numEmbeds embedSize 'Learned dtype device -> IO (Embedding 'Nothing 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 #

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

Defined in Torch.Typed.NN.Sparse

type Rep (Embedding paddingIdx numEmbeds embedSize 'Constant dtype device) = Rec0 (Tensor device dtype '[numEmbeds, embedSize])
type Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Sparse

type Rep (Embedding paddingIdx numEmbeds embedSize 'Learned dtype device) = Rec0 (Parameter device dtype '[numEmbeds, embedSize])
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))

embed :: forall paddingIdx shape numEmbeds embedSize embeddingType dtype device shape'. (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 #