predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Numeric

Contents

Description

promoted numeric functions

Synopsis

numeric expressions

data p + q infixl 6 Source #

Instances
P (AddT p q) x => P (p + q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p + q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (p + q) -> POpts -> x -> m (TT (PP (p + q) x)) Source #

type PP (p + q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p + q :: Type) x

data p - q infixl 6 Source #

Instances
P (SubT p q) x => P (p - q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p - q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (p - q) -> POpts -> x -> m (TT (PP (p - q) x)) Source #

type PP (p - q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p - q :: Type) x

data p * q infixl 7 Source #

Instances
P (MultT p q) x => P (p * q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p * q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (p * q) -> POpts -> x -> m (TT (PP (p * q) x)) Source #

type PP (p * q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p * q :: Type) x

data p / q infixl 7 Source #

fractional division

>>> pz @(Fst Id / Snd Id) (13,2)
PresentT 6.5
>>> pz @(ToRational 13 / Id) 0
FailT "(/) zero denominator"
>>> pz @(12 % 7 / 14 % 5 + Id) 12.4
PresentT (3188 % 245)
Instances
(PP p a ~ PP q a, Eq (PP q a), P p a, P q a, Show (PP p a), Fractional (PP p a)) => P (p / q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p / q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (p / q) -> POpts -> a -> m (TT (PP (p / q) a)) Source #

type PP (p / q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p / q :: Type) a = PP p a

data Negate p Source #

similar to negate

>>> pz @(Negate Id) 14
PresentT (-14)
>>> pz @(Negate (Fst Id * Snd Id)) (14,3)
PresentT (-42)
>>> pz @(Negate (15 -% 4)) "abc"
PresentT (15 % 4)
>>> pz @(Negate (15 % 3)) ()
PresentT ((-5) % 1)
>>> pz @(Negate (Fst Id % Snd Id)) (14,3)
PresentT ((-14) % 3)
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Negate p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Negate p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Negate p) -> POpts -> x -> m (TT (PP (Negate p) x)) Source #

type PP (Negate p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Negate p :: Type) x = PP p x

data Abs p Source #

similar to abs

>>> pz @(Abs Id) (-14)
PresentT 14
>>> pz @(Abs (Snd Id)) ("xx",14)
PresentT 14
>>> pz @(Abs Id) 0
PresentT 0
>>> pz @(Abs (Negate 44)) "aaa"
PresentT 44
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Abs p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Abs p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Abs p) -> POpts -> x -> m (TT (PP (Abs p) x)) Source #

type PP (Abs p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Abs p :: Type) x = PP p x

data Signum p Source #

similar to signum

>>> pz @(Signum Id) (-14)
PresentT (-1)
>>> pz @(Signum Id) 14
PresentT 1
>>> pz @(Signum Id) 0
PresentT 0
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Signum p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Signum p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Signum p) -> POpts -> x -> m (TT (PP (Signum p) x)) Source #

type PP (Signum p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Signum p :: Type) x = PP p x

data FromInteger (t :: Type) p Source #

fromInteger function where you need to provide the type 't' of the result

>>> pz @(FromInteger (SG.Sum _) Id) 23
PresentT (Sum {getSum = 23})
>>> pz @(FromInteger Rational 44) 12
PresentT (44 % 1)
>>> pz @(FromInteger Rational Id) 12
PresentT (12 % 1)
>>> pl @((FromInteger _ 12 &&& Id) >> Fst Id + Snd Id) (SG.Min 7)
Present Min {getMin = 19} ((>>) Min {getMin = 19} | {getMin = 19})
PresentT (Min {getMin = 19})
>>> pl @((FromInteger _ 12 &&& Id) >> SapA) (SG.Product 7)
Present Product {getProduct = 84} ((>>) Product {getProduct = 84} | {getProduct = 84})
PresentT (Product {getProduct = 84})
>>> pl @(FromInteger (SG.Sum _) (Fst Id)) (3,"A")
Present Sum {getSum = 3} (FromInteger Sum {getSum = 3})
PresentT (Sum {getSum = 3})
>>> pl @(FromInteger DiffTime 123) 'x'
Present 123s (FromInteger 123s)
PresentT 123s
Instances
P (FromIntegerT t p) x => P (FromInteger t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromInteger t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (FromInteger t p) -> POpts -> x -> m (TT (PP (FromInteger t p) x)) Source #

type PP (FromInteger t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromInteger t p :: Type) x

data FromInteger' t n Source #

Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a)) => P (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromInteger' t n) a :: Type Source #

Methods

eval :: MonadEval m => proxy (FromInteger' t n) -> POpts -> a -> m (TT (PP (FromInteger' t n) a)) Source #

