termonad-3.1.0.0: Terminal emulator configurable in Haskell
Copyright(c) Dennis Gosnell 2018
LicenseBSD3
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Termonad.Config.Vec

Description

This is a small library of dependent types. It provides indexed types like Fin, Vec, and Matrix.

This is mainly used in Termonad for Termonad.Config.Colour to represent length-indexed colour lists.

This module implements a subset of the functionality from the abandoned type-combinators library. Ideally this module would be split out to a separate package. If you're interested in working on something like this, please see this issue on Github.

Synopsis

Documentation

data Peano Source #

Constructors

Z 
S Peano 

Instances

Instances details
Eq Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(==) :: Peano -> Peano -> Bool #

(/=) :: Peano -> Peano -> Bool #

Num Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Ord Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

compare :: Peano -> Peano -> Ordering #

(<) :: Peano -> Peano -> Bool #

(<=) :: Peano -> Peano -> Bool #

(>) :: Peano -> Peano -> Bool #

(>=) :: Peano -> Peano -> Bool #

max :: Peano -> Peano -> Peano #

min :: Peano -> Peano -> Peano #

Show Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> Peano -> ShowS #

show :: Peano -> String #

showList :: [Peano] -> ShowS #

PShow Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type ShowsPrec arg0 arg1 arg2 :: Symbol #

type Show_ arg0 :: Symbol #

type ShowList arg0 arg1 :: Symbol #

SShow Peano => SShow Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: Peano) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: Peano). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [Peano]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

PNum Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type arg0 + arg1 :: a0 #

type arg0 - arg1 :: a0 #

type arg0 * arg1 :: a0 #

type Negate arg0 :: a0 #

type Abs arg0 :: a0 #

type Signum arg0 :: a0 #

type FromInteger arg0 :: a0 #

SNum Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(%+) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) #

(%-) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) #

(%*) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) #

sNegate :: forall (t :: Peano). Sing t -> Sing (Apply NegateSym0 t) #

sAbs :: forall (t :: Peano). Sing t -> Sing (Apply AbsSym0 t) #

sSignum :: forall (t :: Peano). Sing t -> Sing (Apply SignumSym0 t) #

sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) #

POrd Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Compare arg0 arg1 :: Ordering #

type arg0 < arg1 :: Bool #

type arg0 <= arg1 :: Bool #

type arg0 > arg1 :: Bool #

type arg0 >= arg1 :: Bool #

type Max arg0 arg1 :: a0 #

type Min arg0 arg1 :: a0 #

SOrd Peano => SOrd Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sCompare :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: Peano) (t2 :: Peano). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq Peano => SEq Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(%==) :: forall (a :: Peano) (b :: Peano). Sing a -> Sing b -> Sing (a == b) #

(%/=) :: forall (a :: Peano) (b :: Peano). Sing a -> Sing b -> Sing (a /= b) #

PEq Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

SDecide Peano => SDecide Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(%~) :: forall (a :: Peano) (b :: Peano). Sing a -> Sing b -> Decision (a :~: b) #

SingKind Peano Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Demote Peano = (r :: Type) #

Methods

fromSing :: forall (a :: Peano). Sing a -> Demote Peano #

toSing :: Demote Peano -> SomeSing Peano #

SDecide Peano => TestCoercion SPeano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

testCoercion :: forall (a :: k) (b :: k). SPeano a -> SPeano b -> Maybe (Coercion a b) #

SDecide Peano => TestEquality SPeano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

testEquality :: forall (a :: k) (b :: k). SPeano a -> SPeano b -> Maybe (a :~: b) #

SingI 'Z Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing 'Z #

SingI n => SingI ('S n :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing ('S n) #

