Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data LayoutType
- type family DenseSym0 :: LayoutType where ...
- type family SparseSym0 :: LayoutType where ...
- data SLayoutType :: LayoutType -> Type where
- SDense :: SLayoutType ('Dense :: LayoutType)
- SSparse :: SLayoutType ('Sparse :: LayoutType)
- class KnownLayoutType (layoutType :: LayoutType) where
- data Layout (layoutType :: Type) where
- UncheckedLayout :: forall layoutType. Layout layoutType
- Layout :: forall layoutType. layoutType -> Layout layoutType
- data SLayout (layout :: Layout LayoutType) where
- SUncheckedLayout :: LayoutType -> SLayout 'UncheckedLayout
- SLayout :: forall layoutType. SLayoutType layoutType -> SLayout ('Layout layoutType)
- class KnownLayout (layout :: Layout LayoutType) where
- type family GetLayouts f where ...
Documentation
data LayoutType Source #
Data type that represents the memory layout of a tensor.
Dense | The memory layout of the tensor is dense (strided). |
Sparse | The memory layout of the tensor is sparse. |
Instances
Show LayoutType Source # | |
Defined in Torch.GraduallyTyped.Layout | |
Eq LayoutType Source # | |
Defined in Torch.GraduallyTyped.Layout (==) :: LayoutType -> LayoutType -> Bool Source # (/=) :: LayoutType -> LayoutType -> Bool Source # | |
SingKind LayoutType Source # | |
Defined in Torch.GraduallyTyped.Layout type Demote LayoutType = (r :: Type) Source # fromSing :: forall (a :: LayoutType). Sing a -> Demote LayoutType Source # toSing :: Demote LayoutType -> SomeSing LayoutType Source # | |
Castable LayoutType Layout Source # | |
Defined in Torch.GraduallyTyped.Layout | |
SingI 'Dense Source # | |
SingI 'Sparse Source # | |
MkPosC device shape seqDim seqName seqSize output => HasForward MkAbsPos (Tensor gradient layout device dataType shape) generatorDevice (Tensor ('Gradient 'WithoutGradient) ('Layout 'Dense) device ('DataType 'Int64) ('Shape '['Dim ('Name "*") seqSize])) generatorDevice Source # | |
Defined in Torch.GraduallyTyped.NN.Transformer.Type | |
KnownLayout ('UncheckedLayout :: Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout | |
SGetLayout ('UncheckedLayout :: Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Tensor.Type sGetLayout :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient 'UncheckedLayout device dataType shape -> SLayout 'UncheckedLayout Source # getLayoutType :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient 'UncheckedLayout device dataType shape -> LayoutType Source # | |
SingKind (Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout fromSing :: forall (a :: Layout LayoutType). Sing a -> Demote (Layout LayoutType) Source # toSing :: Demote (Layout LayoutType) -> SomeSing (Layout LayoutType) Source # | |
SingI layoutType => SingI ('Layout layoutType :: Layout LayoutType) Source # | |
MkRelPosC device shape seqDim seqName seqSize output => HasForward (MkRelPos relPosEncBucketDim) (Tensor gradient layout device dataType shape) generatorDevice (Tensor ('Gradient 'WithoutGradient) ('Layout 'Dense) device ('DataType 'Int64) ('Shape '['Dim ('Name "*") ('Size 1), 'Dim ('Name "*") seqSize, 'Dim ('Name "*") seqSize])) generatorDevice Source # | |
Defined in Torch.GraduallyTyped.NN.Transformer.Type forward :: MonadThrow m => MkRelPos relPosEncBucketDim -> Tensor gradient layout device dataType shape -> Generator generatorDevice -> m (Tensor ('Gradient 'WithoutGradient) ('Layout 'Dense) device ('DataType 'Int64) ('Shape '['Dim ('Name "*") ('Size 1), 'Dim ('Name "*") seqSize, 'Dim ('Name "*") seqSize]), Generator generatorDevice) Source # | |
KnownLayoutType layoutType => KnownLayout ('Layout layoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout | |
SGetLayout ('Layout 'Dense) Source # | |
Defined in Torch.GraduallyTyped.Tensor.Type sGetLayout :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient ('Layout 'Dense) device dataType shape -> SLayout ('Layout 'Dense) Source # getLayoutType :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient ('Layout 'Dense) device dataType shape -> LayoutType Source # | |
SGetLayout ('Layout 'Sparse) Source # | |
Defined in Torch.GraduallyTyped.Tensor.Type sGetLayout :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient ('Layout 'Sparse) device dataType shape -> SLayout ('Layout 'Sparse) Source # getLayoutType :: forall (gradient :: Gradient RequiresGradient) (device :: Device (DeviceType Nat)) (dataType :: DataType DType) (shape :: Shape [Dim (Name Symbol) (Size Nat)]). Tensor gradient ('Layout 'Sparse) device dataType shape -> LayoutType Source # | |
(output ~ GLinear (Tensor gradient ('Layout 'Dense) (device <+> generatorDevice) dataType ('Shape '[outputDim, inputDim])) (Tensor gradient ('Layout 'Dense) (device <+> generatorDevice) dataType ('Shape '[outputDim])), generatorOutputDevice ~ (device <+> generatorDevice), SGetGeneratorDevice generatorDevice, SGetGeneratorDevice generatorOutputDevice) => HasInitialize (GLinear (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim, inputDim])) (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim]))) generatorDevice output generatorOutputDevice Source # | |
Defined in Torch.GraduallyTyped.NN.Linear | |
(output ~ GLinear (Tensor gradient ('Layout 'Dense) (device <+> generatorDevice) dataType ('Shape '[outputDim, inputDim])) (), generatorOutputDevice ~ (device <+> generatorDevice), SGetGeneratorDevice generatorDevice) => HasInitialize (GLinear (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim, inputDim])) ()) generatorDevice output generatorOutputDevice Source # | TODO: Add |
Defined in Torch.GraduallyTyped.NN.Linear | |
output ~ Tensor (gradient <|> gradient') ('Layout 'Dense <+> layout') (device <+> device') (dataType <+> dataType') (LinearWithBiasF ('Shape '[outputDim, inputDim]) ('Shape '[outputDim]) shape') => HasForward (GLinear (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim, inputDim])) (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim]))) (Tensor gradient' layout' device' dataType' shape') generatorDevice output generatorDevice Source # | |
Defined in Torch.GraduallyTyped.NN.Linear forward :: MonadThrow m => GLinear (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim, inputDim])) (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim])) -> Tensor gradient' layout' device' dataType' shape' -> Generator generatorDevice -> m (output, Generator generatorDevice) Source # | |
output ~ Tensor (gradient <|> gradient') ('Layout 'Dense <+> layout') (device <+> device') (dataType <+> dataType') (LinearWithoutBiasF ('Shape '[outputDim, inputDim]) shape') => HasForward (GLinear (Tensor gradient ('Layout 'Dense) device dataType ('Shape '[outputDim, inputDim])) ()) (Tensor gradient' layout' device' dataType' shape') generatorDevice output generatorDevice Source # | |
type Demote LayoutType Source # | |
Defined in Torch.GraduallyTyped.Layout | |
type Sing Source # | |
Defined in Torch.GraduallyTyped.Layout | |
type Demote (Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout | |
type Sing Source # | |
Defined in Torch.GraduallyTyped.Layout |
type family SparseSym0 :: LayoutType where ... Source #
SparseSym0 = 'Sparse |
data SLayoutType :: LayoutType -> Type where Source #
SDense :: SLayoutType ('Dense :: LayoutType) | |
SSparse :: SLayoutType ('Sparse :: LayoutType) |
Instances
Show (SLayoutType layoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout |
class KnownLayoutType (layoutType :: LayoutType) where Source #
Instances
KnownLayoutType 'Dense Source # | |
Defined in Torch.GraduallyTyped.Layout | |
KnownLayoutType 'Sparse Source # | |
Defined in Torch.GraduallyTyped.Layout |
data Layout (layoutType :: Type) where Source #
Data type to represent whether or not the tensor's memory layout is checked, that is, known to the compiler.
UncheckedLayout :: forall layoutType. Layout layoutType | The tensor's memory layout is unknown to the compiler. |
Layout :: forall layoutType. layoutType -> Layout layoutType | The tensor's memory layout is known to the compiler. |
Instances
Show layoutType => Show (Layout layoutType) Source # | |
SingKind (Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout fromSing :: forall (a :: Layout LayoutType). Sing a -> Demote (Layout LayoutType) Source # toSing :: Demote (Layout LayoutType) -> SomeSing (Layout LayoutType) Source # | |
SingI layoutType => SingI ('Layout layoutType :: Layout LayoutType) Source # | |
type Demote (Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout | |
type Sing Source # | |
Defined in Torch.GraduallyTyped.Layout |
data SLayout (layout :: Layout LayoutType) where Source #
SUncheckedLayout :: LayoutType -> SLayout 'UncheckedLayout | |
SLayout :: forall layoutType. SLayoutType layoutType -> SLayout ('Layout layoutType) |
class KnownLayout (layout :: Layout LayoutType) where Source #
Instances
KnownLayout ('UncheckedLayout :: Layout LayoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout | |
KnownLayoutType layoutType => KnownLayout ('Layout layoutType) Source # | |
Defined in Torch.GraduallyTyped.Layout |
type family GetLayouts f where ... Source #
GetLayouts (a :: Layout LayoutType) = '[a] | |
GetLayouts (f g) = Concat (GetLayouts f) (GetLayouts g) | |
GetLayouts _ = '[] |