static-tensor-0.2.1.0: Tensors of statically known size

Copyright(C) 2017 Alexey Vagarenko
LicenseBSD-style (see LICENSE)
MaintainerAlexey Vagarenko (vagarenko@gmail.com)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Type.List

Description

 

Synopsis

Documentation

class KnownNats (ns :: [Nat]) where Source #

Demote type-level list of Nat.

Minimal complete definition

natsVal

Methods

natsVal :: [Int] Source #

Instances

KnownNats ([] Nat) Source # 

Methods

natsVal :: [Int] Source #

(KnownNat n, KnownNats ns) => KnownNats ((:) Nat n ns) Source # 

Methods

natsVal :: [Int] Source #

type family MkCtx (kx :: Type) (kctx :: Type) (ctx :: kctx) (x :: kx) :: Constraint where ... Source #

Make a constraint for type x :: kx from TyFun, or partially applied constraint, or make an empty constraint.

Equations

MkCtx kx (kx ~> Constraint) ctx x = Apply ctx x 
MkCtx kx (kx -> Constraint) ctx x = ctx x 
MkCtx _ Constraint () _ = () 
MkCtx _ Type () _ = () 

class DemoteWith (kx :: Type) (kctx :: Type) (ctx :: kctx) (xs :: [kx]) where Source #

Demote a type-level list to value-level list with a type-indexed function. The function takes list element as type parameter x and applies constraints ctx for that element.

Minimal complete definition

demoteWith

Methods

demoteWith :: (forall (x :: kx). MkCtx kx kctx ctx x => Proxy x -> a) -> [a] Source #

Instances

DemoteWith kx kctx ctxs ([] kx) Source # 

Methods

demoteWith :: (forall (x :: kx). MkCtx kx kctx ctxs x => Proxy kx x -> a) -> [a] Source #

(DemoteWith kx kctx ctx xs, MkCtx kx kctx ctx x) => DemoteWith kx kctx ctx ((:) kx x xs) Source # 

Methods

demoteWith :: (forall (a :: kx). MkCtx kx kctx ctx a => Proxy kx a -> a) -> [a] Source #