lorentz-0.16.0: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.CustomArith.FixedArith

Synopsis

Lorentz instructions

Typeclasses

newtype Fixed (a :: k) #

The type parameter should be an instance of HasResolution.

Constructors

MkFixed Integer 

Instances

Instances details
DivIntegralConstraint r b => ArithOpHs Div Integer Integer (Maybe (Fixed (b r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivIntegralConstraint r b => ArithOpHs Div Integer Natural (Maybe (Fixed (b r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivIntegralConstraint r b => ArithOpHs Div Natural Integer (Maybe (Fixed (b r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivIntegralConstraint r b => ArithOpHs Div Natural Natural (Maybe (Fixed (b r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint1 a t r (Fixed :: LorentzFixedBaseKind -> Type) b1 => ArithOpHs Div Integer (Fixed (b1 a)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint1 a t r (Fixed :: LorentzFixedBaseKind -> Type) b1 => ArithOpHs Div Natural (Fixed (b1 a)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

UnaryArithOpHs Neg (Fixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type UnaryArithResHs Neg (Fixed p) Source #

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

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.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint a b t r (Fixed :: LorentzFixedBaseKind -> Type) b1 b2 => ArithOpHs Div (Fixed (b1 a)) (Fixed (b2 b)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

NFData1 (Fixed :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Fixed a -> () #

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

HasResolution a => ToJSONKey (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Typeable k, Typeable a) => Data (Fixed a)

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixed a -> c (Fixed a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fixed a) #

toConstr :: Fixed a -> Constr #

dataTypeOf :: Fixed a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fixed a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fixed a)) #

gmapT :: (forall b. Data b => b -> b) -> Fixed a -> Fixed a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Fixed a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixed a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) #

Enum (Fixed a)

Recall that, for numeric types, succ and pred typically add and subtract 1, respectively. This is not true in the case of Fixed, whose successor and predecessor functions intuitively return the "next" and "previous" values in the enumeration. The results of these functions thus depend on the resolution of the Fixed value. For example, when enumerating values of resolution 10^-3 of type Milli = Fixed E3,

  succ (0.000 :: Milli) == 0.001

and likewise

  pred (0.000 :: Milli) == -0.001

In other words, succ and pred increment and decrement a fixed-precision value by the least amount such that the value's resolution is unchanged. For example, 10^-12 is the smallest (positive) amount that can be added to a value of type Pico = Fixed E12 without changing its resolution, and so

  succ (0.000000000000 :: Pico) == 0.000000000001

and similarly

  pred (0.000000000000 :: Pico) == -0.000000000001

This is worth bearing in mind when defining Fixed arithmetic sequences. In particular, you may be forgiven for thinking the sequence

  [1..10] :: [Pico]

evaluates to [1, 2, 3, 4, 5, 6, 7, 8, 9, 10] :: [Pico].

However, this is not true. On the contrary, similarly to the above implementations of succ and pred, enumFromTo :: Pico -> Pico -> [Pico] has a "step size" of 10^-12. Hence, the list [1..10] :: [Pico] has the form

  [1.000000000000, 1.00000000001, 1.00000000002, ..., 10.000000000000]

and contains 9 * 10^12 + 1 values.

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

succ :: Fixed a -> Fixed a #

pred :: Fixed a -> Fixed a #

toEnum :: Int -> Fixed a #

fromEnum :: Fixed a -> Int #

enumFrom :: Fixed a -> [Fixed a] #

enumFromThen :: Fixed a -> Fixed a -> [Fixed a] #

enumFromTo :: Fixed a -> Fixed a -> [Fixed a] #

enumFromThenTo :: Fixed a -> Fixed a -> Fixed a -> [Fixed a] #

HasResolution a => Num (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(+) :: Fixed a -> Fixed a -> Fixed a #

(-) :: Fixed a -> Fixed a -> Fixed a #

(*) :: Fixed a -> Fixed a -> Fixed a #

negate :: Fixed a -> Fixed a #

abs :: Fixed a -> Fixed a #

signum :: Fixed a -> Fixed a #

fromInteger :: Integer -> Fixed a #

HasResolution a => Read (Fixed a)

Since: base-4.3.0.0

Instance details

Defined in Data.Fixed

HasResolution a => Fractional (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(/) :: Fixed a -> Fixed a -> Fixed a #

recip :: Fixed a -> Fixed a #

fromRational :: Rational -> Fixed a #

HasResolution a => Real (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

toRational :: Fixed a -> Rational #

HasResolution a => RealFrac (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

properFraction :: Integral b => Fixed a -> (b, Fixed a) #

truncate :: Integral b => Fixed a -> b #

round :: Integral b => Fixed a -> b #

ceiling :: Integral b => Fixed a -> b #

floor :: Integral b => Fixed a -> b #

HasResolution a => Show (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

show :: Fixed a -> String #

showList :: [Fixed a] -> ShowS #

NFData (Fixed a)

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fixed a -> () #

Eq (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

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

Ord (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

compare :: Fixed a -> Fixed a -> Ordering #

(<) :: Fixed a -> Fixed a -> Bool #

(<=) :: Fixed a -> Fixed a -> Bool #

(>) :: Fixed a -> Fixed a -> Bool #

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

max :: Fixed a -> Fixed a -> Fixed a #

min :: Fixed a -> Fixed a -> Fixed a #

Hashable (Fixed a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Fixed a -> Int #

hash :: Fixed a -> Int #

Unwrappable (Fixed a) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappabled (Fixed a) Source #

IsoValue (Fixed p) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (Fixed p) :: T #

Methods

toVal :: Fixed p -> Value (ToT (Fixed p)) #

fromVal :: Value (ToT (Fixed p)) -> Fixed p #

HasResolution a => Ring (Fixed a) 
Instance details

Defined in Data.Semiring

Methods

negate :: Fixed a -> Fixed a #

HasResolution a => Semiring (Fixed a) 
Instance details

Defined in Data.Semiring

Methods

plus :: Fixed a -> Fixed a -> Fixed a #

zero :: Fixed a #

times :: Fixed a -> Fixed a -> Fixed a #

one :: Fixed a #

fromNatural :: Natural -> Fixed a #

(KnownNat a, KnownNat b, b1 ~ b2, LorentzFixedBase b1) => LorentzRounding (Fixed (b1 a)) (Fixed (b2 b)) Source #

Round is implemented using "banker's rounding" strategy, rounding half-way values towards nearest even value

Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (Fixed (b1 a) ': s) :-> (Fixed (b2 b) ': s) Source #

ceil_ :: forall (s :: [Type]). (Fixed (b1 a) ': s) :-> (Fixed (b2 b) ': s) Source #

floor_ :: forall (s :: [Type]). (Fixed (b1 a) ': s) :-> (Fixed (b2 b) ': s) Source #

type UnaryArithResHs Neg (Fixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

type UnaryArithResHs Neg (Fixed p) = Fixed p
type Unwrappabled (Fixed a) Source # 
Instance details

Defined in Lorentz.Wrappable

type ToT (Fixed p) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (Fixed p) = 'TInt
type PrettyShow (Fixed _1) 
Instance details

Defined in Morley.Prelude.Show

type PrettyShow (Fixed _1) = ()

newtype NFixed p Source #

Like Fixed but with a Natural value inside constructor

Constructors

MkNFixed Natural 

Instances

Instances details
DivIntegralConstraint r b => ArithOpHs Div Natural Natural (Maybe (NFixed (b r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint1 a t r (Fixed :: LorentzFixedBaseKind -> Type) b1 => ArithOpHs Div Integer (NFixed (b1 a)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint1 a t r (NFixed :: LorentzFixedBaseKind -> Type) b1 => ArithOpHs Div Natural (NFixed (b1 a)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

UnaryArithOpHs Neg (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type UnaryArithResHs Neg (NFixed p) Source #

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

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.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

DivConstraint a b t r (NFixed :: LorentzFixedBaseKind -> Type) b1 b2 => ArithOpHs Div (NFixed (b1 a)) (NFixed (b2 b)) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

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.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

Methods

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

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

Defined in Lorentz.CustomArith.FixedArith

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.CustomArith.FixedArith

Methods

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

HasResolution a => Num (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

(+) :: NFixed a -> NFixed a -> NFixed a #

(-) :: NFixed a -> NFixed a -> NFixed a #

(*) :: NFixed a -> NFixed a -> NFixed a #

negate :: NFixed a -> NFixed a #

abs :: NFixed a -> NFixed a #

signum :: NFixed a -> NFixed a #

fromInteger :: Integer -> NFixed a #

HasResolution a => Fractional (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

(/) :: NFixed a -> NFixed a -> NFixed a #

recip :: NFixed a -> NFixed a #

fromRational :: Rational -> NFixed a #

HasResolution a => Real (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

toRational :: NFixed a -> Rational #

HasResolution a => Show (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

show :: NFixed a -> String #

showList :: [NFixed a] -> ShowS #

Eq (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

(==) :: NFixed p -> NFixed p -> Bool #

(/=) :: NFixed p -> NFixed p -> Bool #

Ord (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

compare :: NFixed p -> NFixed p -> Ordering #

(<) :: NFixed p -> NFixed p -> Bool #

(<=) :: NFixed p -> NFixed p -> Bool #

(>) :: NFixed p -> NFixed p -> Bool #

(>=) :: NFixed p -> NFixed p -> Bool #

max :: NFixed p -> NFixed p -> NFixed p #

min :: NFixed p -> NFixed p -> NFixed p #

ToIntegerArithOpHs (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

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

Unwrappable (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type Unwrappabled (NFixed a) Source #

IsoValue (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type ToT (NFixed p) :: T #

Methods

toVal :: NFixed p -> Value (ToT (NFixed p)) #

fromVal :: Value (ToT (NFixed p)) -> NFixed p #

(KnownNat a, KnownNat b, b1 ~ b2, LorentzFixedBase b1) => LorentzRounding (NFixed (b1 a)) (NFixed (b2 b)) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (NFixed (b1 a) ': s) :-> (NFixed (b2 b) ': s) Source #

ceil_ :: forall (s :: [Type]). (NFixed (b1 a) ': s) :-> (NFixed (b2 b) ': s) Source #

floor_ :: forall (s :: [Type]). (NFixed (b1 a) ': s) :-> (NFixed (b2 b) ': s) Source #

type UnaryArithResHs Neg (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

type UnaryArithResHs Neg (NFixed p) = Fixed p
type Unwrappabled (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

type ToT (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

type ToT (NFixed p) = 'TNat

Support types and functions

type LorentzFixedBaseKind = LorentzFixedBaseKindTag -> Type Source #

Open kind for fixed value bases.

data DecBase :: Nat -> LorentzFixedBaseKind Source #

Represents decimal base of the Lorentz fixed-point values

Instances

Instances details
LorentzFixedBase DecBase Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

getBase :: Num b => b Source #

data BinBase :: Nat -> LorentzFixedBaseKind Source #

Represents binary base of the Lorentz fixed-point values

Instances

Instances details
LorentzFixedBase BinBase Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

getBase :: Num b => b Source #

resolution_ :: forall a. HasResolution a => Natural Source #

Special function to get resolution without argument

toFixed :: forall a f base t s. (a ~ f (base t), LorentzFixedBase base, Unwrappable a, KnownNat t, ArithOpHs Mul Natural (Unwrappabled a) (Unwrappabled a)) => (Unwrappabled a : s) :-> (a : s) Source #

Convert from the corresponding integral type.

fromFixed :: forall a f base t s. (a ~ f (base t), ToT (f (base 0)) ~ ToT (Unwrappabled a), LorentzRounding a (f (base 0))) => (a : s) :-> (Unwrappabled a : s) Source #

Convert to the corresponding integral type by banker's rounding.

class Typeable a => LorentzFixedBase a Source #

Minimal complete definition

getBase

Instances

Instances details
LorentzFixedBase BinBase Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

getBase :: Num b => b Source #

LorentzFixedBase DecBase Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

getBase :: Num b => b Source #

Internals

Orphan instances

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

UnaryArithOpHs Neg (Fixed p) Source # 
Instance details

Associated Types

type UnaryArithResHs Neg (Fixed p) Source #

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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