lorentz-0.13.1: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Arith

Description

Type families from Morley.Michelson.Typed.Arith lifted to Haskell types.

Synopsis

Documentation

class ArithOpHs (aop :: Type) (n :: Type) (m :: Type) (r :: Type) where Source #

Lifted ArithOp.

Minimal complete definition

Nothing

Methods

evalArithOpHs :: (n ': (m ': s)) :-> (r ': s) Source #

default evalArithOpHs :: (DefArithOp aop, ArithOp aop (ToT n) (ToT m), ToT r ~ ArithRes aop (ToT n) (ToT m)) => (n ': (m ': s)) :-> (r ': s) Source #

Instances

Instances details
r ~ Integer => ArithOpHs Add Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Add Integer Timestamp r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Timestamp ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Add Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Add Bls12381Fr Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Add Bls12381G1 Bls12381G1 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': (Bls12381G1 ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Add Bls12381G2 Bls12381G2 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': (Bls12381G2 ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Add Mutez Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Add Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

r ~ Bool => ArithOpHs And Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs And Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs And Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Maybe (Natural, Natural) => ArithOpHs EDiv Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Mutez, Mutez) => ArithOpHs EDiv Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Natural, Mutez) => ArithOpHs EDiv Mutez Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Lsl Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Lsr Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Integer Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Mul Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Natural Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Natural Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Integer ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381Fr Bls12381G1 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G1 ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381Fr Bls12381G2 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G2 ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381G1 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381G2 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bool => ArithOpHs Or Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Or Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Sub Mutez Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Sub Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Timestamp Timestamp r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Timestamp ': s)) :-> (r ': s) Source #

r ~ Bool => ArithOpHs Xor Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Xor Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Add Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Mul Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Add (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (BinBase a)) Integer r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (DecBase a)) Natural r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (DecBase a)) Integer r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Natural, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (BinBase a)) Integer r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Natural, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (DecBase a)) Natural r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (DecBase a)) Integer r Source # 
Instance details

Defined in Lorentz.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (Integer ': s)) :-> (r ': s) Source #

