Safe Haskell | None |
---|---|
Language | Haskell2010 |
Torch.Typed.NN.Convolution
Synopsis
- data Conv1dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = Conv1dSpec
- data Conv1d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- conv1dForward :: forall (stride :: Nat) (padding :: Nat) {kernelSize :: Nat} {inputSize :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 stride) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType stride) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize) :: Constraint), Assert (OrdCond (CmpNat (kernelSize - 1) (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize, KnownNat kernelSize, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat padding, KnownNat stride) => Conv1d inputChannelSize outputChannelSize kernelSize w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize + (2 * padding)) - kernelSize) stride + 1]
- data Conv2dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = Conv2dSpec
- data Conv2d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- conv2dForward :: forall (stride :: (Nat, Nat)) (padding :: (Nat, Nat)) {kernelSize1 :: Nat} {inputSize1 :: Nat} {kernelSize0 :: Nat} {inputSize0 :: Nat} {inputChannelSize :: Nat} {outputChannelSize :: Nat} {batchSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint), KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat inputSize0, KnownNat inputSize1, KnownNat batchSize, KnownNat (Fst stride), KnownNat (Fst padding), KnownNat (Snd stride), KnownNat (Snd padding)) => Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst padding)) - kernelSize0) (Fst stride) + 1, Div ((inputSize1 + (2 * Snd padding)) - kernelSize1) (Snd stride) + 1]
- data Conv3dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = Conv3dSpec
- data Conv3d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- conv3dForward :: forall (stride :: (Nat, Nat, Nat)) (padding :: (Nat, Nat, Nat)) {kernelSize0 :: Nat} {inputSize0 :: Nat} {kernelSize2 :: Nat} {inputSize2 :: Nat} {kernelSize1 :: Nat} {inputSize1 :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize2 (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize2) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Trd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Trd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize2) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize2) :: Constraint), Assert (OrdCond (CmpNat (kernelSize2 - 1) (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize2 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize2, KnownNat inputSize1, KnownNat inputSize0, KnownNat kernelSize2, KnownNat kernelSize1, KnownNat kernelSize0, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat (Trd3 padding), KnownNat (Trd3 stride), KnownNat (Snd3 padding), KnownNat (Snd3 stride), KnownNat (Fst3 padding), KnownNat (Fst3 stride)) => Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst3 padding)) - kernelSize0) (Fst3 stride) + 1, Div ((inputSize1 + (2 * Snd3 padding)) - kernelSize1) (Snd3 stride) + 1, Div ((inputSize2 + (2 * Trd3 padding)) - kernelSize2) (Trd3 stride) + 1]
- data ConvTranspose1dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = ConvTranspose1dSpec
- data ConvTranspose1d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- ConvTranspose1d :: forall (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). {..} -> ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device
- convTranspose1dForward :: forall (stride :: Nat) (padding :: Nat) {kernelSize :: Nat} {inputSize :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 stride) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType stride) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize) :: Constraint), Assert (OrdCond (CmpNat (kernelSize - 1) (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize, KnownNat kernelSize, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat padding, KnownNat stride) => ConvTranspose1d inputChannelSize outputChannelSize kernelSize w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize + (2 * padding)) - kernelSize) stride + 1]
- data ConvTranspose2dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = ConvTranspose2dSpec
- data ConvTranspose2d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- ConvTranspose2d :: forall (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). {..} -> ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device
- convTranspose2dForward :: forall (stride :: (Nat, Nat)) (padding :: (Nat, Nat)) {kernelSize1 :: Nat} {inputSize1 :: Nat} {kernelSize0 :: Nat} {inputSize0 :: Nat} {inputChannelSize :: Nat} {outputChannelSize :: Nat} {batchSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint), KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat inputSize0, KnownNat inputSize1, KnownNat batchSize, KnownNat (Fst stride), KnownNat (Fst padding), KnownNat (Snd stride), KnownNat (Snd padding)) => ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst padding)) - kernelSize0) (Fst stride) + 1, Div ((inputSize1 + (2 * Snd padding)) - kernelSize1) (Snd stride) + 1]
- data ConvTranspose3dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) = ConvTranspose3dSpec
- data ConvTranspose3d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where
- ConvTranspose3d :: forall (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). {..} -> ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device
- convTranspose3dForward :: forall (stride :: (Nat, Nat, Nat)) (padding :: (Nat, Nat, Nat)) {kernelSize0 :: Nat} {inputSize0 :: Nat} {kernelSize2 :: Nat} {inputSize2 :: Nat} {kernelSize1 :: Nat} {inputSize1 :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize2 (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize2) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Trd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Trd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize2) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize2) :: Constraint), Assert (OrdCond (CmpNat (kernelSize2 - 1) (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize2 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize2, KnownNat inputSize1, KnownNat inputSize0, KnownNat kernelSize2, KnownNat kernelSize1, KnownNat kernelSize0, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat (Trd3 padding), KnownNat (Trd3 stride), KnownNat (Snd3 padding), KnownNat (Snd3 stride), KnownNat (Fst3 padding), KnownNat (Fst3 stride)) => ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst3 padding)) - kernelSize0) (Fst3 stride) + 1, Div ((inputSize1 + (2 * Snd3 padding)) - kernelSize1) (Snd3 stride) + 1, Div ((inputSize2 + (2 * Trd3 padding)) - kernelSize2) (Trd3 stride) + 1]
Documentation
data Conv1dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
Conv1dSpec |
Instances
Show (Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> ShowS # show :: Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> String # showList :: [Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device] -> ShowS # | |
Eq (Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Bool # (/=) :: Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Conv1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Bool # | |
(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 # | |
Defined in Torch.Typed.NN.Convolution |
data Conv1d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
Conv1d | |
Fields
|
Instances
Generic (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: Conv1d inputChannelSize outputChannelSize kernelSize dtype device -> Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) x # to :: Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) x -> Conv1d inputChannelSize outputChannelSize kernelSize dtype device # | |||||
Show (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution | |||||
Parameterized (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
Defined in Torch.Typed.NN.Convolution | |||||
type Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) = D1 ('MetaData "Conv1d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "Conv1d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize, inputChannelSize, kernelSize])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Parameters (Conv1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (Conv1d inputChannelSize outputChannelSize kernelSize dtype device)) |
conv1dForward :: forall (stride :: Nat) (padding :: Nat) {kernelSize :: Nat} {inputSize :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 stride) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType stride) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize) :: Constraint), Assert (OrdCond (CmpNat (kernelSize - 1) (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize, KnownNat kernelSize, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat padding, KnownNat stride) => Conv1d inputChannelSize outputChannelSize kernelSize w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize + (2 * padding)) - kernelSize) stride + 1] Source #
conv1d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.
data Conv2dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
Conv2dSpec |
Instances
Show (Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ShowS # show :: Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> String # showList :: [Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device] -> ShowS # | |
Eq (Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Bool # (/=) :: Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Conv2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Bool # | |
(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 # | |
Defined in Torch.Typed.NN.Convolution |
data Conv2d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
Conv2d | |
Fields
|
Instances
Generic (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) x # to :: Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) x -> Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device # | |||||
Show (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ShowS # show :: Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> String # showList :: [Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device] -> ShowS # | |||||
Parameterized (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
Defined in Torch.Typed.NN.Convolution | |||||
type Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = D1 ('MetaData "Conv2d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "Conv2d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize, inputChannelSize, kernelSize0, kernelSize1])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Parameters (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) |
conv2dForward :: forall (stride :: (Nat, Nat)) (padding :: (Nat, Nat)) {kernelSize1 :: Nat} {inputSize1 :: Nat} {kernelSize0 :: Nat} {inputSize0 :: Nat} {inputChannelSize :: Nat} {outputChannelSize :: Nat} {batchSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint), KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat inputSize0, KnownNat inputSize1, KnownNat batchSize, KnownNat (Fst stride), KnownNat (Fst padding), KnownNat (Snd stride), KnownNat (Snd padding)) => Conv2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst padding)) - kernelSize0) (Fst stride) + 1, Div ((inputSize1 + (2 * Snd padding)) - kernelSize1) (Snd stride) + 1] Source #
conv2d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.
data Conv3dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
Conv3dSpec |
Instances
Show (Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ShowS # show :: Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> String # showList :: [Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device] -> ShowS # | |
Eq (Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Bool # (/=) :: Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Conv3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Bool # | |
(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 # | |
Defined in Torch.Typed.NN.Convolution |
data Conv3d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
Conv3d | |
Fields
|
Instances
Generic (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) x # to :: Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) x -> Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device # | |||||
Show (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ShowS # show :: Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> String # showList :: [Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device] -> ShowS # | |||||
Parameterized (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
Defined in Torch.Typed.NN.Convolution | |||||
type Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = D1 ('MetaData "Conv3d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "Conv3d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize, inputChannelSize, kernelSize0, kernelSize1, kernelSize2])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
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)) |
conv3dForward :: forall (stride :: (Nat, Nat, Nat)) (padding :: (Nat, Nat, Nat)) {kernelSize0 :: Nat} {inputSize0 :: Nat} {kernelSize2 :: Nat} {inputSize2 :: Nat} {kernelSize1 :: Nat} {inputSize1 :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize2 (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize2) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Trd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Trd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize2) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize2) :: Constraint), Assert (OrdCond (CmpNat (kernelSize2 - 1) (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize2 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize2, KnownNat inputSize1, KnownNat inputSize0, KnownNat kernelSize2, KnownNat kernelSize1, KnownNat kernelSize0, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat (Trd3 padding), KnownNat (Trd3 stride), KnownNat (Snd3 padding), KnownNat (Snd3 stride), KnownNat (Fst3 padding), KnownNat (Fst3 stride)) => Conv3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst3 padding)) - kernelSize0) (Fst3 stride) + 1, Div ((inputSize1 + (2 * Snd3 padding)) - kernelSize1) (Snd3 stride) + 1, Div ((inputSize2 + (2 * Trd3 padding)) - kernelSize2) (Trd3 stride) + 1] Source #
conv3d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.
data ConvTranspose1dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
ConvTranspose1dSpec |
Instances
Show (ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> ShowS # show :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> String # showList :: [ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device] -> ShowS # | |
Eq (ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Bool # (/=) :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> Bool # | |
(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 # | |
Defined in Torch.Typed.NN.Convolution Methods sample :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> IO (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # |
data ConvTranspose1d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
ConvTranspose1d | |
Fields
|
Instances
Generic (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) x # to :: Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) x -> ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device # | |||||
Show (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> ShowS # show :: ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device -> String # showList :: [ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device] -> ShowS # | |||||
Parameterized (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
Defined in Torch.Typed.NN.Convolution Methods sample :: ConvTranspose1dSpec inputChannelSize outputChannelSize kernelSize dtype device -> IO (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
type Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) = D1 ('MetaData "ConvTranspose1d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "ConvTranspose1d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[inputChannelSize, outputChannelSize, kernelSize])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Parameters (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device) = GParameters (Rep (ConvTranspose1d inputChannelSize outputChannelSize kernelSize dtype device)) |
convTranspose1dForward :: forall (stride :: Nat) (padding :: Nat) {kernelSize :: Nat} {inputSize :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 stride) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType stride) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize) :: Constraint), Assert (OrdCond (CmpNat (kernelSize - 1) (inputSize + (2 * padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize + (2 * padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize, KnownNat kernelSize, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat padding, KnownNat stride) => ConvTranspose1d inputChannelSize outputChannelSize kernelSize w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize + (2 * padding)) - kernelSize) stride + 1] Source #
convTranspose1d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.
data ConvTranspose2dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
ConvTranspose2dSpec |
Instances
Show (ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ShowS # show :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> String # showList :: [ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device] -> ShowS # | |
Eq (ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Bool # (/=) :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Bool # | |
(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 # | |
Defined in Torch.Typed.NN.Convolution Methods sample :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> IO (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # |
data ConvTranspose2d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
ConvTranspose2d | |
Fields
|
Instances
Generic (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) x # to :: Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) x -> ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device # | |||||
Show (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> ShowS # show :: ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> String # showList :: [ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device] -> ShowS # | |||||
Parameterized (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
Defined in Torch.Typed.NN.Convolution Methods sample :: ConvTranspose2dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device -> IO (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
type Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = D1 ('MetaData "ConvTranspose2d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "ConvTranspose2d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[inputChannelSize, outputChannelSize, kernelSize0, kernelSize1])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Parameters (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device) = GParameters (Rep (ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 dtype device)) |
convTranspose2dForward :: forall (stride :: (Nat, Nat)) (padding :: (Nat, Nat)) {kernelSize1 :: Nat} {inputSize1 :: Nat} {kernelSize0 :: Nat} {inputSize0 :: Nat} {inputChannelSize :: Nat} {outputChannelSize :: Nat} {batchSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd padding))) :: Constraint), KnownNat inputChannelSize, KnownNat outputChannelSize, KnownNat kernelSize0, KnownNat kernelSize1, KnownNat inputSize0, KnownNat inputSize1, KnownNat batchSize, KnownNat (Fst stride), KnownNat (Fst padding), KnownNat (Snd stride), KnownNat (Snd padding)) => ConvTranspose2d inputChannelSize outputChannelSize kernelSize0 kernelSize1 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst padding)) - kernelSize0) (Fst stride) + 1, Div ((inputSize1 + (2 * Snd padding)) - kernelSize1) (Snd stride) + 1] Source #
convTranspose2d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.
data ConvTranspose3dSpec (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) Source #
Constructors
ConvTranspose3dSpec |
Instances
Show (ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ShowS # show :: ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> String # showList :: [ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device] -> ShowS # | |
Eq (ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |
Defined in Torch.Typed.NN.Convolution Methods (==) :: ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Bool # (/=) :: ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ConvTranspose3dSpec inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Bool # | |
(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 # | |
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 # |
data ConvTranspose3d (inputChannelSize :: Nat) (outputChannelSize :: Nat) (kernelSize0 :: Nat) (kernelSize1 :: Nat) (kernelSize2 :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)) where Source #
Constructors
ConvTranspose3d | |
Fields
|
Instances
Generic (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
Methods from :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) x # to :: Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) x -> ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device # | |||||
Show (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Methods showsPrec :: Int -> ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> ShowS # show :: ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device -> String # showList :: [ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device] -> ShowS # | |||||
Parameterized (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution Associated Types
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 # | |||||
(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 # | |||||
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 # | |||||
(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 # | |||||
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 # | |||||
type Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
Defined in Torch.Typed.NN.Convolution type Rep (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) = D1 ('MetaData "ConvTranspose3d" "Torch.Typed.NN.Convolution" "hasktorch-0.2.1.2-inplace" 'False) (C1 ('MetaCons "ConvTranspose3d" 'PrefixI 'True) (S1 ('MetaSel ('Just "weight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[inputChannelSize, outputChannelSize, kernelSize0, kernelSize1, kernelSize2])) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Parameter device dtype '[outputChannelSize])))) | |||||
type Parameters (ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 dtype device) Source # | |||||
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)) |
convTranspose3dForward :: forall (stride :: (Nat, Nat, Nat)) (padding :: (Nat, Nat, Nat)) {kernelSize0 :: Nat} {inputSize0 :: Nat} {kernelSize2 :: Nat} {inputSize2 :: Nat} {kernelSize1 :: Nat} {inputSize1 :: Nat} {batchSize :: Nat} {outputChannelSize :: Nat} {inputChannelSize :: Nat} {w1 :: DType} {w2 :: (DeviceType, Nat)}. (Assert (OrdCond (CmpNat kernelSize0 (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize0) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize2 (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize2) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat kernelSize1 (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType kernelSize1) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Snd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Snd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Trd3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Trd3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 (Fst3 stride)) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType (Fst3 stride)) :: Constraint) ~ (), Assert (OrdCond (CmpNat 1 kernelSize0) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize0) :: Constraint), Assert (OrdCond (CmpNat (kernelSize0 - 1) (inputSize0 + (2 * Fst3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize0 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize0 + (2 * Fst3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize1) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize1) :: Constraint), Assert (OrdCond (CmpNat (kernelSize1 - 1) (inputSize1 + (2 * Snd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize1 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize1 + (2 * Snd3 padding))) :: Constraint), Assert (OrdCond (CmpNat 1 kernelSize2) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType 1) ':<>: 'Text " <= ") ':<>: 'ShowType kernelSize2) :: Constraint), Assert (OrdCond (CmpNat (kernelSize2 - 1) (inputSize2 + (2 * Trd3 padding))) 'True 'True 'False) (TypeError ((('Text "Cannot satisfy: " ':<>: 'ShowType (kernelSize2 - 1)) ':<>: 'Text " <= ") ':<>: 'ShowType (inputSize2 + (2 * Trd3 padding))) :: Constraint), KnownNat batchSize, KnownNat inputSize2, KnownNat inputSize1, KnownNat inputSize0, KnownNat kernelSize2, KnownNat kernelSize1, KnownNat kernelSize0, KnownNat outputChannelSize, KnownNat inputChannelSize, KnownNat (Trd3 padding), KnownNat (Trd3 stride), KnownNat (Snd3 padding), KnownNat (Snd3 stride), KnownNat (Fst3 padding), KnownNat (Fst3 stride)) => ConvTranspose3d inputChannelSize outputChannelSize kernelSize0 kernelSize1 kernelSize2 w1 w2 -> Tensor w2 w1 '[batchSize, inputChannelSize, inputSize0, inputSize1, inputSize2] -> Tensor w2 w1 '[batchSize, outputChannelSize, Div ((inputSize0 + (2 * Fst3 padding)) - kernelSize0) (Fst3 stride) + 1, Div ((inputSize1 + (2 * Snd3 padding)) - kernelSize1) (Snd3 stride) + 1, Div ((inputSize2 + (2 * Trd3 padding)) - kernelSize2) (Trd3 stride) + 1] Source #
convTranspose3d The constraints on this one are _very_ involved, so the partial signatures make the code significantly cleaner.