Safe Haskell | None |
---|---|
Language | Haskell2010 |
Torch.Typed.NN.Linear
Synopsis
- data LinearSpec (inputFeatures :: Nat) (outputFeatures :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = LinearSpec
- data Linear (inputFeatures :: Nat) (outputFeatures :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- linearForward :: forall {inputFeatures :: Nat} {outputFeatures :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)} {shape :: [Nat]}. Linear inputFeatures outputFeatures w1 w2 -> Tensor w2 w1 shape -> Tensor w2 w1 (CheckBroadcast (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) (ComputeBroadcast (ReverseImpl (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) ('[] :: [Nat])) (ReverseImpl (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) ('[] :: [Nat]))))
Documentation
data LinearSpec (inputFeatures :: Nat) (outputFeatures :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
LinearSpec |
Instances
Show (LinearSpec inputFeatures outputFeatures dtype device) Source # | |
Defined in Torch.Typed.NN.Linear Methods showsPrec :: Int -> LinearSpec inputFeatures outputFeatures dtype device -> ShowS # show :: LinearSpec inputFeatures outputFeatures dtype device -> String # showList :: [LinearSpec inputFeatures outputFeatures dtype device] -> ShowS # | |
Eq (LinearSpec inputFeatures outputFeatures dtype device) Source # | |
Defined in Torch.Typed.NN.Linear Methods (==) :: LinearSpec inputFeatures outputFeatures dtype device -> LinearSpec inputFeatures outputFeatures dtype device -> Bool # (/=) :: LinearSpec inputFeatures outputFeatures dtype device -> LinearSpec inputFeatures outputFeatures dtype device -> Bool # | |
(KnownNat inputFeatures, KnownNat outputFeatures, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (LinearSpec inputFeatures outputFeatures dtype device) (Linear inputFeatures outputFeatures dtype device) Source # | |
Defined in Torch.Typed.NN.Linear |
data Linear (inputFeatures :: Nat) (outputFeatures :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
Linear | |
Instances
Generic (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Defined in Torch.Typed.NN.Linear Associated Types
| |||||
Show (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Parameterized (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Defined in Torch.Typed.NN.Linear Associated Types
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 # | |||||
(shape'' ~ MatMul shape '[inputFeatures, outputFeatures], shape' ~ Broadcast shape'' shape'') => HasForward (Linear inputFeatures outputFeatures dtype device) (Tensor device dtype shape) (Tensor device dtype shape') Source # | |||||
Defined in Torch.Typed.NN.Linear | |||||
(KnownNat inputFeatures, KnownNat outputFeatures, KnownDType dtype, KnownDevice device, RandDTypeIsValid device dtype) => Randomizable (LinearSpec inputFeatures outputFeatures dtype device) (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Defined in Torch.Typed.NN.Linear | |||||
type Rep (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Defined in Torch.Typed.NN.Linear type Rep (Linear inputFeatures outputFeatures dtype device) = D1 ('MetaData "Linear" "Torch.Typed.NN.Linear" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "Linear" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputFeatures, inputFeatures])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputFeatures])))) | |||||
type Parameters (Linear inputFeatures outputFeatures dtype device) Source # | |||||
Defined in Torch.Typed.NN.Linear type Parameters (Linear inputFeatures outputFeatures dtype device) = GParameters (Rep (Linear inputFeatures outputFeatures dtype device)) |
linearForward :: forall {inputFeatures :: Nat} {outputFeatures :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)} {shape :: [Nat]}. Linear inputFeatures outputFeatures w1 w2 -> Tensor w2 w1 shape -> Tensor w2 w1 (CheckBroadcast (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) (ComputeBroadcast (ReverseImpl (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) ('[] :: [Nat])) (ReverseImpl (CheckMatMul shape '[inputFeatures, outputFeatures] (ComputeMatMul (ReverseImpl shape ('[] :: [Nat])) '[outputFeatures, inputFeatures])) ('[] :: [Nat])))) Source #
linear The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.