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

Torch.Typed.Factories

Synopsis

Documentation

zeros :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). TensorOptions shape dtype device => Tensor device dtype shape Source #

full :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)) a. (TensorOptions shape dtype device, Scalar a) => a -> Tensor device dtype shape Source #

ones :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). TensorOptions shape dtype device => Tensor device dtype shape Source #

type family RandDTypeIsValid (device :: (DeviceType, Nat)) (dtype :: DType) where ... Source #

Equations

RandDTypeIsValid '('CPU, 0) dtype = (DTypeIsNotBool '('CPU, 0) dtype, DTypeIsNotHalf '('CPU, 0) dtype) 
RandDTypeIsValid '('CUDA, _1) dtype = () 
RandDTypeIsValid '('MPS, 0) dtype = () 
RandDTypeIsValid '(deviceType, _1) dtype = UnsupportedDTypeForDevice deviceType dtype 

rand :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (TensorOptions shape dtype device, RandDTypeIsValid device dtype) => IO (Tensor device dtype shape) Source #

randn :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (TensorOptions shape dtype device, RandDTypeIsValid device dtype) => IO (Tensor device dtype shape) Source #

randint :: forall (shape :: [Nat]) (dtype :: DType) (device :: (DeviceType, Nat)). (TensorOptions shape dtype device, RandDTypeIsValid device dtype) => Int -> Int -> IO (Tensor device dtype shape) Source #

linspace Source #

Arguments

:: forall (steps :: Nat) (device :: (DeviceType, Nat)) start end. (Scalar start, Scalar end, KnownNat steps, TensorOptions '[steps] 'Float device) 
=> start

start

-> end

end

-> Tensor device 'Float '[steps]

output

linspace >>> dtype &&& shape &&& (t' -> D.asValue (toDynamic t') :: [Float]) $ linspace 7 '( 'D.CPU, 0) 0 3 (Float,([7],[0.0,0.5,1.0,1.5,2.0,2.5,3.0])) >>> dtype &&& shape &&& (t' -> D.asValue (toDynamic t') :: [Float]) $ linspace 3 '( 'D.CPU, 0) 0 2 (Float,([3],[0.0,1.0,2.0]))

eyeSquare Source #

Arguments

:: forall (n :: Nat) (dtype :: DType) (device :: (DeviceType, Nat)). (KnownNat n, TensorOptions '[n, n] dtype device) 
=> Tensor device dtype '[n, n]

output

Orphan instances

(TensorOptions shape' dtype device, shape' ~ ToNats shape) => Default (NamedTensor device dtype shape) Source # 
Instance details

Methods

def :: NamedTensor device dtype shape #

TensorOptions shape dtype device => Default (Tensor device dtype shape) Source # 
Instance details

Methods

def :: Tensor device dtype shape #