hasktorch-gradually-typed-0.2.0.0: experimental project for hasktorch
Safe HaskellSafe-Inferred
LanguageHaskell2010

Torch.GraduallyTyped.Tensor.Indexing

Synopsis

Documentation

data IndexType a Source #

Instances

Instances details
Functor IndexType Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

fmap :: (a -> b) -> IndexType a -> IndexType b Source #

(<$) :: a -> IndexType b -> IndexType a Source #

SingI2 ('SliceFromUpTo :: k2 -> k2 -> IndexType k2) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing2 :: forall (x :: k1) (y :: k20). Sing x -> Sing y -> Sing ('SliceFromUpTo x y) Source #

SingI2 ('SliceFromWithStep :: k2 -> k2 -> IndexType k2) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing2 :: forall (x :: k1) (y :: k20). Sing x -> Sing y -> Sing ('SliceFromWithStep x y) Source #

SingI2 ('SliceUpToWithStep :: k2 -> k2 -> IndexType k2) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing2 :: forall (x :: k1) (y :: k20). Sing x -> Sing y -> Sing ('SliceUpToWithStep x y) Source #

SingI n => SingI2 ('SliceFromUpToWithStep n :: a -> a -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing ('SliceFromUpToWithStep n x y) Source #

SingI1 ('SliceBool :: Bool -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('SliceBool x) Source #

SingI1 ('SliceAt :: k1 -> IndexType k1) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k10). Sing x -> Sing ('SliceAt x) Source #

SingI1 ('SliceFrom :: k1 -> IndexType k1) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k10). Sing x -> Sing ('SliceFrom x) Source #

SingI1 ('SliceUpTo :: k1 -> IndexType k1) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k10). Sing x -> Sing ('SliceUpTo x) Source #

SingI1 ('SliceWithStep :: k1 -> IndexType k1) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k10). Sing x -> Sing ('SliceWithStep x) Source #

SingI n => SingI1 ('SliceFromUpTo n :: a -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('SliceFromUpTo n x) Source #

SingI n => SingI1 ('SliceFromWithStep n :: a -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('SliceFromWithStep n x) Source #

SingI n => SingI1 ('SliceUpToWithStep n :: a -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('SliceUpToWithStep n x) Source #

(SingI n1, SingI n2) => SingI1 ('SliceFromUpToWithStep n1 n2 :: a -> IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('SliceFromUpToWithStep n1 n2 x) Source #