r ~ NFixed (BinBase b) => ArithOpHs Lsl (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

r ~ NFixed (BinBase b) => ArithOpHs Lsr (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Mul (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (Fixed p) (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (Fixed p) (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (NFixed p) (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Add (NFixed p) (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) (Fixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) (NFixed p) r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ (a + b) => ArithOpHs Mul (Fixed (BinBase a)) (NFixed (BinBase b)) (Fixed (BinBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (NFixed (BinBase b) ': s)) :-> (Fixed (BinBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (Fixed (BinBase a)) (Fixed (BinBase b)) (Fixed (BinBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Fixed (BinBase b) ': s)) :-> (Fixed (BinBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (Fixed (DecBase a)) (NFixed (DecBase b)) (Fixed (DecBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (NFixed (DecBase b) ': s)) :-> (Fixed (DecBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (Fixed (DecBase a)) (Fixed (DecBase b)) (Fixed (DecBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Fixed (DecBase b) ': s)) :-> (Fixed (DecBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (NFixed (BinBase a)) (Fixed (BinBase b)) (Fixed (BinBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Fixed (BinBase b) ': s)) :-> (Fixed (BinBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (NFixed (BinBase a)) (NFixed (BinBase b)) (NFixed (BinBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (NFixed (BinBase b) ': s)) :-> (NFixed (BinBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (NFixed (DecBase a)) (Fixed (DecBase b)) (Fixed (DecBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (Fixed (DecBase b) ': s)) :-> (Fixed (DecBase r) ': s) Source #

r ~ (a + b) => ArithOpHs Mul (NFixed (DecBase a)) (NFixed (DecBase b)) (NFixed (DecBase r)) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (NFixed (DecBase b) ': s)) :-> (NFixed (DecBase r) ': s) Source #

class DefArithOp aop where Source #

Helper typeclass that provides default definition of evalArithOpHs.

Methods

defEvalOpHs :: (ArithOp aop n m, r ~ ArithRes aop n m) => Instr (n ': (m ': s)) (r ': s) Source #

Instances

Instances details
DefArithOp Add Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Add n m, r ~ ArithRes Add n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp And Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp And n m, r ~ ArithRes And n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp EDiv Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp EDiv n m, r ~ ArithRes EDiv n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Lsl Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Lsl n m, r ~ ArithRes Lsl n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Lsr Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Lsr n m, r ~ ArithRes Lsr n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Mul Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Mul n m, r ~ ArithRes Mul n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Or Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Or n m, r ~ ArithRes Or n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Sub Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Sub n m, r ~ ArithRes Sub n m) => Instr (n ': (m ': s)) (r ': s) Source #

DefArithOp Xor Source # 
Instance details

Defined in Lorentz.Arith

Methods

defEvalOpHs :: forall (n :: T) (m :: T) (r :: T) (s :: [T]). (ArithOp Xor n m, r ~ ArithRes Xor n m) => Instr (n ': (m ': s)) (r ': s) Source #

class UnaryArithOpHs (aop :: Type) (n :: Type) where Source #

Lifted UnaryArithOp.

Minimal complete definition

Nothing

Associated Types

type UnaryArithResHs aop n :: Type Source #

Methods

evalUnaryArithOpHs :: (n ': s) :-> (UnaryArithResHs aop n ': s) Source #

default evalUnaryArithOpHs :: (DefUnaryArithOp aop, UnaryArithOp aop (ToT n), ToT (UnaryArithResHs aop n) ~ UnaryArithRes aop (ToT n)) => (n ': s) :-> (UnaryArithResHs aop n ': s) Source #

Instances

Instances details
UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Abs Integer ': s) Source #

UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Eq' Integer ': s) Source #

UnaryArithOpHs Eq' Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Eq' Natural ': s) Source #

UnaryArithOpHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Ge Integer ': s) Source #

UnaryArithOpHs Ge Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Ge Natural ': s) Source #

UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Gt Integer ': s) Source #

UnaryArithOpHs Gt Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Gt Natural ': s) Source #

UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Le Integer ': s) Source #

UnaryArithOpHs Le Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Le Natural ': s) Source #

UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Lt Integer ': s) Source #

UnaryArithOpHs Lt Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Lt Natural ': s) Source #

UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Neg Integer ': s) Source #

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Neg Natural ': s) Source #

UnaryArithOpHs Neg Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381Fr Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': s) :-> (UnaryArithResHs Neg Bls12381Fr ': s) Source #

UnaryArithOpHs Neg Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G1 Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': s) :-> (UnaryArithResHs Neg Bls12381G1 ': s) Source #

UnaryArithOpHs Neg Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G2 Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': s) :-> (UnaryArithResHs Neg Bls12381G2 ': s) Source #

UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Neq Integer ': s) Source #

UnaryArithOpHs Neq Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Neq Natural ': s) Source #

UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bool ': s) :-> (UnaryArithResHs Not Bool ': s) Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Not Integer ': s) Source #

UnaryArithOpHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Not Natural ': s) Source #

UnaryArithOpHs Neg (Fixed p) Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg (Fixed p) Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Fixed p ': s) :-> (UnaryArithResHs Neg (Fixed p) ': s) Source #

UnaryArithOpHs Neg (NFixed p) Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg (NFixed p) Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (NFixed p ': s) :-> (UnaryArithResHs Neg (NFixed p) ': s) Source #

class DefUnaryArithOp aop where Source #

Helper typeclass that provides default definition of evalUnaryArithOpHs.

Methods

defUnaryArithOpHs :: (UnaryArithOp aop n, r ~ UnaryArithRes aop n) => Instr (n ': s) (r ': s) Source #

Instances

Instances details
DefUnaryArithOp Abs Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Abs n, r ~ UnaryArithRes Abs n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Eq' Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Eq' n, r ~ UnaryArithRes Eq' n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Ge Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Ge n, r ~ UnaryArithRes Ge n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Gt Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Gt n, r ~ UnaryArithRes Gt n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Le Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Le n, r ~ UnaryArithRes Le n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Lt Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Lt n, r ~ UnaryArithRes Lt n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Neg Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Neg n, r ~ UnaryArithRes Neg n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Neq Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Neq n, r ~ UnaryArithRes Neq n) => Instr (n ': s) (r ': s) Source #

DefUnaryArithOp Not Source # 
Instance details

Defined in Lorentz.Arith

Methods

defUnaryArithOpHs :: forall (n :: T) (r :: T) (s :: [T]). (UnaryArithOp Not n, r ~ UnaryArithRes Not n) => Instr (n ': s) (r ': s) Source #

class ToIntegerArithOpHs (n :: Type) where Source #

Minimal complete definition

Nothing

Methods

evalToIntOpHs :: (n ': s) :-> (Integer ': s) Source #

default evalToIntOpHs :: ToIntArithOp (ToT n) => (n ': s) :-> (Integer ': s) Source #

Instances

Instances details
ToIntegerArithOpHs Natural Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalToIntOpHs :: forall (s :: [Type]). (Natural ': s) :-> (Integer ': s) Source #

ToIntegerArithOpHs Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalToIntOpHs :: forall (s :: [Type]). (Bls12381Fr ': s) :-> (Integer ': s) Source #

ToIntegerArithOpHs (NFixed a) Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalToIntOpHs :: forall (s :: [Type]). (NFixed a ': s) :-> (Integer ': s) Source #