Num a => Num (Matrix ('[] :: [Peano]) a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(+) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

(-) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

(*) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

negate :: Matrix '[] a -> Matrix '[] a #

abs :: Matrix '[] a -> Matrix '[] a #

signum :: Matrix '[] a -> Matrix '[] a #

fromInteger :: Integer -> Matrix '[] a #

SuppressUnusedWarnings FromInteger_6989586621679503106Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings ShowsPrec_6989586621679502503Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings Signum_6989586621679503100Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings Abs_6989586621679503091Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings Compare_6989586621679501810Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings TFHelper_6989586621679503076Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings TFHelper_6989586621679503060Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings TFHelper_6989586621679503044Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings AddPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings SubtractPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings MultPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI SSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing SSym0 #

SingI AddPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI SubtractPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI MultPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SuppressUnusedWarnings (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SingI d => SingI (AddPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing (AddPeanoSym1 d) #

SingI d => SingI (SubtractPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SingI d => SingI (MultPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing (MultPeanoSym1 d) #

type Sing Source # 
Instance details

Defined in Termonad.Config.Vec

type Sing = SPeano
type Demote Peano Source # 
Instance details

Defined in Termonad.Config.Vec

type Show_ (arg0 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Show_ (arg0 :: Peano) = Apply (Show__6989586621680590310Sym0 :: TyFun Peano Symbol -> Type) arg0
type FromInteger a Source # 
Instance details

Defined in Termonad.Config.Vec

type Signum (a :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Abs (a :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Negate (arg0 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Negate (arg0 :: Peano) = Apply (Negate_6989586621680020922Sym0 :: TyFun Peano Peano -> Type) arg0
type ShowList (arg0 :: [Peano]) arg1 Source # 
Instance details

Defined in Termonad.Config.Vec

type ShowList (arg0 :: [Peano]) arg1 = Apply (Apply (ShowList_6989586621680590318Sym0 :: TyFun [Peano] (Symbol ~> Symbol) -> Type) arg0) arg1
type (a1 :: Peano) * (a2 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (a1 :: Peano) * (a2 :: Peano) = Apply (Apply TFHelper_6989586621679503076Sym0 a1) a2
type (a1 :: Peano) - (a2 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (a1 :: Peano) - (a2 :: Peano) = Apply (Apply TFHelper_6989586621679503060Sym0 a1) a2
type (a1 :: Peano) + (a2 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (a1 :: Peano) + (a2 :: Peano) = Apply (Apply TFHelper_6989586621679503044Sym0 a1) a2
type Min (arg0 :: Peano) (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Min (arg0 :: Peano) (arg1 :: Peano) = Apply (Apply (Min_6989586621679805065Sym0 :: TyFun Peano (Peano ~> Peano) -> Type) arg0) arg1
type Max (arg0 :: Peano) (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Max (arg0 :: Peano) (arg1 :: Peano) = Apply (Apply (Max_6989586621679805047Sym0 :: TyFun Peano (Peano ~> Peano) -> Type) arg0) arg1
type (arg0 :: Peano) >= (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (arg0 :: Peano) >= (arg1 :: Peano) = Apply (Apply (TFHelper_6989586621679805029Sym0 :: TyFun Peano (Peano ~> Bool) -> Type) arg0) arg1
type (arg0 :: Peano) > (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (arg0 :: Peano) > (arg1 :: Peano) = Apply (Apply (TFHelper_6989586621679805011Sym0 :: TyFun Peano (Peano ~> Bool) -> Type) arg0) arg1
type (arg0 :: Peano) <= (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (arg0 :: Peano) <= (arg1 :: Peano) = Apply (Apply (TFHelper_6989586621679804993Sym0 :: TyFun Peano (Peano ~> Bool) -> Type) arg0) arg1
type (arg0 :: Peano) < (arg1 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (arg0 :: Peano) < (arg1 :: Peano) = Apply (Apply (TFHelper_6989586621679804975Sym0 :: TyFun Peano (Peano ~> Bool) -> Type) arg0) arg1
type Compare (a1 :: Peano) (a2 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (x :: Peano) /= (y :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (x :: Peano) /= (y :: Peano) = Not (x == y)
type (a :: Peano) == (b :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type (a :: Peano) == (b :: Peano) = Equals_6989586621679503122 a b
type ShowsPrec a1 (a2 :: Peano) a3 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply FromInteger_6989586621679503106Sym0 (a6989586621679503105 :: Nat) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply FromInteger_6989586621679503106Sym0 (a6989586621679503105 :: Nat) = FromInteger_6989586621679503106 a6989586621679503105
type Apply Signum_6989586621679503100Sym0 (a6989586621679503099 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Signum_6989586621679503100Sym0 (a6989586621679503099 :: Peano) = Signum_6989586621679503100 a6989586621679503099
type Apply Abs_6989586621679503091Sym0 (a6989586621679503090 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Abs_6989586621679503091Sym0 (a6989586621679503090 :: Peano) = Abs_6989586621679503091 a6989586621679503090
type Apply SSym0 (t6989586621679500065 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply SSym0 (t6989586621679500065 :: Peano) = 'S t6989586621679500065
type Apply (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) (a6989586621679501809 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) (a6989586621679501809 :: Peano) = Compare_6989586621679501810 a6989586621679501808 a6989586621679501809
type Apply (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) (a6989586621679503075 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) (a6989586621679503075 :: Peano) = TFHelper_6989586621679503076 a6989586621679503074 a6989586621679503075
type Apply (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) (a6989586621679503059 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) (a6989586621679503059 :: Peano) = TFHelper_6989586621679503060 a6989586621679503058 a6989586621679503059
type Apply (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) (a6989586621679503043 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) (a6989586621679503043 :: Peano) = TFHelper_6989586621679503044 a6989586621679503042 a6989586621679503043
type Apply (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) (a6989586621679500081 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) (a6989586621679500081 :: Peano) = AddPeano a6989586621679500080 a6989586621679500081
type Apply (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) (a6989586621679500074 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) (a6989586621679500074 :: Peano) = SubtractPeano a6989586621679500073 a6989586621679500074
type Apply (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) (a6989586621679500068 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) (a6989586621679500068 :: Peano) = MultPeano a6989586621679500067 a6989586621679500068
type Apply ShowsPrec_6989586621679502503Sym0 (a6989586621679502500 :: Nat) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply ShowsPrec_6989586621679502503Sym0 (a6989586621679502500 :: Nat) = ShowsPrec_6989586621679502503Sym1 a6989586621679502500
type Apply Compare_6989586621679501810Sym0 (a6989586621679501808 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Compare_6989586621679501810Sym0 (a6989586621679501808 :: Peano) = Compare_6989586621679501810Sym1 a6989586621679501808
type Apply TFHelper_6989586621679503076Sym0 (a6989586621679503074 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503076Sym0 (a6989586621679503074 :: Peano) = TFHelper_6989586621679503076Sym1 a6989586621679503074
type Apply TFHelper_6989586621679503060Sym0 (a6989586621679503058 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503060Sym0 (a6989586621679503058 :: Peano) = TFHelper_6989586621679503060Sym1 a6989586621679503058
type Apply TFHelper_6989586621679503044Sym0 (a6989586621679503042 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503044Sym0 (a6989586621679503042 :: Peano) = TFHelper_6989586621679503044Sym1 a6989586621679503042
type Apply AddPeanoSym0 (a6989586621679500080 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply AddPeanoSym0 (a6989586621679500080 :: Peano) = AddPeanoSym1 a6989586621679500080
type Apply SubtractPeanoSym0 (a6989586621679500073 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply SubtractPeanoSym0 (a6989586621679500073 :: Peano) = SubtractPeanoSym1 a6989586621679500073
type Apply MultPeanoSym0 (a6989586621679500067 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply MultPeanoSym0 (a6989586621679500067 :: Peano) = MultPeanoSym1 a6989586621679500067
type Apply (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) (a6989586621679502501 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) (a6989586621679502501 :: Peano) = ShowsPrec_6989586621679502503Sym2 a6989586621679502500 a6989586621679502501
type Apply MatrixTFSym0 (l :: [Peano]) Source # 
Instance details

Defined in Termonad.Config.Vec

type ZSym0 = Z Source #

type SSym1 (t6989586621679500065 :: Peano) = S t6989586621679500065 Source #

data SSym0 :: (~>) Peano Peano where Source #

Constructors

SSym0KindInference :: forall t6989586621679500065 arg. SameKind (Apply SSym0 arg) (SSym1 arg) => SSym0 t6989586621679500065 

Instances

Instances details
SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI SSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing SSym0 #

type Apply SSym0 (t6989586621679500065 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply SSym0 (t6989586621679500065 :: Peano) = 'S t6989586621679500065

type family N0 :: Peano where ... Source #

Equations

N0 = ZSym0 

type N0Sym0 = N0 Source #

type family N1 :: Peano where ... Source #

Equations

N1 = Apply SSym0 N0Sym0 

type N1Sym0 = N1 Source #

type family N2 :: Peano where ... Source #

Equations

N2 = Apply SSym0 N1Sym0 

type N2Sym0 = N2 Source #

type family N3 :: Peano where ... Source #

Equations

N3 = Apply SSym0 N2Sym0 

type N3Sym0 = N3 Source #

type family N4 :: Peano where ... Source #

Equations

N4 = Apply SSym0 N3Sym0 

type N4Sym0 = N4 Source #

type family N5 :: Peano where ... Source #

Equations

N5 = Apply SSym0 N4Sym0 

type N5Sym0 = N5 Source #

type family N6 :: Peano where ... Source #

Equations

N6 = Apply SSym0 N5Sym0 

type N6Sym0 = N6 Source #

type family N7 :: Peano where ... Source #

Equations

N7 = Apply SSym0 N6Sym0 

type N7Sym0 = N7 Source #

type family N8 :: Peano where ... Source #

Equations

N8 = Apply SSym0 N7Sym0 

type N8Sym0 = N8 Source #

type family N9 :: Peano where ... Source #

Equations

N9 = Apply SSym0 N8Sym0 

type N9Sym0 = N9 Source #

type family N10 :: Peano where ... Source #

Equations

N10 = Apply SSym0 N9Sym0 

type family SubtractPeano (a :: Peano) (a :: Peano) :: Peano where ... Source #

data SubtractPeanoSym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Constructors

SubtractPeanoSym0KindInference :: forall a6989586621679500073 arg. SameKind (Apply SubtractPeanoSym0 arg) (SubtractPeanoSym1 arg) => SubtractPeanoSym0 a6989586621679500073 

Instances

Instances details
SuppressUnusedWarnings SubtractPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI SubtractPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply SubtractPeanoSym0 (a6989586621679500073 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply SubtractPeanoSym0 (a6989586621679500073 :: Peano) = SubtractPeanoSym1 a6989586621679500073

data SubtractPeanoSym1 (a6989586621679500073 :: Peano) :: (~>) Peano Peano where Source #

Constructors

SubtractPeanoSym1KindInference :: forall a6989586621679500073 a6989586621679500074 arg. SameKind (Apply (SubtractPeanoSym1 a6989586621679500073) arg) (SubtractPeanoSym2 a6989586621679500073 arg) => SubtractPeanoSym1 a6989586621679500073 a6989586621679500074 

Instances

Instances details
SuppressUnusedWarnings (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SingI d => SingI (SubtractPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) (a6989586621679500074 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (SubtractPeanoSym1 a6989586621679500073 :: TyFun Peano Peano -> Type) (a6989586621679500074 :: Peano) = SubtractPeano a6989586621679500073 a6989586621679500074

type SubtractPeanoSym2 (a6989586621679500073 :: Peano) (a6989586621679500074 :: Peano) = SubtractPeano a6989586621679500073 a6989586621679500074 Source #

type family AddPeano (a :: Peano) (a :: Peano) :: Peano where ... Source #

Equations

AddPeano Z a = a 
AddPeano (S a) b = Apply SSym0 (Apply (Apply AddPeanoSym0 a) b) 

data AddPeanoSym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Constructors

AddPeanoSym0KindInference :: forall a6989586621679500080 arg. SameKind (Apply AddPeanoSym0 arg) (AddPeanoSym1 arg) => AddPeanoSym0 a6989586621679500080 

Instances

Instances details
SuppressUnusedWarnings AddPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI AddPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply AddPeanoSym0 (a6989586621679500080 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply AddPeanoSym0 (a6989586621679500080 :: Peano) = AddPeanoSym1 a6989586621679500080

data AddPeanoSym1 (a6989586621679500080 :: Peano) :: (~>) Peano Peano where Source #

Constructors

AddPeanoSym1KindInference :: forall a6989586621679500080 a6989586621679500081 arg. SameKind (Apply (AddPeanoSym1 a6989586621679500080) arg) (AddPeanoSym2 a6989586621679500080 arg) => AddPeanoSym1 a6989586621679500080 a6989586621679500081 

Instances

Instances details
SuppressUnusedWarnings (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SingI d => SingI (AddPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing (AddPeanoSym1 d) #

type Apply (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) (a6989586621679500081 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (AddPeanoSym1 a6989586621679500080 :: TyFun Peano Peano -> Type) (a6989586621679500081 :: Peano) = AddPeano a6989586621679500080 a6989586621679500081

type AddPeanoSym2 (a6989586621679500080 :: Peano) (a6989586621679500081 :: Peano) = AddPeano a6989586621679500080 a6989586621679500081 Source #

type family MultPeano (a :: Peano) (a :: Peano) :: Peano where ... Source #

data MultPeanoSym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Constructors

MultPeanoSym0KindInference :: forall a6989586621679500067 arg. SameKind (Apply MultPeanoSym0 arg) (MultPeanoSym1 arg) => MultPeanoSym0 a6989586621679500067 

Instances

Instances details
SuppressUnusedWarnings MultPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

SingI MultPeanoSym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply MultPeanoSym0 (a6989586621679500067 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply MultPeanoSym0 (a6989586621679500067 :: Peano) = MultPeanoSym1 a6989586621679500067

data MultPeanoSym1 (a6989586621679500067 :: Peano) :: (~>) Peano Peano where Source #

Constructors

MultPeanoSym1KindInference :: forall a6989586621679500067 a6989586621679500068 arg. SameKind (Apply (MultPeanoSym1 a6989586621679500067) arg) (MultPeanoSym2 a6989586621679500067 arg) => MultPeanoSym1 a6989586621679500067 a6989586621679500068 

Instances

Instances details
SuppressUnusedWarnings (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

SingI d => SingI (MultPeanoSym1 d :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing (MultPeanoSym1 d) #

type Apply (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) (a6989586621679500068 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (MultPeanoSym1 a6989586621679500067 :: TyFun Peano Peano -> Type) (a6989586621679500068 :: Peano) = MultPeano a6989586621679500067 a6989586621679500068

type MultPeanoSym2 (a6989586621679500067 :: Peano) (a6989586621679500068 :: Peano) = MultPeano a6989586621679500067 a6989586621679500068 Source #

type family N24 :: Peano where ... Source #

type family Compare_6989586621679501810 (a :: Peano) (a :: Peano) :: Ordering where ... Source #

Equations

Compare_6989586621679501810 Z Z = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] 
Compare_6989586621679501810 (S a_6989586621679500055) (S b_6989586621679500057) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_6989586621679500055) b_6989586621679500057)) '[]) 
Compare_6989586621679501810 Z (S _) = LTSym0 
Compare_6989586621679501810 (S _) Z = GTSym0 

type Compare_6989586621679501810Sym2 (a6989586621679501808 :: Peano) (a6989586621679501809 :: Peano) = Compare_6989586621679501810 a6989586621679501808 a6989586621679501809 Source #

data Compare_6989586621679501810Sym1 (a6989586621679501808 :: Peano) :: (~>) Peano Ordering where Source #

Constructors

Compare_6989586621679501810Sym1KindInference :: forall a6989586621679501808 a6989586621679501809 arg. SameKind (Apply (Compare_6989586621679501810Sym1 a6989586621679501808) arg) (Compare_6989586621679501810Sym2 a6989586621679501808 arg) => Compare_6989586621679501810Sym1 a6989586621679501808 a6989586621679501809 

Instances

Instances details
SuppressUnusedWarnings (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) (a6989586621679501809 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (Compare_6989586621679501810Sym1 a6989586621679501808 :: TyFun Peano Ordering -> Type) (a6989586621679501809 :: Peano) = Compare_6989586621679501810 a6989586621679501808 a6989586621679501809

data Compare_6989586621679501810Sym0 :: (~>) Peano ((~>) Peano Ordering) where Source #

Instances

Instances details
SuppressUnusedWarnings Compare_6989586621679501810Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Compare_6989586621679501810Sym0 (a6989586621679501808 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Compare_6989586621679501810Sym0 (a6989586621679501808 :: Peano) = Compare_6989586621679501810Sym1 a6989586621679501808

type family ShowsPrec_6989586621679502503 (a :: Nat) (a :: Peano) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679502503 _ Z a_6989586621679502511 = Apply (Apply ShowStringSym0 (FromString "Z")) a_6989586621679502511 
ShowsPrec_6989586621679502503 p_6989586621679500059 (S arg_6989586621679500061) a_6989586621679502513 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_6989586621679500059) (FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 (FromString "S "))) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_6989586621679500061))) a_6989586621679502513 

type ShowsPrec_6989586621679502503Sym3 (a6989586621679502500 :: Nat) (a6989586621679502501 :: Peano) (a6989586621679502502 :: Symbol) = ShowsPrec_6989586621679502503 a6989586621679502500 a6989586621679502501 a6989586621679502502 Source #

data ShowsPrec_6989586621679502503Sym2 (a6989586621679502500 :: Nat) (a6989586621679502501 :: Peano) :: (~>) Symbol Symbol where Source #

Constructors

ShowsPrec_6989586621679502503Sym2KindInference :: forall a6989586621679502500 a6989586621679502501 a6989586621679502502 arg. SameKind (Apply (ShowsPrec_6989586621679502503Sym2 a6989586621679502500 a6989586621679502501) arg) (ShowsPrec_6989586621679502503Sym3 a6989586621679502500 a6989586621679502501 arg) => ShowsPrec_6989586621679502503Sym2 a6989586621679502500 a6989586621679502501 a6989586621679502502 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679502503Sym2 a6989586621679502501 a6989586621679502500 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (ShowsPrec_6989586621679502503Sym2 a6989586621679502501 a6989586621679502500 :: TyFun Symbol Symbol -> Type) (a6989586621679502502 :: Symbol) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (ShowsPrec_6989586621679502503Sym2 a6989586621679502501 a6989586621679502500 :: TyFun Symbol Symbol -> Type) (a6989586621679502502 :: Symbol) = ShowsPrec_6989586621679502503 a6989586621679502501 a6989586621679502500 a6989586621679502502

data ShowsPrec_6989586621679502503Sym1 (a6989586621679502500 :: Nat) :: (~>) Peano ((~>) Symbol Symbol) where Source #

Constructors

ShowsPrec_6989586621679502503Sym1KindInference :: forall a6989586621679502500 a6989586621679502501 arg. SameKind (Apply (ShowsPrec_6989586621679502503Sym1 a6989586621679502500) arg) (ShowsPrec_6989586621679502503Sym2 a6989586621679502500 arg) => ShowsPrec_6989586621679502503Sym1 a6989586621679502500 a6989586621679502501 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) (a6989586621679502501 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (ShowsPrec_6989586621679502503Sym1 a6989586621679502500 :: TyFun Peano (Symbol ~> Symbol) -> Type) (a6989586621679502501 :: Peano) = ShowsPrec_6989586621679502503Sym2 a6989586621679502500 a6989586621679502501

type family TFHelper_6989586621679503044 (a :: Peano) (a :: Peano) :: Peano where ... Source #

Equations

TFHelper_6989586621679503044 a_6989586621679503046 a_6989586621679503048 = Apply (Apply AddPeanoSym0 a_6989586621679503046) a_6989586621679503048 

type TFHelper_6989586621679503044Sym2 (a6989586621679503042 :: Peano) (a6989586621679503043 :: Peano) = TFHelper_6989586621679503044 a6989586621679503042 a6989586621679503043 Source #

data TFHelper_6989586621679503044Sym1 (a6989586621679503042 :: Peano) :: (~>) Peano Peano where Source #

Constructors

TFHelper_6989586621679503044Sym1KindInference :: forall a6989586621679503042 a6989586621679503043 arg. SameKind (Apply (TFHelper_6989586621679503044Sym1 a6989586621679503042) arg) (TFHelper_6989586621679503044Sym2 a6989586621679503042 arg) => TFHelper_6989586621679503044Sym1 a6989586621679503042 a6989586621679503043 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) (a6989586621679503043 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503044Sym1 a6989586621679503042 :: TyFun Peano Peano -> Type) (a6989586621679503043 :: Peano) = TFHelper_6989586621679503044 a6989586621679503042 a6989586621679503043

data TFHelper_6989586621679503044Sym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Instances

Instances details
SuppressUnusedWarnings TFHelper_6989586621679503044Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503044Sym0 (a6989586621679503042 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503044Sym0 (a6989586621679503042 :: Peano) = TFHelper_6989586621679503044Sym1 a6989586621679503042

type family TFHelper_6989586621679503060 (a :: Peano) (a :: Peano) :: Peano where ... Source #

Equations

TFHelper_6989586621679503060 a_6989586621679503062 a_6989586621679503064 = Apply (Apply SubtractPeanoSym0 a_6989586621679503062) a_6989586621679503064 

type TFHelper_6989586621679503060Sym2 (a6989586621679503058 :: Peano) (a6989586621679503059 :: Peano) = TFHelper_6989586621679503060 a6989586621679503058 a6989586621679503059 Source #

data TFHelper_6989586621679503060Sym1 (a6989586621679503058 :: Peano) :: (~>) Peano Peano where Source #

Constructors

TFHelper_6989586621679503060Sym1KindInference :: forall a6989586621679503058 a6989586621679503059 arg. SameKind (Apply (TFHelper_6989586621679503060Sym1 a6989586621679503058) arg) (TFHelper_6989586621679503060Sym2 a6989586621679503058 arg) => TFHelper_6989586621679503060Sym1 a6989586621679503058 a6989586621679503059 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) (a6989586621679503059 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503060Sym1 a6989586621679503058 :: TyFun Peano Peano -> Type) (a6989586621679503059 :: Peano) = TFHelper_6989586621679503060 a6989586621679503058 a6989586621679503059

data TFHelper_6989586621679503060Sym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Instances

Instances details
SuppressUnusedWarnings TFHelper_6989586621679503060Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503060Sym0 (a6989586621679503058 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503060Sym0 (a6989586621679503058 :: Peano) = TFHelper_6989586621679503060Sym1 a6989586621679503058

type family TFHelper_6989586621679503076 (a :: Peano) (a :: Peano) :: Peano where ... Source #

Equations

TFHelper_6989586621679503076 a_6989586621679503078 a_6989586621679503080 = Apply (Apply MultPeanoSym0 a_6989586621679503078) a_6989586621679503080 

type TFHelper_6989586621679503076Sym2 (a6989586621679503074 :: Peano) (a6989586621679503075 :: Peano) = TFHelper_6989586621679503076 a6989586621679503074 a6989586621679503075 Source #

data TFHelper_6989586621679503076Sym1 (a6989586621679503074 :: Peano) :: (~>) Peano Peano where Source #

Constructors

TFHelper_6989586621679503076Sym1KindInference :: forall a6989586621679503074 a6989586621679503075 arg. SameKind (Apply (TFHelper_6989586621679503076Sym1 a6989586621679503074) arg) (TFHelper_6989586621679503076Sym2 a6989586621679503074 arg) => TFHelper_6989586621679503076Sym1 a6989586621679503074 a6989586621679503075 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) (a6989586621679503075 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (TFHelper_6989586621679503076Sym1 a6989586621679503074 :: TyFun Peano Peano -> Type) (a6989586621679503075 :: Peano) = TFHelper_6989586621679503076 a6989586621679503074 a6989586621679503075

data TFHelper_6989586621679503076Sym0 :: (~>) Peano ((~>) Peano Peano) where Source #

Instances

Instances details
SuppressUnusedWarnings TFHelper_6989586621679503076Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503076Sym0 (a6989586621679503074 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply TFHelper_6989586621679503076Sym0 (a6989586621679503074 :: Peano) = TFHelper_6989586621679503076Sym1 a6989586621679503074

type family Abs_6989586621679503091 (a :: Peano) :: Peano where ... Source #

Equations

Abs_6989586621679503091 a_6989586621679503093 = Apply IdSym0 a_6989586621679503093 

type Abs_6989586621679503091Sym1 (a6989586621679503090 :: Peano) = Abs_6989586621679503091 a6989586621679503090 Source #

data Abs_6989586621679503091Sym0 :: (~>) Peano Peano where Source #

Constructors

Abs_6989586621679503091Sym0KindInference :: forall a6989586621679503090 arg. SameKind (Apply Abs_6989586621679503091Sym0 arg) (Abs_6989586621679503091Sym1 arg) => Abs_6989586621679503091Sym0 a6989586621679503090 

Instances

Instances details
SuppressUnusedWarnings Abs_6989586621679503091Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Abs_6989586621679503091Sym0 (a6989586621679503090 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Abs_6989586621679503091Sym0 (a6989586621679503090 :: Peano) = Abs_6989586621679503091 a6989586621679503090

type Signum_6989586621679503100Sym1 (a6989586621679503099 :: Peano) = Signum_6989586621679503100 a6989586621679503099 Source #

data Signum_6989586621679503100Sym0 :: (~>) Peano Peano where Source #

Instances

Instances details
SuppressUnusedWarnings Signum_6989586621679503100Sym0 Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Signum_6989586621679503100Sym0 (a6989586621679503099 :: Peano) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply Signum_6989586621679503100Sym0 (a6989586621679503099 :: Peano) = Signum_6989586621679503100 a6989586621679503099

type FromInteger_6989586621679503106Sym1 (a6989586621679503105 :: Nat) = FromInteger_6989586621679503106 a6989586621679503105 Source #

data SPeano :: Peano -> Type where Source #

Constructors

SZ :: SPeano Z 
SS :: forall (n :: Peano). (Sing (n :: Peano)) -> SPeano (S n) 

Instances

Instances details
SDecide Peano => TestCoercion SPeano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

testCoercion :: forall (a :: k) (b :: k). SPeano a -> SPeano b -> Maybe (Coercion a b) #

SDecide Peano => TestEquality SPeano Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

testEquality :: forall (a :: k) (b :: k). SPeano a -> SPeano b -> Maybe (a :~: b) #

ShowSing Peano => Show (SPeano z) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> SPeano z -> ShowS #

show :: SPeano z -> String #

showList :: [SPeano z] -> ShowS #

sAddPeano :: forall (t :: Peano) (t :: Peano). Sing t -> Sing t -> Sing (Apply (Apply AddPeanoSym0 t) t :: Peano) Source #

sSubtractPeano :: forall (t :: Peano) (t :: Peano). Sing t -> Sing t -> Sing (Apply (Apply SubtractPeanoSym0 t) t :: Peano) Source #

sMultPeano :: forall (t :: Peano) (t :: Peano). Sing t -> Sing t -> Sing (Apply (Apply MultPeanoSym0 t) t :: Peano) Source #

ltSuccProof :: forall (n :: Peano) (m :: Peano) proxy. ('S n < 'S m) ~ 'True => proxy n -> proxy m -> (n < m) :~: 'True Source #

This is a proof that if we know S n is less than S m, then we know n is also less than m.

>>> ltSuccProof (sing :: Sing N4) (sing :: Sing N5)
Refl

data Fin :: Peano -> Type where Source #

Constructors

FZ :: forall (n :: Peano). Fin ('S n) 
FS :: forall (n :: Peano). !(Fin n) -> Fin ('S n) 

Instances

Instances details
Eq (Fin n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(==) :: Fin n -> Fin n -> Bool #

(/=) :: Fin n -> Fin n -> Bool #

Ord (Fin n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

compare :: Fin n -> Fin n -> Ordering #

(<) :: Fin n -> Fin n -> Bool #

(<=) :: Fin n -> Fin n -> Bool #

(>) :: Fin n -> Fin n -> Bool #

(>=) :: Fin n -> Fin n -> Bool #

max :: Fin n -> Fin n -> Fin n #

min :: Fin n -> Fin n -> Fin n #

Show (Fin n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> Fin n -> ShowS #

show :: Fin n -> String #

showList :: [Fin n] -> ShowS #

SingKind (Fin n) Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Demote (Fin n) = (r :: Type) #

Methods

fromSing :: forall (a :: Fin n). Sing a -> Demote (Fin n) #

toSing :: Demote (Fin n) -> SomeSing (Fin n) #

SingI ('FZ :: Fin ('S n)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing 'FZ #

SingI n2 => SingI ('FS n2 :: Fin ('S n1)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing ('FS n2) #

type Sing Source # 
Instance details

Defined in Termonad.Config.Vec

type Sing = SFin :: Fin n -> Type
type Demote (Fin n) Source # 
Instance details

Defined in Termonad.Config.Vec

type Demote (Fin n) = Fin n

fin :: forall total n. (n < total) ~ 'True => Sing total -> Sing n -> Fin total Source #

Similar to ifin but for Fin.

>>> fin (sing :: Sing N5) (sing :: Sing N1) :: Fin N5
FS FZ

fin_ :: forall total n. (SingI total, (n < total) ~ 'True) => Sing n -> Fin total Source #

Similar to ifin_ but for Fin.

>>> fin_ @N4 (sing :: Sing N2) :: Fin N4
FS (FS FZ)

data SFin :: forall n. Fin n -> Type where Source #

Constructors

SFZ :: SFin 'FZ 
SFS :: SFin n -> SFin ('FS n) 

Instances

Instances details
Show (SFin n2) => Show (SFin ('FS n2)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> SFin ('FS n2) -> ShowS #

show :: SFin ('FS n2) -> String #

showList :: [SFin ('FS n2)] -> ShowS #

Show (SFin ('FZ :: Fin ('S n))) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> SFin 'FZ -> ShowS #

show :: SFin 'FZ -> String #

showList :: [SFin 'FZ] -> ShowS #

data IFin :: Peano -> Peano -> Type where Source #

Constructors

IFZ :: forall (n :: Peano). IFin ('S n) 'Z 
IFS :: forall (n :: Peano) (m :: Peano). !(IFin n m) -> IFin ('S n) ('S m) 

Instances

Instances details
Eq (IFin x y) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(==) :: IFin x y -> IFin x y -> Bool #

(/=) :: IFin x y -> IFin x y -> Bool #

Ord (IFin x y) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

compare :: IFin x y -> IFin x y -> Ordering #

(<) :: IFin x y -> IFin x y -> Bool #

(<=) :: IFin x y -> IFin x y -> Bool #

(>) :: IFin x y -> IFin x y -> Bool #

(>=) :: IFin x y -> IFin x y -> Bool #

max :: IFin x y -> IFin x y -> IFin x y #

min :: IFin x y -> IFin x y -> IFin x y #

Show (IFin x y) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> IFin x y -> ShowS #

show :: IFin x y -> String #

showList :: [IFin x y] -> ShowS #

SingKind (IFin n m) Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Demote (IFin n m) = (r :: Type) #

Methods

fromSing :: forall (a :: IFin n m). Sing a -> Demote (IFin n m) #

toSing :: Demote (IFin n m) -> SomeSing (IFin n m) #

SingI ('IFZ :: IFin ('S n) 'Z) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing 'IFZ #

SingI n2 => SingI ('IFS n2 :: IFin ('S n1) ('S m)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

sing :: Sing ('IFS n2) #

type Sing Source # 
Instance details

Defined in Termonad.Config.Vec

type Sing = SIFin :: IFin n m -> Type
type Demote (IFin n m) Source # 
Instance details

Defined in Termonad.Config.Vec

type Demote (IFin n m) = IFin n m

toFinIFin :: IFin n m -> Fin n Source #

ifin :: forall total n. (n < total) ~ 'True => Sing total -> Sing n -> IFin total n Source #

Create an IFin.

>>> ifin (sing :: Sing N5) (sing :: Sing N2) :: IFin N5 N2
IFS (IFS IFZ)

ifin_ :: forall total n. (SingI total, (n < total) ~ 'True) => Sing n -> IFin total n Source #

Create an IFin, but take the total implicitly.

>>> ifin_ @N5 (sing :: Sing N3) :: IFin N5 N3
IFS (IFS (IFS IFZ))

data SIFin :: forall n m. IFin n m -> Type where Source #

Constructors

SIFZ :: SIFin 'IFZ 
SIFS :: SIFin x -> SIFin ('IFS x) 

Instances

Instances details
Show (SIFin n2) => Show (SIFin ('IFS n2)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> SIFin ('IFS n2) -> ShowS #

show :: SIFin ('IFS n2) -> String #

showList :: [SIFin ('IFS n2)] -> ShowS #

Show (SIFin ('IFZ :: IFin ('S n) 'Z)) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> SIFin 'IFZ -> ShowS #

show :: SIFin 'IFZ -> String #

showList :: [SIFin 'IFZ] -> ShowS #

data HList :: (k -> Type) -> [k] -> Type where Source #

Constructors

EmptyHList :: HList f '[] 
(:<) :: forall (f :: k -> Type) (a :: k) (as :: [k]). f a -> HList f as -> HList f (a ': as) infixr 6 

pattern ConsHList :: (f a :: Type) -> HList f as -> HList f (a ': as) Source #

Data constructor for :<.

data Vec (n :: Peano) :: Type -> Type where Source #

Constructors

EmptyVec :: Vec 'Z a 
(:*) :: !a -> !(Vec n a) -> Vec ('S n) a infixr 6 

Instances

Instances details
SingI n => Monad (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(>>=) :: Vec n a -> (a -> Vec n b) -> Vec n b #

(>>) :: Vec n a -> Vec n b -> Vec n b #

return :: a -> Vec n a #

Functor (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

fmap :: (a -> b) -> Vec n a -> Vec n b #

(<$) :: a -> Vec n b -> Vec n a #

SingI n => Applicative (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

pure :: a -> Vec n a #

(<*>) :: Vec n (a -> b) -> Vec n a -> Vec n b #

liftA2 :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c #

(*>) :: Vec n a -> Vec n b -> Vec n b #

(<*) :: Vec n a -> Vec n b -> Vec n a #

Foldable (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

fold :: Monoid m => Vec n m -> m #

foldMap :: Monoid m => (a -> m) -> Vec n a -> m #

foldMap' :: Monoid m => (a -> m) -> Vec n a -> m #

foldr :: (a -> b -> b) -> b -> Vec n a -> b #

foldr' :: (a -> b -> b) -> b -> Vec n a -> b #

foldl :: (b -> a -> b) -> b -> Vec n a -> b #

foldl' :: (b -> a -> b) -> b -> Vec n a -> b #

foldr1 :: (a -> a -> a) -> Vec n a -> a #

foldl1 :: (a -> a -> a) -> Vec n a -> a #

toList :: Vec n a -> [a] #

null :: Vec n a -> Bool #

length :: Vec n a -> Int #

elem :: Eq a => a -> Vec n a -> Bool #

maximum :: Ord a => Vec n a -> a #

minimum :: Ord a => Vec n a -> a #

sum :: Num a => Vec n a -> a #

product :: Num a => Vec n a -> a #

SingI n => Distributive (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

distribute :: Functor f => f (Vec n a) -> Vec n (f a) #

collect :: Functor f => (a -> Vec n b) -> f a -> Vec n (f b) #

distributeM :: Monad m => m (Vec n a) -> Vec n (m a) #

collectM :: Monad m => (a -> Vec n b) -> m a -> Vec n (m b) #

SingI n => Representable (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Rep (Vec n) #

Methods

tabulate :: (Rep (Vec n) -> a) -> Vec n a #

index :: Vec n a -> Rep (Vec n) -> a #

Eq a => Eq (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

Ord a => Ord (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

compare :: Vec n a -> Vec n a -> Ordering #

(<) :: Vec n a -> Vec n a -> Bool #

(<=) :: Vec n a -> Vec n a -> Bool #

(>) :: Vec n a -> Vec n a -> Bool #

(>=) :: Vec n a -> Vec n a -> Bool #

max :: Vec n a -> Vec n a -> Vec n a #

min :: Vec n a -> Vec n a -> Vec n a #

Show a => Show (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

SingI n => MonoPointed (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

opoint :: Element (Vec n a) -> Vec n a #

MonoFoldable (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

ofoldMap :: Monoid m => (Element (Vec n a) -> m) -> Vec n a -> m #

ofoldr :: (Element (Vec n a) -> b -> b) -> b -> Vec n a -> b #

ofoldl' :: (a0 -> Element (Vec n a) -> a0) -> a0 -> Vec n a -> a0 #

otoList :: Vec n a -> [Element (Vec n a)] #

oall :: (Element (Vec n a) -> Bool) -> Vec n a -> Bool #

oany :: (Element (Vec n a) -> Bool) -> Vec n a -> Bool #

onull :: Vec n a -> Bool #

olength :: Vec n a -> Int #

olength64 :: Vec n a -> Int64 #

ocompareLength :: Integral i => Vec n a -> i -> Ordering #

otraverse_ :: Applicative f => (Element (Vec n a) -> f b) -> Vec n a -> f () #

ofor_ :: Applicative f => Vec n a -> (Element (Vec n a) -> f b) -> f () #

omapM_ :: Applicative m => (Element (Vec n a) -> m ()) -> Vec n a -> m () #

oforM_ :: Applicative m => Vec n a -> (Element (Vec n a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (Vec n a) -> m a0) -> a0 -> Vec n a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (Vec n a) -> m) -> Vec n a -> m #

ofoldr1Ex :: (Element (Vec n a) -> Element (Vec n a) -> Element (Vec n a)) -> Vec n a -> Element (Vec n a) #

ofoldl1Ex' :: (Element (Vec n a) -> Element (Vec n a) -> Element (Vec n a)) -> Vec n a -> Element (Vec n a) #

headEx :: Vec n a -> Element (Vec n a) #

lastEx :: Vec n a -> Element (Vec n a) #

unsafeHead :: Vec n a -> Element (Vec n a) #

unsafeLast :: Vec n a -> Element (Vec n a) #

maximumByEx :: (Element (Vec n a) -> Element (Vec n a) -> Ordering) -> Vec n a -> Element (Vec n a) #

minimumByEx :: (Element (Vec n a) -> Element (Vec n a) -> Ordering) -> Vec n a -> Element (Vec n a) #

oelem :: Element (Vec n a) -> Vec n a -> Bool #

onotElem :: Element (Vec n a) -> Vec n a -> Bool #

MonoFunctor (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

omap :: (Element (Vec n a) -> Element (Vec n a)) -> Vec n a -> Vec n a #

type Rep (Vec n) Source # 
Instance details

Defined in Termonad.Config.Vec

type Rep (Vec n) = Fin n
type Element (Vec n a) Source # 
Instance details

Defined in Termonad.Config.Vec

type Element (Vec n a) = a

pattern ConsVec :: (a :: Type) -> Vec n a -> Vec ('S n) a Source #

Data constructor for :*.

genVec_ :: SingI n => (Fin n -> a) -> Vec n a Source #

genVec :: SPeano n -> (Fin n -> a) -> Vec n a Source #

indexVec :: Fin n -> Vec n a -> a Source #

replaceVec :: Sing n -> a -> Vec n a Source #

imapVec :: forall n a b. (Fin n -> a -> b) -> Vec n a -> Vec n b Source #

replaceVec_ :: SingI n => a -> Vec n a Source #

apVec :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n c Source #

onHeadVec :: (a -> a) -> Vec ('S n) a -> Vec ('S n) a Source #

dropVec :: Sing m -> Vec (m + n) a -> Vec n a Source #

takeVec :: IFin n m -> Vec n a -> Vec m a Source #

updateAtVec :: Fin n -> (a -> a) -> Vec n a -> Vec n a Source #

setAtVec :: Fin n -> a -> Vec n a -> Vec n a Source #

fromListVec :: Sing n -> [a] -> Maybe (Vec n a) Source #

fromListVec_ :: SingI n => [a] -> Maybe (Vec n a) Source #

unsafeFromListVec :: Sing n -> [a] -> Vec n a Source #

unsafeFromListVec_ :: SingI n => [a] -> Vec n a Source #

type family MatrixTF (ns :: [Peano]) (a :: Type) :: Type where ... Source #

Equations

MatrixTF '[] a = a 
MatrixTF (n ': ns) a = Vec n (MatrixTF ns a) 

newtype Matrix ns a Source #

Constructors

Matrix 

Fields

Instances

Instances details
SingI ns => Monad (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(>>=) :: Matrix ns a -> (a -> Matrix ns b) -> Matrix ns b #

(>>) :: Matrix ns a -> Matrix ns b -> Matrix ns b #

return :: a -> Matrix ns a #

SingI ns => Functor (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

fmap :: (a -> b) -> Matrix ns a -> Matrix ns b #

(<$) :: a -> Matrix ns b -> Matrix ns a #

SingI ns => Applicative (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

pure :: a -> Matrix ns a #

(<*>) :: Matrix ns (a -> b) -> Matrix ns a -> Matrix ns b #

liftA2 :: (a -> b -> c) -> Matrix ns a -> Matrix ns b -> Matrix ns c #

(*>) :: Matrix ns a -> Matrix ns b -> Matrix ns b #

(<*) :: Matrix ns a -> Matrix ns b -> Matrix ns a #

SingI ns => Foldable (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

fold :: Monoid m => Matrix ns m -> m #

foldMap :: Monoid m => (a -> m) -> Matrix ns a -> m #

foldMap' :: Monoid m => (a -> m) -> Matrix ns a -> m #

foldr :: (a -> b -> b) -> b -> Matrix ns a -> b #

foldr' :: (a -> b -> b) -> b -> Matrix ns a -> b #

foldl :: (b -> a -> b) -> b -> Matrix ns a -> b #

foldl' :: (b -> a -> b) -> b -> Matrix ns a -> b #

foldr1 :: (a -> a -> a) -> Matrix ns a -> a #

foldl1 :: (a -> a -> a) -> Matrix ns a -> a #

toList :: Matrix ns a -> [a] #

null :: Matrix ns a -> Bool #

length :: Matrix ns a -> Int #

elem :: Eq a => a -> Matrix ns a -> Bool #

maximum :: Ord a => Matrix ns a -> a #

minimum :: Ord a => Matrix ns a -> a #

sum :: Num a => Matrix ns a -> a #

product :: Num a => Matrix ns a -> a #

SingI ns => Distributive (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

distribute :: Functor f => f (Matrix ns a) -> Matrix ns (f a) #

collect :: Functor f => (a -> Matrix ns b) -> f a -> Matrix ns (f b) #

distributeM :: Monad m => m (Matrix ns a) -> Matrix ns (m a) #

collectM :: Monad m => (a -> Matrix ns b) -> m a -> Matrix ns (m b) #

SingI ns => Representable (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

Associated Types

type Rep (Matrix ns) #

Methods

tabulate :: (Rep (Matrix ns) -> a) -> Matrix ns a #

index :: Matrix ns a -> Rep (Matrix ns) -> a #

Eq (MatrixTF ns a) => Eq (Matrix ns a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(==) :: Matrix ns a -> Matrix ns a -> Bool #

(/=) :: Matrix ns a -> Matrix ns a -> Bool #

Num a => Num (Matrix ('[] :: [Peano]) a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

(+) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

(-) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

(*) :: Matrix '[] a -> Matrix '[] a -> Matrix '[] a #

negate :: Matrix '[] a -> Matrix '[] a #

abs :: Matrix '[] a -> Matrix '[] a #

signum :: Matrix '[] a -> Matrix '[] a #

fromInteger :: Integer -> Matrix '[] a #

Ord (MatrixTF ns a) => Ord (Matrix ns a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

compare :: Matrix ns a -> Matrix ns a -> Ordering #

(<) :: Matrix ns a -> Matrix ns a -> Bool #

(<=) :: Matrix ns a -> Matrix ns a -> Bool #

(>) :: Matrix ns a -> Matrix ns a -> Bool #

(>=) :: Matrix ns a -> Matrix ns a -> Bool #

max :: Matrix ns a -> Matrix ns a -> Matrix ns a #

min :: Matrix ns a -> Matrix ns a -> Matrix ns a #

Show (MatrixTF ns a) => Show (Matrix ns a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

showsPrec :: Int -> Matrix ns a -> ShowS #

show :: Matrix ns a -> String #

showList :: [Matrix ns a] -> ShowS #

SingI ns => MonoFoldable (Matrix ns a) Source # 
Instance details

Defined in Termonad.Config.Vec

Methods

ofoldMap :: Monoid m => (Element (Matrix ns a) -> m) -> Matrix ns a -> m #

ofoldr :: (Element (Matrix ns a) -> b -> b) -> b -> Matrix ns a -> b #

ofoldl' :: (a0 -> Element (Matrix ns a) -> a0) -> a0 -> Matrix ns a -> a0 #

otoList :: Matrix ns a -> [Element (Matrix ns a)] #

oall :: (Element (Matrix ns a) -> Bool) -> Matrix ns a -> Bool #

oany :: (Element (Matrix ns a) -> Bool) -> Matrix ns a -> Bool #

onull :: Matrix ns a -> Bool #

olength :: Matrix ns a -> Int #

olength64 :: Matrix ns a -> Int64 #

ocompareLength :: Integral i => Matrix ns a -> i -> Ordering #

otraverse_ :: Applicative f => (Element (Matrix ns a) -> f b) -> Matrix ns a -> f () #

ofor_ :: Applicative f => Matrix ns a -> (Element (Matrix ns a) -> f b) -> f () #

omapM_ :: Applicative m => (Element (Matrix ns a) -> m ()) -> Matrix ns a -> m () #

oforM_ :: Applicative m => Matrix ns a -> (Element (Matrix ns a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (Matrix ns a) -> m a0) -> a0 -> Matrix ns a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (Matrix ns a) -> m) -> Matrix ns a -> m #

ofoldr1Ex :: (Element (Matrix ns a) -> Element (Matrix ns a) -> Element (Matrix ns a)) -> Matrix ns a -> Element (Matrix ns a) #

ofoldl1Ex' :: (Element (Matrix ns a) -> Element (Matrix ns a) -> Element (Matrix ns a)) -> Matrix ns a -> Element (Matrix ns a) #

headEx :: Matrix ns a -> Element (Matrix ns a) #

lastEx :: Matrix ns a -> Element (Matrix ns a) #

unsafeHead :: Matrix ns a -> Element (Matrix ns a) #

unsafeLast :: Matrix ns a -> Element (Matrix ns a) #

maximumByEx :: (Element (Matrix ns a) -> Element (Matrix ns a) -> Ordering) -> Matrix ns a -> Element (Matrix ns a) #

minimumByEx :: (Element (Matrix ns a) -> Element (Matrix ns a) -> Ordering) -> Matrix ns a -> Element (Matrix ns a) #

oelem :: Element (Matrix ns a) -> Matrix ns a -> Bool #

onotElem :: Element (Matrix ns a) -> Matrix ns a -> Bool #

type Rep (Matrix ns) Source # 
Instance details

Defined in Termonad.Config.Vec

type Rep (Matrix ns) = HList Fin ns
type Element (Matrix ns a) Source # 
Instance details

Defined in Termonad.Config.Vec

type Element (Matrix ns a) = a

type MatrixTFSym2 (ns :: [Peano]) (t :: Type) = MatrixTF ns t :: Type Source #

data MatrixTFSym1 (ns :: [Peano]) (z :: TyFun Type Type) Source #

Constructors

forall (arg :: Type).SameKind (Apply (MatrixTFSym1 ns) arg) (MatrixTFSym2 ns arg) => MatrixTFSym1KindInference 

Instances

Instances details
type Apply (MatrixTFSym1 l1 :: TyFun Type Type -> Type) (l2 :: Type) Source # 
Instance details

Defined in Termonad.Config.Vec

type Apply (MatrixTFSym1 l1 :: TyFun Type Type -> Type) (l2 :: Type) = MatrixTF l1 l2

data MatrixTFSym0 (l :: TyFun [Peano] (Type ~> Type)) Source #

Constructors

forall (arg :: [Peano]).SameKind (Apply MatrixTFSym0 arg) (MatrixTFSym1 arg) => MatrixTFSym0KindInference 

Instances

Instances details
type Apply MatrixTFSym0 (l :: [Peano]) Source # 
Instance details

Defined in Termonad.Config.Vec

eqSingMatrix :: forall (peanos :: [Peano]) (a :: Type). Eq a => Sing peanos -> Matrix peanos a -> Matrix peanos a -> Bool Source #

ordSingMatrix :: forall (peanos :: [Peano]) (a :: Type). Ord a => Sing peanos -> Matrix peanos a -> Matrix peanos a -> Ordering Source #

compareSingMatrix :: forall (peanos :: [Peano]) (a :: Type) (c :: Type). (a -> a -> c) -> c -> (c -> c -> c) -> Sing peanos -> Matrix peanos a -> Matrix peanos a -> c Source #

fmapSingMatrix :: forall (peanos :: [Peano]) (a :: Type) (b :: Type). Sing peanos -> (a -> b) -> Matrix peanos a -> Matrix peanos b Source #

consMatrix :: Matrix ns a -> Matrix (n ': ns) a -> Matrix ('S n ': ns) a Source #

toListMatrix :: forall (peanos :: [Peano]) (a :: Type). Sing peanos -> Matrix peanos a -> [a] Source #

genMatrix :: forall (ns :: [Peano]) (a :: Type). Sing ns -> (HList Fin ns -> a) -> Matrix ns a Source #

genMatrix_ :: SingI ns => (HList Fin ns -> a) -> Matrix ns a Source #

indexMatrix :: HList Fin ns -> Matrix ns a -> a Source #

imapMatrix :: forall (ns :: [Peano]) a b. Sing ns -> (HList Fin ns -> a -> b) -> Matrix ns a -> Matrix ns b Source #

imapMatrix_ :: SingI ns => (HList Fin ns -> a -> b) -> Matrix ns a -> Matrix ns b Source #

onMatrixTF :: (MatrixTF ns a -> MatrixTF ms b) -> Matrix ns a -> Matrix ms b Source #

onMatrix :: (Matrix ns a -> Matrix ms b) -> MatrixTF ns a -> MatrixTF ms b Source #

updateAtMatrix :: HList Fin ns -> (a -> a) -> Matrix ns a -> Matrix ns a Source #

setAtMatrix :: HList Fin ns -> a -> Matrix ns a -> Matrix ns a Source #