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

Torch.Typed.Lens

Documentation

class HasName (name :: Type -> Type) (shape :: Shape) where Source #

Minimal complete definition

Nothing

Methods

name :: forall (device :: (DeviceType, Nat)) (dtype :: DType). Traversal' (NamedTensor device dtype shape) (NamedTensor device dtype (DropName name shape)) Source #

default name :: forall (device :: (DeviceType, Nat)) (dtype :: DType). KnownNat (NamedIdx name shape) => Traversal' (NamedTensor device dtype shape) (NamedTensor device dtype (DropName name shape)) Source #

Instances

Instances details
KnownNat (NamedIdx name shape) => HasName name shape Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

name :: forall (device :: (DeviceType, Nat)) (dtype :: DType). Traversal' (NamedTensor device dtype shape) (NamedTensor device dtype (DropName name shape)) Source #

class HasField (field :: Symbol) (shape :: Shape) where Source #

Minimal complete definition

Nothing

Methods

field :: forall (device :: (DeviceType, Nat)) (dtype :: DType). Lens' (NamedTensor device dtype shape) (NamedTensor device dtype (DropField field shape)) Source #

default field :: forall (device :: (DeviceType, Nat)) (dtype :: DType). FieldIdx field shape => Lens' (NamedTensor device dtype shape) (NamedTensor device dtype (DropField field shape)) Source #

Instances

Instances details
FieldIdx field shape => HasField field shape Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

field :: forall (device :: (DeviceType, Nat)) (dtype :: DType). Lens' (NamedTensor device dtype shape) (NamedTensor device dtype (DropField field shape)) Source #

type family GHasField (field :: Symbol) (f :: Type -> Type) :: Bool where ... Source #

Equations

GHasField field (S1 ('MetaSel ('Just field) _1 _2 _3) _4) = 'True 
GHasField field (S1 ('MetaSel _1 _2 _3 _4) _5) = 'False 
GHasField field (D1 _1 f) = GHasField field f 
GHasField field (C1 _1 f) = GHasField field f 
GHasField field (l :*: r) = GHasField field l || GHasField field r 
GHasField field (l :+: r) = GHasField field l || GHasField field r 
GHasField field (K1 _1 _2 :: Type -> Type) = 'False 
GHasField field (U1 :: Type -> Type) = 'False 
GHasField field (Vector n) = 'False 
GHasField field a = GHasField field (Rep (a ())) 

type family DropField (field :: Symbol) (a :: [Type -> Type]) :: [Type -> Type] where ... Source #

Equations

DropField field ('[] :: [Type -> Type]) = '[] :: [Type -> Type] 
DropField field (x ': xs) = If (GHasField field x) xs (x ': DropField field xs) 

type family DropName (name :: Type -> Type) (a :: [Type -> Type]) :: [Type -> Type] where ... Source #

Equations

DropName name ('[] :: [Type -> Type]) = '[] :: [Type -> Type] 
DropName name (name ': xs) = xs 
DropName name (x ': xs) = x ': DropName name xs 

type family NamedIdx (name :: Type -> Type) (shape :: [Type -> Type]) :: Nat where ... Source #

Equations

NamedIdx name ('[] :: [Type -> Type]) = TypeError ('Text "There is not the name in the shape.") :: Nat 
NamedIdx name (name ': xs) = 0 
NamedIdx name (x ': xs) = NamedIdx name xs + 1 

class FieldIdx (field :: Symbol) (a :: [Type -> Type]) where Source #

Methods

fieldIdx :: Proxy a -> [Maybe Int] Source #

Return field-id

Instances

Instances details
FieldIdx field ('[] :: [Type -> Type]) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

fieldIdx :: Proxy ('[] :: [Type -> Type]) -> [Maybe Int] Source #

(FieldId field (x ()), FieldIdx field xs) => FieldIdx field (x ': xs) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

fieldIdx :: Proxy (x ': xs) -> [Maybe Int] Source #

class FieldId (field :: Symbol) a where Source #

Minimal complete definition

Nothing

Methods

fieldId :: Proxy a -> Maybe Int Source #

Return field-id

default fieldId :: (Generic a, GFieldId field (Rep a)) => Proxy a -> Maybe Int Source #

Instances

Instances details
(Generic s, GFieldId field (Rep s)) => FieldId field s Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

fieldId :: Proxy s -> Maybe Int Source #

FieldId field (Vector n v) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

fieldId :: Proxy (Vector n v) -> Maybe Int Source #

class GFieldId (field :: Symbol) (a :: Type -> Type) where Source #

Minimal complete definition

gfieldId'

Instances

Instances details
GFieldId field (U1 :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (U1 :: Type -> Type) -> Maybe Int Source #

gfieldId' :: Proxy (U1 :: Type -> Type) -> (Maybe Int, Int) Source #

(GFieldId field f, GFieldId field g) => GFieldId field (f :*: g) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (f :*: g) -> Maybe Int Source #

gfieldId' :: Proxy (f :*: g) -> (Maybe Int, Int) Source #

(GFieldId field f, GFieldId field g) => GFieldId field (f :+: g) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (f :+: g) -> Maybe Int Source #

gfieldId' :: Proxy (f :+: g) -> (Maybe Int, Int) Source #

GFieldId field (K1 c f :: Type -> Type) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (K1 c f :: Type -> Type) -> Maybe Int Source #

gfieldId' :: Proxy (K1 c f :: Type -> Type) -> (Maybe Int, Int) Source #

(KnownSymbol field, KnownSymbol field_) => GFieldId field (S1 ('MetaSel ('Just field_) p f b) (Rec0 a)) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (S1 ('MetaSel ('Just field_) p f b) (Rec0 a)) -> Maybe Int Source #

gfieldId' :: Proxy (S1 ('MetaSel ('Just field_) p f b) (Rec0 a)) -> (Maybe Int, Int) Source #

GFieldId field f => GFieldId field (M1 C t f) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (M1 C t f) -> Maybe Int Source #

gfieldId' :: Proxy (M1 C t f) -> (Maybe Int, Int) Source #

GFieldId field f => GFieldId field (M1 D t f) Source # 
Instance details

Defined in Torch.Typed.Lens

Methods

gfieldId :: Proxy (M1 D t f) -> Maybe Int Source #

gfieldId' :: Proxy (M1 D t f) -> (Maybe Int, Int) Source #

Orphan instances