type PP (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromInteger' t n :: Type) a = PP t a

data FromIntegral (t :: Type) p Source #

Instances
P (FromIntegralT t p) x => P (FromIntegral t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromIntegral t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (FromIntegral t p) -> POpts -> x -> m (TT (PP (FromIntegral t p) x)) Source #

type PP (FromIntegral t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromIntegral t p :: Type) x

data FromIntegral' t n Source #

fromIntegral function where you need to provide the type 't' of the result

>>> pz @(FromIntegral (SG.Sum _) Id) 23
PresentT (Sum {getSum = 23})
Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a), Show (PP n a)) => P (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromIntegral' t n) a :: Type Source #

Methods

eval :: MonadEval m => proxy (FromIntegral' t n) -> POpts -> a -> m (TT (PP (FromIntegral' t n) a)) Source #

type PP (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromIntegral' t n :: Type) a = PP t a

data Truncate (t :: Type) p Source #

Instances
P (TruncateT t p) x => P (Truncate t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Truncate t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Truncate t p) -> POpts -> x -> m (TT (PP (Truncate t p) x)) Source #

type PP (Truncate t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Truncate t p :: Type) x

data Truncate' t p Source #

truncate function where you need to provide the type 't' of the result

>>> pz @(Truncate Int Id) (23 % 5)
PresentT 4
>>> pl @(Truncate' (Fst Id >> Unproxy) (Snd Id)) (Proxy @Integer,2.3)
Present 2 (Truncate 2 | 2.3)
PresentT 2
>>> pl @(Truncate' (Fst Id) (Snd Id)) (1::Int,2.3)
Present 2 (Truncate 2 | 2.3)
PresentT 2
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Truncate' t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Truncate' t p) -> POpts -> x -> m (TT (PP (Truncate' t p) x)) Source #

type PP (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Truncate' t p :: Type) x = PP t x

data Ceiling (t :: Type) p Source #

Instances
P (CeilingT t p) x => P (Ceiling t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Ceiling t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Ceiling t p) -> POpts -> x -> m (TT (PP (Ceiling t p) x)) Source #

type PP (Ceiling t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Ceiling t p :: Type) x

data Ceiling' t p Source #

ceiling function where you need to provide the type 't' of the result

>>> pz @(Ceiling Int Id) (23 % 5)
PresentT 5
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Ceiling' t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Ceiling' t p) -> POpts -> x -> m (TT (PP (Ceiling' t p) x)) Source #

type PP (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Ceiling' t p :: Type) x = PP t x

data Floor (t :: Type) p Source #

Instances
P (FloorT t p) x => P (Floor t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Floor t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Floor t p) -> POpts -> x -> m (TT (PP (Floor t p) x)) Source #

type PP (Floor t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Floor t p :: Type) x

data Floor' t p Source #

floor function where you need to provide the type 't' of the result

>>> pz @(Floor Int Id) (23 % 5)
PresentT 4
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Floor' t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Floor' t p) -> POpts -> x -> m (TT (PP (Floor' t p) x)) Source #

type PP (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Floor' t p :: Type) x = PP t x

data Even Source #

similar to even

>>> pz @(Map Even Id) [9,-4,12,1,2,3]
PresentT [False,True,True,False,True,False]
>>> pz @(Map '(Even,Odd) Id) [9,-4,12,1,2,3]
PresentT [(False,True),(True,False),(True,False),(False,True),(True,False),(False,True)]
Instances
P EvenT x => P Even x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP Even x :: Type Source #

Methods

eval :: MonadEval m => proxy Even -> POpts -> x -> m (TT (PP Even x)) Source #

type PP Even x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP Even x = Bool

data Odd Source #

Instances
P OddT x => P Odd x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP Odd x :: Type Source #

Methods

eval :: MonadEval m => proxy Odd -> POpts -> x -> m (TT (PP Odd x)) Source #

type PP Odd x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP Odd x = Bool

data Div p q Source #

similar to div

>>> pz @(Div (Fst Id) (Snd Id)) (10,4)
PresentT 2
>>> pz @(Div (Fst Id) (Snd Id)) (10,0)
FailT "Div zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Div p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Div p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (Div p q) -> POpts -> a -> m (TT (PP (Div p q) a)) Source #

type PP (Div p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Div p q :: Type) a = PP p a

data Mod p q Source #

similar to mod

>>> pz @(Mod (Fst Id) (Snd Id)) (10,3)
PresentT 1
>>> pz @(Mod (Fst Id) (Snd Id)) (10,0)
FailT "Mod zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Mod p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Mod p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (Mod p q) -> POpts -> a -> m (TT (PP (Mod p q) a)) Source #

type PP (Mod p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Mod p q :: Type) a = PP p a

data DivMod p q Source #

similar to divMod

>>> pz @(DivMod (Fst Id) (Snd Id)) (10,3)
PresentT (3,1)
>>> pz @(DivMod (Fst Id) (Snd Id)) (10,-3)
PresentT (-4,-2)
>>> pz @(DivMod (Fst Id) (Snd Id)) (-10,3)
PresentT (-4,2)
>>> pz @(DivMod (Fst Id) (Snd Id)) (-10,-3)
PresentT (3,-1)
>>> pz @(DivMod (Fst Id) (Snd Id)) (10,0)
FailT "DivMod zero denominator"
>>> pl @(DivMod (Negate Id) 7) 23
Present (-4,5) (-23 `divMod` 7 = (-4,5))
PresentT (-4,5)
>>> pl @(DivMod (Fst Id) (Snd Id)) (10,-3)
Present (-4,-2) (10 `divMod` -3 = (-4,-2))
PresentT (-4,-2)
>>> pl @(DivMod (Fst Id) (Snd Id)) (10,0)
Error DivMod zero denominator
FailT "DivMod zero denominator"
>>> pl @(DivMod (9 - Fst Id) (Last (Snd Id))) (10,[12,13])
Present (-1,12) (-1 `divMod` 13 = (-1,12))
PresentT (-1,12)
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (DivMod p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (DivMod p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (DivMod p q) -> POpts -> a -> m (TT (PP (DivMod p q) a)) Source #

type PP (DivMod p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (DivMod p q :: Type) a = (PP p a, PP p a)

data QuotRem p q Source #

similar to quotRem

>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,3)
PresentT (3,1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,-3)
PresentT (-3,1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (-10,-3)
PresentT (3,-1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (-10,3)
PresentT (-3,-1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,0)
FailT "QuotRem zero denominator"
>>> pl @(QuotRem (Negate Id) 7) 23
Present (-3,-2) (-23 `quotRem` 7 = (-3,-2))
PresentT (-3,-2)
>>> pl @(QuotRem (Fst Id) (Snd Id)) (10,-3)
Present (-3,1) (10 `quotRem` -3 = (-3,1))
PresentT (-3,1)
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (QuotRem p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (QuotRem p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (QuotRem p q) -> POpts -> a -> m (TT (PP (QuotRem p q) a)) Source #

type PP (QuotRem p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (QuotRem p q :: Type) a = (PP p a, PP p a)

data Quot p q Source #

Instances
P (QuotT p q) x => P (Quot p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Quot p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Quot p q) -> POpts -> x -> m (TT (PP (Quot p q) x)) Source #

type PP (Quot p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Quot p q :: Type) x

data Rem p q Source #

Instances
P (RemT p q) x => P (Rem p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (Rem p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Rem p q) -> POpts -> x -> m (TT (PP (Rem p q) x)) Source #

type PP (Rem p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (Rem p q :: Type) x

data LogBase p q Source #

similar to logBase

>>> pz @(Fst Id `LogBase` Snd Id >> Truncate Int Id) (10,12345)
PresentT 4
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP q a), Floating (PP q a), Ord (PP p a)) => P (LogBase p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (LogBase p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (LogBase p q) -> POpts -> a -> m (TT (PP (LogBase p q) a)) Source #

type PP (LogBase p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (LogBase p q :: Type) a = PP p a

data p ^ q infixr 8 Source #

similar to 'GHC.Real.(^)'

>>> pz @(Fst Id ^ Snd Id) (10,4)
PresentT 10000
Instances
(P p a, P q a, Show (PP p a), Show (PP q a), Num (PP p a), Integral (PP q a)) => P (p ^ q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p ^ q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (p ^ q) -> POpts -> a -> m (TT (PP (p ^ q) a)) Source #

type PP (p ^ q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p ^ q :: Type) a = PP p a

data p ** q infixr 8 Source #

similar to 'GHC.Float.(**)'

>>> pz @(Fst Id ** Snd Id) (10,4)
PresentT 10000.0
>>> pz @'(Prime Id,Id ^ 3,(FromIntegral _ Id) ** (FromRational _ (1 % 2))) 4
PresentT (False,64,2.0)
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Floating (PP p a), Ord (PP q a)) => P (p ** q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p ** q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (p ** q) -> POpts -> a -> m (TT (PP (p ** q) a)) Source #

type PP (p ** q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p ** q :: Type) a = PP p a

rational numbers

data p % q infixl 8 Source #

creates a Rational value

>>> pz @(Id < 21 % 5) (-3.1)
TrueT
>>> pz @(Id < 21 % 5) 4.5
FalseT
>>> pz @(Fst Id % Snd Id) (13,2)
PresentT (13 % 2)
>>> pz @(13 % Id) 0
FailT "(%) zero denominator"
>>> pz @(4 % 3 + 5 % 7) "asfd"
PresentT (43 % 21)
>>> pz @(4 -% 7 * 5 -% 3) "asfd"
PresentT (20 % 21)
>>> pz @(Negate (14 % 3)) ()
PresentT ((-14) % 3)
>>> pz @(14 % 3) ()
PresentT (14 % 3)
>>> pz @(Negate (14 % 3) ==! FromIntegral _ (Negate 5)) ()
PresentT GT
>>> pz @(14 -% 3 ==! 5 -% 1) "aa"
PresentT GT
>>> pz @(Negate (14 % 3) ==! Negate 5 % 2) ()
PresentT LT
>>> pz @(14 -% 3 * 5 -% 1) ()
PresentT (70 % 3)
>>> pz @(14 % 3 ==! 5 % 1) ()
PresentT LT
>>> pz @(15 % 3 / 4 % 2) ()
PresentT (5 % 2)
Instances
(Integral (PP p x), Integral (PP q x), Eq (PP q x), P p x, P q x, Show (PP p x), Show (PP q x)) => P (p % q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p % q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (p % q) -> POpts -> x -> m (TT (PP (p % q) x)) Source #

type PP (p % q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p % q :: Type) x = Rational

data p -% q infixl 8 Source #

negate a ratio

>>> pl @'[1 % 1 ,3 -% 2,3 -% 1] ()
Present [1 % 1,(-3) % 2,(-3) % 1] ('[1 % 1,(-3) % 2,(-3) % 1] (1 % 1) | ())
PresentT [1 % 1,(-3) % 2,(-3) % 1]
>>> pl @('[1 % 1 ,Negate (33 % 7), 21 % 4,Signum (7 -% 5)] >> Map (Floor _ Id) Id) ()
Present [1,-5,5,-1] ((>>) [1,-5,5,-1] | {Map [1,-5,5,-1] | [1 % 1,(-33) % 7,21 % 4,(-1) % 1]})
PresentT [1,-5,5,-1]
>>> pl @('[1 % 1 ,Negate (33 % 7), 21 % 4,Signum (7 -% 5)] >> Map (Ceiling _ Id) Id) ()
Present [1,-4,6,-1] ((>>) [1,-4,6,-1] | {Map [1,-4,6,-1] | [1 % 1,(-33) % 7,21 % 4,(-1) % 1]})
PresentT [1,-4,6,-1]
>>> pl @('[1 % 1 ,Negate (33 % 7), 21 % 4,Signum (7 -% 5)] >> Map (Truncate _ Id) Id) ()
Present [1,-4,5,-1] ((>>) [1,-4,5,-1] | {Map [1,-4,5,-1] | [1 % 1,(-33) % 7,21 % 4,(-1) % 1]})
PresentT [1,-4,5,-1]
>>> pl @(5 % 1 / 3 -% 1) 'x'
Present (-5) % 3 (5 % 1 / (-3) % 1 = (-5) % 3)
PresentT ((-5) % 3)
>>> pl @(5 -% 1 / Fst Id) (3,'x')
Present (-5) % 3 ((-5) % 1 / 3 % 1 = (-5) % 3)
PresentT ((-5) % 3)
Instances
P (NegateRatioT p q) x => P (p -% q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p -% q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (p -% q) -> POpts -> x -> m (TT (PP (p -% q) x)) Source #

type PP (p -% q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (p -% q :: Type) x

data ToRational p Source #

toRational function

>>> pz @(ToRational Id) 23.5
PresentT (47 % 2)
>>> pl @((ToRational 123 &&& Id) >> Fst Id + Snd Id) 4.2
Present 636 % 5 ((>>) 636 % 5 | {123 % 1 + 21 % 5 = 636 % 5})
PresentT (636 % 5)
>>> pl @(Fst Id >= Snd Id || Snd Id > 23 || 12 -% 5 <= ToRational (Fst Id)) (12,13)
True (False || True)
TrueT
>>> pl @(ToRational 14) ()
Present 14 % 1 (ToRational 14 % 1 | 14)
PresentT (14 % 1)
>>> pl @(ToRational 5 / ToRational 3) 'x'
Present 5 % 3 (5 % 1 / 3 % 1 = 5 % 3)
PresentT (5 % 3)
Instances
(a ~ PP p x, Show a, Real a, P p x) => P (ToRational p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ToRational p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ToRational p) -> POpts -> x -> m (TT (PP (ToRational p) x)) Source #

type PP (ToRational p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (ToRational p :: Type) x = Rational

data FromRational (t :: Type) p Source #

fromRational function where you need to provide the type 't' of the result

>>> pz @(FromRational Rational Id) 23.5
PresentT (47 % 2)
>>> pl @(FromRational Float (4 % 5)) ()
Present 0.8 (FromRational 0.8 | 4 % 5)
PresentT 0.8
Instances
P (FromRationalT t p) x => P (FromRational t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (FromRational t p) -> POpts -> x -> m (TT (PP (FromRational t p) x)) Source #

type PP (FromRational t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromRational t p :: Type) x

data FromRational' t r Source #

fromRational function where you need to provide the type 't' of the result

>>> pl @(FromRational' (Fst Id) (Snd Id)) (1::Float,2 % 5)
Present 0.4 (FromRational 0.4 | 2 % 5)
PresentT 0.4
Instances
(P r a, PP r a ~ Rational, Show (PP t a), Fractional (PP t a)) => P (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational' t r) a :: Type Source #

Methods

eval :: MonadEval m => proxy (FromRational' t r) -> POpts -> a -> m (TT (PP (FromRational' t r) a)) Source #

type PP (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (FromRational' t r :: Type) a = PP t a

read / show expressions

data ReadBase (t :: Type) (n :: Nat) p Source #

Read a number using base 2 through a maximum of 36

>>> pz @(ReadBase Int 16 Id) "00feD"
PresentT 4077
>>> pz @(ReadBase Int 16 Id) "-ff"
PresentT (-255)
>>> pz @(ReadBase Int 2 Id) "10010011"
PresentT 147
>>> pz @(ReadBase Int 8 Id) "Abff"
FailT "invalid base 8"
>>> pl @(ReadBase Int 16 Id >> GuardSimple (Id > 0xffff) >> ShowBase 16 Id) "12344"
Present "12344" ((>>) "12344" | {ShowBase(16) 12344 | 74564})
PresentT "12344"
>>> :set -XBinaryLiterals
>>> pz @(ReadBase Int 16 Id >> GuardSimple (Id > 0b10011111) >> ShowBase 16 Id) "7f"
FailT "(127 > 159)"
>>> pl @(ReadBase Int 16 Id) "fFe0"
Present 65504 (ReadBase(Int,16) 65504 | "fFe0")
PresentT 65504
>>> pl @(ReadBase Int 16 Id) "-ff"
Present -255 (ReadBase(Int,16) -255 | "-ff")
PresentT (-255)
>>> pl @(ReadBase Int 16 Id) "ff"
Present 255 (ReadBase(Int,16) 255 | "ff")
PresentT 255
>>> pl @(ReadBase Int 22 Id) "zzz"
Error invalid base 22 (ReadBase(Int,22) as=zzz err=[])
FailT "invalid base 22"
>>> pl @((ReadBase Int 16 Id &&& Id) >> First (ShowBase 16 Id)) "fFe0"
Present ("ffe0","fFe0") ((>>) ("ffe0","fFe0") | {(***) ("ffe0","fFe0") | (65504,"fFe0")})
PresentT ("ffe0","fFe0")
>>> pl @(ReadBase Int 2 Id) "101111"
Present 47 (ReadBase(Int,2) 47 | "101111")
PresentT 47
Instances
P (ReadBaseT t n p) x => P (ReadBase t n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ReadBase t n p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ReadBase t n p) -> POpts -> x -> m (TT (PP (ReadBase t n p) x)) Source #

type PP (ReadBase t n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (ReadBase t n p :: Type) x

data ReadBase' t (n :: Nat) p Source #

Instances
(Typeable (PP t x), ZwischenT 2 36 n, Show (PP t x), Num (PP t x), KnownNat n, PP p x ~ String, P p x) => P (ReadBase' t n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ReadBase' t n p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ReadBase' t n p) -> POpts -> x -> m (TT (PP (ReadBase' t n p) x)) Source #

type PP (ReadBase' t n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (ReadBase' t n p :: Type) x = PP t x

data ShowBase (n :: Nat) p Source #

Display a number at base 2 to 36, similar to showIntAtBase but supports signed numbers

>>> pz @(ShowBase 16 Id) 4077
PresentT "fed"
>>> pz @(ShowBase 16 Id) (-255)
PresentT "-ff"
>>> pz @(ShowBase 2 Id) 147
PresentT "10010011"
>>> pz @(ShowBase 2 (Negate 147)) "whatever"
PresentT "-10010011"
>>> pl @(ShowBase 16 Id) (-123)
Present "-7b" (ShowBase(16) -7b | -123)
PresentT "-7b"
>>> pl @(ShowBase 16 Id) 123
Present "7b" (ShowBase(16) 7b | 123)
PresentT "7b"
>>> pl @(ShowBase 16 Id) 65504
Present "ffe0" (ShowBase(16) ffe0 | 65504)
PresentT "ffe0"
Instances
(PP p x ~ a, P p x, Show a, 2 <= n, n <= 36, KnownNat n, Integral a) => P (ShowBase n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ShowBase n p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ShowBase n p) -> POpts -> x -> m (TT (PP (ShowBase n p) x)) Source #

type PP (ShowBase n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

type PP (ShowBase n p :: Type) x = String