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

Torch.Typed.NN.Normalization

Documentation

data LayerNormSpec (normalizedShape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #

Constructors

LayerNormSpec 

Fields

Instances

Instances details
Show (LayerNormSpec normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Methods

showsPrec :: Int -> LayerNormSpec normalizedShape dtype device -> ShowS #

show :: LayerNormSpec normalizedShape dtype device -> String #

showList :: [LayerNormSpec normalizedShape dtype device] -> ShowS #

Eq (LayerNormSpec normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Methods

(==) :: LayerNormSpec normalizedShape dtype device -> LayerNormSpec normalizedShape dtype device -> Bool #

(/=) :: LayerNormSpec normalizedShape dtype device -> LayerNormSpec normalizedShape dtype device -> Bool #

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

data LayerNorm (normalizedShape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #

Constructors

LayerNorm 

Fields

Instances

Instances details
Generic (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Associated Types

type Rep (LayerNorm normalizedShape dtype device) 
Instance details

Defined in Torch.Typed.NN.Normalization

type Rep (LayerNorm normalizedShape dtype device) = D1 ('MetaData "LayerNorm" "Torch.Typed.NN.Normalization" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "LayerNorm" 'PrefixI 'True) (S1 ('MetaSel ('Just "layerNormWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype normalizedShape)) :*: (S1 ('MetaSel ('Just "layerNormBias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype normalizedShape)) :*: S1 ('MetaSel ('Just "layerNormEps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))))

Methods

from :: LayerNorm normalizedShape dtype device -> Rep (LayerNorm normalizedShape dtype device) x #

to :: Rep (LayerNorm normalizedShape dtype device) x -> LayerNorm normalizedShape dtype device #

Show (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

Methods

showsPrec :: Int -> LayerNorm normalizedShape dtype device -> ShowS #

show :: LayerNorm normalizedShape dtype device -> String #

showList :: [LayerNorm normalizedShape dtype device] -> ShowS #

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 #

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

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

type Rep (LayerNorm normalizedShape dtype device) Source # 
Instance details

Defined in Torch.Typed.NN.Normalization

type Rep (LayerNorm normalizedShape dtype device) = D1 ('MetaData "LayerNorm" "Torch.Typed.NN.Normalization" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "LayerNorm" 'PrefixI 'True) (S1 ('MetaSel ('Just "layerNormWeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype normalizedShape)) :*: (S1 ('MetaSel ('Just "layerNormBias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype normalizedShape)) :*: S1 ('MetaSel ('Just "layerNormEps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))))
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))

layerNormForward :: forall (normalizedShape :: [Nat]) (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (IsSuffixOf normalizedShape shape, KnownShape normalizedShape) => LayerNorm normalizedShape dtype device -> Tensor device dtype shape -> Tensor device dtype shape Source #