opencv-0.0.2.1: Haskell binding to OpenCV-3.x

Safe HaskellNone
LanguageHaskell2010

OpenCV.TypeLevel

Contents

Synopsis

Kinds and types

data DS a Source #

Dynamically or Statically known values

Mainly used as a promoted type.

Operationally exactly the Maybe type

Constructors

D

Something is dynamically known

S a

Something is statically known, in particular: a

Instances

Functor DS Source # 

Methods

fmap :: (a -> b) -> DS a -> DS b #

(<$) :: a -> DS b -> DS a #

Eq a => Eq (DS a) Source # 

Methods

(==) :: DS a -> DS a -> Bool #

(/=) :: DS a -> DS a -> Bool #

Show a => Show (DS a) Source # 

Methods

showsPrec :: Int -> DS a -> ShowS #

show :: DS a -> String #

showList :: [DS a] -> ShowS #

ToInt32 (Proxy a n) => ToNatDS (Proxy (DS a) (S a n)) Source #

type level numbers are statically known

Methods

toNatDS :: Proxy (DS a) (S a n) -> DS Int32 Source #

ToNatListDS (Proxy a as) => ToShapeDS (Proxy (DS a) (S a as)) Source # 

Methods

toShapeDS :: Proxy (DS a) (S a as) -> DS [DS Int32] Source #

dsToMaybe :: DS a -> Maybe a Source #

Converts a DS value to the corresponding Maybe value

data Z Source #

End of list

Constructors

Z 

Instances

data a ::: b infixr 5 Source #

Heterogeneous lists

Implemented as nested 2-tuples.

f :: Int ::: Bool ::: Char ::: Z
f = 3 ::: False ::: 'X' ::: Z

Constructors

a ::: b infixr 5 

Instances

(ToInt32 a, ToShape as) => ToShape ((:::) a as) Source #

fold over :::

Methods

toShape :: (a ::: as) -> Vector Int32 Source #

Type level to value level conversions

class ToInt32 a where Source #

Minimal complete definition

toInt32

Methods

toInt32 :: a -> Int32 Source #

Instances

ToInt32 Int32 Source #

value level: identity

Methods

toInt32 :: Int32 -> Int32 Source #

KnownNat n => ToInt32 (proxy n) Source #

type level: reify the known natural number n

Methods

toInt32 :: proxy n -> Int32 Source #

class ToNatDS a where Source #

Type level to value level conversion of numbers that are either Dynamically or Statically known.

toNatDS (Proxy ('S 42)) == S 42
toNatDS (Proxy 'D) == D

Minimal complete definition

toNatDS

Methods

toNatDS :: a -> DS Int32 Source #

Instances

ToNatDS (proxy (D a)) Source #

value level numbers are dynamically known

Methods

toNatDS :: proxy (D a) -> DS Int32 Source #

ToInt32 (Proxy a n) => ToNatDS (Proxy (DS a) (S a n)) Source #

type level numbers are statically known

Methods

toNatDS :: Proxy (DS a) (S a n) -> DS Int32 Source #

class ToNatListDS a where Source #

Minimal complete definition

toNatListDS

Methods

toNatListDS :: a -> [DS Int32] Source #

Instances

ToNatListDS (proxy ([] k)) Source # 

Methods

toNatListDS :: proxy [k] -> [DS Int32] Source #

(ToNatDS (Proxy a1 a2), ToNatListDS (Proxy [a1] as)) => ToNatListDS (Proxy [a1] ((:) a1 a2 as)) Source # 

Methods

toNatListDS :: Proxy [a1] ((a1 ': a2) as) -> [DS Int32] Source #

Type functions

type family Length (xs :: [a]) :: Nat where ... Source #

Equations

Length '[] = 0 
Length (_x ': xs) = 1 + Length xs 

type family Elem (e :: a) (xs :: [a]) :: Bool where ... Source #

Equations

Elem _e '[] = False 
Elem e (e ': _xs) = True 
Elem e (_x ': xs) = Elem e xs 

type family Relax (a :: DS ka) (b :: DS kb) :: Bool where ... Source #

Equations

Relax x D = True 
Relax (S (x ': xs)) (S (y ': ys)) = Relax x y && Relax (S xs) (S ys) 
Relax (S x) (S y) = Relax x y 
Relax x x = True 
Relax x y = False 

Predicates (constraints)

type In e xs = Elem e xs ~ True Source #

type MayRelax a b = Relax a b ~ True Source #

class All (p :: k -> Constraint) (xs :: [k]) Source #

Instances

All k p ([] k) Source # 
(p x, All a p xs) => All a p ((:) a x xs) Source # 

class PrivateIsStatic ds => IsStatic (ds :: DS a) Source #

Instances

IsStatic a1 (S a1 a2) Source # 

Type conversions

type family DSNat (a :: ka) :: DS Nat where ... Source #

Equations

DSNat Integer = D 
DSNat Int32 = D 
DSNat (Proxy n) = S n 
DSNat (n :: Nat) = S n 

type family DSNats (a :: ka) :: [DS Nat] where ... Source #

Equations

DSNats Z = '[] 
DSNats (x ::: xs) = DSNat x ': DSNats xs 
DSNats ('[] :: [Nat]) = '[] 
DSNats (x ': xs) = DSNat x ': DSNats xs