Show a => Show (IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Eq a => Eq (IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

SingKind a => SingKind (IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Associated Types

type Demote (IndexType a) = (r :: Type) Source #

Methods

fromSing :: forall (a0 :: IndexType a). Sing a0 -> Demote (IndexType a) Source #

toSing :: Demote (IndexType a) -> SomeSing (IndexType a) Source #

SingKind (Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Associated Types

type Demote (Indices [IndexType (Index Nat)]) = (r :: Type) Source #

SingI ('Ellipsis :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

SingI ('NewAxis :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing 'NewAxis Source #

SingI ('SliceAll :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

SingI n => SingI ('SliceAt n :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceAt n) Source #

SingI n => SingI ('SliceBool n :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceBool n) Source #

SingI n => SingI ('SliceFrom n :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceFrom n) Source #

SingI n => SingI ('SliceUpTo n :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceUpTo n) Source #

SingI n => SingI ('SliceWithStep n :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceWithStep n) Source #

SingI indexTypes => SingI ('Indices indexTypes :: Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('Indices indexTypes) Source #

(SingI n1, SingI n2) => SingI ('SliceFromUpTo n1 n2 :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceFromUpTo n1 n2) Source #

(SingI n1, SingI n2) => SingI ('SliceFromWithStep n1 n2 :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceFromWithStep n1 n2) Source #

(SingI n1, SingI n2) => SingI ('SliceUpToWithStep n1 n2 :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceUpToWithStep n1 n2) Source #

(SingI n1, SingI n2, SingI n3) => SingI ('SliceFromUpToWithStep n1 n2 n3 :: IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('SliceFromUpToWithStep n1 n2 n3) Source #

type Demote (IndexType a) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Demote (Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Sing Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Sing = SIndexType :: IndexType a -> Type
type Sing Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Sing = SIndices

data SIndexType :: forall (a :: Type). IndexType a -> Type where Source #

Constructors

SNewAxis :: forall (a :: Type). SIndexType ('NewAxis :: IndexType (a :: Type)) 
SEllipsis :: forall (a :: Type). SIndexType ('Ellipsis :: IndexType (a :: Type)) 
SSliceAll :: forall (a :: Type). SIndexType ('SliceAll :: IndexType (a :: Type)) 
SSliceAt :: forall (a :: Type) (n :: a). (Sing n) -> SIndexType ('SliceAt n :: IndexType (a :: Type)) 
SSliceBool :: forall (a :: Type) (n :: Bool). (Sing n) -> SIndexType ('SliceBool n :: IndexType (a :: Type)) 
SSliceFrom :: forall (a :: Type) (n :: a). (Sing n) -> SIndexType ('SliceFrom n :: IndexType (a :: Type)) 
SSliceUpTo :: forall (a :: Type) (n :: a). (Sing n) -> SIndexType ('SliceUpTo n :: IndexType (a :: Type)) 
SSliceWithStep :: forall (a :: Type) (n :: a). (Sing n) -> SIndexType ('SliceWithStep n :: IndexType (a :: Type)) 
SSliceFromUpTo :: forall (a :: Type) (n :: a) (n :: a). (Sing n) -> (Sing n) -> SIndexType ('SliceFromUpTo n n :: IndexType (a :: Type)) 
SSliceFromWithStep :: forall (a :: Type) (n :: a) (n :: a). (Sing n) -> (Sing n) -> SIndexType ('SliceFromWithStep n n :: IndexType (a :: Type)) 
SSliceUpToWithStep :: forall (a :: Type) (n :: a) (n :: a). (Sing n) -> (Sing n) -> SIndexType ('SliceUpToWithStep n n :: IndexType (a :: Type)) 
SSliceFromUpToWithStep :: forall (a :: Type) (n :: a) (n :: a) (n :: a). (Sing n) -> (Sing n) -> (Sing n) -> SIndexType ('SliceFromUpToWithStep n n n :: IndexType (a :: Type)) 

data Indices (indexTypes :: Type) where Source #

Constructors

UncheckedIndices :: forall indexTypes. Indices indexTypes 
Indices :: forall indexTypes. indexTypes -> Indices indexTypes 

Instances

Instances details
SingKind (Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Associated Types

type Demote (Indices [IndexType (Index Nat)]) = (r :: Type) Source #

SingI indexTypes => SingI ('Indices indexTypes :: Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

Methods

sing :: Sing ('Indices indexTypes) Source #

type Demote (Indices [IndexType (Index Nat)]) Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Sing Source # 
Instance details

Defined in Torch.GraduallyTyped.Tensor.Indexing

type Sing = SIndices

data SIndices (indices :: Indices [IndexType (Index Nat)]) where Source #

Constructors

SUncheckedIndices :: [IndexType Integer] -> SIndices 'UncheckedIndices 
SIndices :: forall indexTypes. SList indexTypes -> SIndices ('Indices indexTypes) 

type family IndexDims indices shape where ... Source #

Equations

IndexDims 'UncheckedIndices _ = 'UncheckedShape 
IndexDims _ 'UncheckedShape = 'UncheckedShape 
IndexDims ('Indices indices) ('Shape dims) = IndexDimsImpl indices dims 

(!) :: forall indices requiresGradient layout device dataType shape m. MonadThrow m => Tensor requiresGradient layout device dataType shape -> SIndices indices -> m (Tensor requiresGradient layout device dataType (IndexDims indices shape)) Source #

slice :: QuasiQuoter Source #

Generate a slice from a python compatible expression. When you take the odd-numberPed element of tensor with `tensor[1::2]` in python, you can write `tensor ! [slice|1::2|]` in hasktorch.