Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family ListLength (xs :: [k]) :: Nat where ...
- data family HList (xs :: [k])
- pattern (:.) :: forall x (xs :: [Type]). x -> HList xs -> HList (x ': xs)
- class Apply f a b where
- apply :: f -> a -> b
- class Apply' f a b | f a -> b where
- apply' :: f -> a -> b
- data AFst = AFst
- data ASnd = ASnd
- class HMap f (xs :: [k]) (ys :: [k]) where
- class HMap' f (xs :: [k]) (ys :: [k]) | f xs -> ys where
- class HMapM m f (xs :: [k]) (ys :: [k]) where
- class HMapM' m f (xs :: [k]) (ys :: [k]) | f xs -> ys where
- class Applicative f => HSequence f (xs :: [k]) (ys :: [k]) | xs -> ys, ys f -> xs where
- class HFoldr f acc xs res | f acc xs -> res where
- class HFoldrM m f acc xs res | m f acc xs -> res where
- data HNothing = HNothing
- newtype HJust x = HJust x
- class HUnfold f res xs where
- type family HUnfoldRes s xs where ...
- hunfoldr :: forall f res (xs :: [Type]) a. (Apply f a res, HUnfold f res xs, res ~ HUnfoldRes a xs) => f -> a -> HList xs
- class HUnfoldM m f res xs where
- hunfoldrM' :: f -> res -> m (HList xs)
- type family HUnfoldMRes m s xs where ...
- hunfoldrM :: forall (m :: Type -> Type) f res (xs :: [Type]) a. (HUnfoldM m f res xs, Apply f a res, res ~ HUnfoldMRes m a xs) => f -> a -> m (HList xs)
- type HReplicate n e = HReplicateFD n e (HReplicateR n e)
- hreplicate :: forall n e. HReplicate n e => e -> HList (HReplicateR n e)
- class HReplicateFD (n :: Nat) (e :: Type) (es :: [Type]) | n e -> es where
- hreplicateFD :: e -> HList es
- type family HReplicateR (n :: Nat) (e :: a) :: [a] where ...
- type HConcat xs = HConcatFD xs (HConcatR xs)
- hconcat :: HConcat xs => HList xs -> HList (HConcatR xs)
- type family HConcatR (a :: [Type]) :: [Type]
- type family UnHList a :: [Type]
- class HConcatFD (xxs :: [k]) (xs :: [k]) | xxs -> xs where
- type HAppend as bs = HAppendFD as bs (as ++ bs)
- happend :: HAppend as bs => HList as -> HList bs -> HList (as ++ bs)
- hunappend :: (cs ~ (as ++ bs), HAppend as bs) => HList cs -> (HList as, HList bs)
- class HAppendFD (a :: [k]) (b :: [k]) (ab :: [k]) | a b -> ab, a ab -> b where
- type family (as :: [k]) ++ (bs :: [k]) :: [k] where ...
- class HZip (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs, zs -> xs ys where
- class HZip' (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs where
- data HZipF = HZipF
- htranspose :: forall (acc :: [Type]) (xs :: [Type]) (xxs :: [Type]) (res :: Type). (HReplicateFD (ListLength xs) (HList ('[] :: [Type])) acc, HFoldr HZipF (HList acc) (HList xs ': xxs) res) => HList (HList xs ': xxs) -> res
- class HZipWith f (xs :: [k]) (ys :: [k]) (zs :: [k]) | f xs ys -> zs where
- class HZipWithM m f (xs :: [k]) (ys :: [k]) (zs :: [k]) | f xs ys -> zs where
- class HZip3 (as :: [k]) (bs :: [k]) (cs :: [k]) (ds :: [k]) | as bs cs -> ds, ds -> as bs cs where
- class HZipWith3 f (as :: [k]) (bs :: [k]) (cs :: [k]) (ds :: [k]) | f as bs cs -> ds where
- class HCartesianProduct (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs where
- class HAttach x (ys :: [k]) (zs :: [k]) | x ys -> zs where
Documentation
type family ListLength (xs :: [k]) :: Nat where ... Source #
ListLength '[] = 0 | |
ListLength (_h ': t) = 1 + ListLength t |
data family HList (xs :: [k]) Source #
Instances
class Apply f a b where Source #
Instances
Castable x ATenTensor => Apply TensorListUnfold [ATenTensor] (IO (HJust (x, [ATenTensor]))) Source # | |
Defined in Torch.Typed.Tensor apply :: TensorListUnfold -> [ATenTensor] -> IO (HJust (x, [ATenTensor])) Source # | |
Apply TensorListUnfold [ATenTensor] (IO HNothing) Source # | |
Defined in Torch.Typed.Tensor apply :: TensorListUnfold -> [ATenTensor] -> IO HNothing Source # |
class Apply' f a b | f a -> b where Source #
Stronger version of Apply
that allows for better inference of the return type
Instances
(HZip' a b c, x ~ (HList a, HList b), y ~ HList c) => Apply' HZipF x y Source # | |
Defined in Torch.HList | |
(momentum ~ Tensor device dtype shape, KnownDevice device, KnownDType dtype, shape ~ Reverse (Reverse shape), BasicArithmeticDTypeIsValid device dtype) => Apply' AdamBiasAdjustment momentum momentum Source # | bias adjustment |
Defined in Torch.Typed.Optim apply' :: AdamBiasAdjustment -> momentum -> momentum Source # | |
(parameter ~ Parameter device dtype shape, momentum ~ Tensor device dtype shape, TensorOptions shape dtype device) => Apply' ZerosLike parameter momentum Source # | |
Defined in Torch.Typed.Optim | |
Apply' AFst (a, b) a Source # | |
Defined in Torch.HList | |
Apply' ASnd (a, b) b Source # | |
Defined in Torch.HList | |
Num y => Apply' SumF (y, y) y Source # | |
Defined in Torch.Typed.NN.DataParallel | |
(gradient ~ Tensor device dtype shape, momentum1 ~ Tensor device dtype shape, KnownDevice device) => Apply' AdamMomentum1Update (momentum1, gradient) momentum1 Source # | decaying average of the first momenta |
Defined in Torch.Typed.Optim apply' :: AdamMomentum1Update -> (momentum1, gradient) -> momentum1 Source # | |
(gradient ~ Tensor device dtype shape, momentum2 ~ Tensor device dtype shape, shape ~ Broadcast shape shape, KnownDevice device, BasicArithmeticDTypeIsValid device dtype) => Apply' AdamMomentum2Update (momentum2, gradient) momentum2 Source # | decaying average of the second momenta |
Defined in Torch.Typed.Optim apply' :: AdamMomentum2Update -> (momentum2, gradient) -> momentum2 Source # | |
HasForward model input output => Apply' ForwardConcurrentlyF (model, input) (Concurrently output) Source # | |
Defined in Torch.Typed.NN.DataParallel apply' :: ForwardConcurrentlyF -> (model, input) -> Concurrently output Source # | |
(HasGrad (HList parameters) (HList gradients), Castable (HList gradients) [ATenTensor]) => Apply' GradConcurrentlyF (HList parameters, Loss device dtype) (Concurrently (HList gradients)) Source # | |
Defined in Torch.Typed.NN.DataParallel apply' :: GradConcurrentlyF -> (HList parameters, Loss device dtype) -> Concurrently (HList gradients) Source # | |
Castable x ATenTensor => Apply' TensorListFold (x, IO [ATenTensor]) (IO [ATenTensor]) Source # | |
Defined in Torch.Typed.Tensor apply' :: TensorListFold -> (x, IO [ATenTensor]) -> IO [ATenTensor] Source # | |
Apply' MakeIndependent (Tensor device dtype shape) (IO (Parameter device dtype shape)) Source # | |
Defined in Torch.Typed.Parameter | |
Apply' ToParameter (Tensor dev dtype shape) (Parameter dev dtype shape) Source # | |
Defined in Torch.Typed.Optim.CppOptim | |
Apply' ToDependent (Parameter device dtype shape) (Tensor device dtype shape) Source # | |
Defined in Torch.Typed.Parameter | |
(parameter ~ Tensor device dtype shape, gradient ~ Tensor device dtype shape, shape ~ Broadcast ('[] :: [Nat]) shape, BasicArithmeticDTypeIsValid device dtype, KnownDevice device) => Apply' (GDStep device dtype) (parameter, gradient) parameter Source # | |
Defined in Torch.Typed.Optim | |
(parameter ~ Tensor device dtype shape, momentum ~ Tensor device dtype shape, shape ~ Broadcast ('[] :: [Nat]) shape, KnownDevice device, BasicArithmeticDTypeIsValid device dtype, StandardFloatingPointDTypeValidation device dtype) => Apply' (AdamParameterUpdate device dtype) (parameter, momentum, momentum) parameter Source # | parameter update |
Defined in Torch.Typed.Optim apply' :: AdamParameterUpdate device dtype -> (parameter, momentum, momentum) -> parameter Source # | |
(parameter ~ Tensor device dtype shape, gradient ~ Tensor device dtype shape, momentum ~ Tensor device dtype shape, shape ~ Broadcast ('[] :: [Nat]) shape, KnownDevice device, BasicArithmeticDTypeIsValid device dtype) => Apply' (GDMStep device dtype) (parameter, gradient, momentum) (parameter, momentum) Source # | |
Defined in Torch.Typed.Optim | |
(1 <= numHeads, embedDim ~ (headDim * numHeads), All KnownNat '[embedDim, numHeads, seqLen, batchSize, headDim], IsSuffixOf '[embedDim] '[batchSize, seqLen, embedDim], KnownDType dtype, StandardFloatingPointDTypeValidation device dtype, MatMulDTypeIsValid device dtype, BasicArithmeticDTypeIsValid device dtype, dtype ~ SumDType dtype, SumDTypeIsValid device dtype, KnownDevice device) => Apply' (FoldLayers batchSize seqLen dtype device) (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device, IO (Tensor device dtype '[batchSize, seqLen, embedDim])) (IO (Tensor device dtype '[batchSize, seqLen, embedDim])) Source # | |
Defined in Torch.Typed.NN.Transformer apply' :: FoldLayers batchSize seqLen dtype device -> (TransformerLayer embedDim embedDim embedDim numHeads ffnDim dtype device, IO (Tensor device dtype '[batchSize, seqLen, embedDim])) -> IO (Tensor device dtype '[batchSize, seqLen, embedDim]) Source # |
class HMapM' m f (xs :: [k]) (ys :: [k]) | f xs -> ys where Source #
class Applicative f => HSequence f (xs :: [k]) (ys :: [k]) | xs -> ys, ys f -> xs where Source #
class HFoldrM m f acc xs res | m f acc xs -> res where Source #
Instances
HUnfold f HNothing ('[] :: [k]) Source # | |
Monad m => HUnfoldM m f (m HNothing) ('[] :: [k]) Source # | |
Defined in Torch.HList hunfoldrM' :: f -> m HNothing -> m (HList '[]) Source # | |
Apply TensorListUnfold [ATenTensor] (IO HNothing) Source # | |
Defined in Torch.Typed.Tensor apply :: TensorListUnfold -> [ATenTensor] -> IO HNothing Source # |
HJust x |
Instances
(Monad m, HUnfoldM m f res xs, Apply f s res, res ~ HUnfoldMRes m s xs) => HUnfoldM m f (m (HJust (x, s))) (x ': xs :: [Type]) Source # | |
Defined in Torch.HList hunfoldrM' :: f -> m (HJust (x, s)) -> m (HList (x ': xs)) Source # | |
(Apply f s res, HUnfold f res xs, res ~ HUnfoldRes s xs) => HUnfold f (HJust (x, s)) (x ': xs :: [Type]) Source # | |
Castable x ATenTensor => Apply TensorListUnfold [ATenTensor] (IO (HJust (x, [ATenTensor]))) Source # | |
Defined in Torch.Typed.Tensor apply :: TensorListUnfold -> [ATenTensor] -> IO (HJust (x, [ATenTensor])) Source # |
type family HUnfoldRes s xs where ... Source #
HUnfoldRes _ '[] = HNothing | |
HUnfoldRes s (x ': _) = HJust (x, s) |
hunfoldr :: forall f res (xs :: [Type]) a. (Apply f a res, HUnfold f res xs, res ~ HUnfoldRes a xs) => f -> a -> HList xs Source #
class HUnfoldM m f res xs where Source #
hunfoldrM' :: f -> res -> m (HList xs) Source #
Instances
Monad m => HUnfoldM m f (m HNothing) ('[] :: [k]) Source # | |
Defined in Torch.HList hunfoldrM' :: f -> m HNothing -> m (HList '[]) Source # | |
(Monad m, HUnfoldM m f res xs, Apply f s res, res ~ HUnfoldMRes m s xs) => HUnfoldM m f (m (HJust (x, s))) (x ': xs :: [Type]) Source # | |
Defined in Torch.HList hunfoldrM' :: f -> m (HJust (x, s)) -> m (HList (x ': xs)) Source # |
type family HUnfoldMRes m s xs where ... Source #
HUnfoldMRes m _ '[] = m HNothing | |
HUnfoldMRes m s (x ': _) = m (HJust (x, s)) |
hunfoldrM :: forall (m :: Type -> Type) f res (xs :: [Type]) a. (HUnfoldM m f res xs, Apply f a res, res ~ HUnfoldMRes m a xs) => f -> a -> m (HList xs) Source #
type HReplicate n e = HReplicateFD n e (HReplicateR n e) Source #
hreplicate :: forall n e. HReplicate n e => e -> HList (HReplicateR n e) Source #
class HReplicateFD (n :: Nat) (e :: Type) (es :: [Type]) | n e -> es where Source #
hreplicateFD :: e -> HList es Source #
Instances
(HReplicateFD (n - 1) e es, es' ~ (e ': es), 1 <= n) => HReplicateFD n e es' Source # | |
Defined in Torch.HList hreplicateFD :: e -> HList es' Source # | |
HReplicateFD 0 e ('[] :: [Type]) Source # | |
Defined in Torch.HList hreplicateFD :: e -> HList '[] Source # |
type family HReplicateR (n :: Nat) (e :: a) :: [a] where ... Source #
HReplicateR 0 _ = '[] | |
HReplicateR n e = e ': HReplicateR (n - 1) e |
class HAppendFD (a :: [k]) (b :: [k]) (ab :: [k]) | a b -> ab, a ab -> b where Source #
class HZip (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs, zs -> xs ys where Source #
class HZip' (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs where Source #
htranspose :: forall (acc :: [Type]) (xs :: [Type]) (xxs :: [Type]) (res :: Type). (HReplicateFD (ListLength xs) (HList ('[] :: [Type])) acc, HFoldr HZipF (HList acc) (HList xs ': xxs) res) => HList (HList xs ': xxs) -> res Source #
class HZipWith f (xs :: [k]) (ys :: [k]) (zs :: [k]) | f xs ys -> zs where Source #
class HZipWithM m f (xs :: [k]) (ys :: [k]) (zs :: [k]) | f xs ys -> zs where Source #
class HZip3 (as :: [k]) (bs :: [k]) (cs :: [k]) (ds :: [k]) | as bs cs -> ds, ds -> as bs cs where Source #
hzip3 :: HList as -> HList bs -> HList cs -> HList ds Source #
hunzip3 :: HList ds -> (HList as, HList bs, HList cs) Source #
class HZipWith3 f (as :: [k]) (bs :: [k]) (cs :: [k]) (ds :: [k]) | f as bs cs -> ds where Source #
class HCartesianProduct (xs :: [k]) (ys :: [k]) (zs :: [k]) | xs ys -> zs where Source #
Instances
HCartesianProduct ('[] :: [k]) (ys :: [k]) ('[] :: [k]) Source # | |
(HCartesianProduct xs ys zs, HAttach x ys xys, HAppendFD xys zs zs') => HCartesianProduct (x ': xs :: [Type]) (ys :: [Type]) (zs' :: [Type]) Source # | |