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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Numeric

Contents

Description

promoted numeric functions

Synopsis

numeric

data p + q infixl 6 #

adds two values together pointed to by p and q

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p + q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p + q) -> ShowS #

show :: (p + q) -> String #

showList :: [p + q] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (p + q :: Type) x

data p - q infixl 6 #

subtracts two values together pointed to by p and q

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p - q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p - q) -> ShowS #

show :: (p - q) -> String #

showList :: [p - q] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (p - q :: Type) x

data p * q infixl 7 #

multiply two values together pointed to by p and q

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p * q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p * q) -> ShowS #

show :: (p * q) -> String #

showList :: [p * q] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (p * q :: Type) x

data p / q infixl 7 #

fractional division

>>> pz @(Fst / Snd) (13,2)
Val 6.5
>>> pz @(ToRational 13 / Id) 0
Fail "(/) zero denominator"
>>> pz @(12 % 7 / 14 % 5 + Id) 12.4
Val (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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p / q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p / q) -> ShowS #

show :: (p / q) -> String #

showList :: [p / q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Negate p #

similar to negate

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Negate p) x :: Type #

Methods

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

Show (Negate p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Negate p -> ShowS #

show :: Negate p -> String #

showList :: [Negate p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Abs p #

similar to abs

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Abs p) x :: Type #

Methods

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

Show (Abs p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Abs p -> ShowS #

show :: Abs p -> String #

showList :: [Abs p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Signum p #

similar to signum

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Signum p) x :: Type #

Methods

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

Show (Signum p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Signum p -> ShowS #

show :: Signum p -> String #

showList :: [Signum p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data FromInteger (t :: Type) #

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

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

Defined in Predicate.Data.Numeric

P (FromIntegerT t) x => P (FromInteger t :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromInteger t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (FromInteger t :: Type) x

data FromInteger' t n #

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (FromInteger' t n) # 
Instance details

Defined in Predicate.Data.Numeric

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

Defined in Predicate.Data.Numeric

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

data FromIntegral (t :: Type) #

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

>>> pz @(FromIntegral (SG.Sum _)) 23
Val (Sum {getSum = 23})
>>> pz @(Pop1' (Proxy FromIntegral) 'Proxy 44) (1 % 0)
Val (44 % 1)
Instances
Show (FromIntegral t) # 
Instance details

Defined in Predicate.Data.Numeric

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromIntegral t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (FromIntegral t :: Type) x

data FromIntegral' t n #

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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (FromIntegral' t n) # 
Instance details

Defined in Predicate.Data.Numeric

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

Defined in Predicate.Data.Numeric

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

data Truncate (t :: Type) #

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

>>> pz @(Truncate Int) (23 % 5)
Val 4
Instances
Show (Truncate t) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Truncate t -> ShowS #

show :: Truncate t -> String #

showList :: [Truncate t] -> ShowS #

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Truncate t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (Truncate t :: Type) x

data Truncate' t p #

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

>>> pl @(Truncate' (Fst >> UnproxyT) Snd) (Proxy @Integer,2.3)
Present 2 (Truncate 2 | 2.3)
Val 2
>>> pl @(Truncate' Fst Snd) (1::Int,2.3)
Present 2 (Truncate 2 | 2.3)
Val 2
Instances
(P p x, RealFrac (PP p x), Integral (PP t x), Show (PP t x), Show (PP p x)) => P (Truncate' t p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Truncate' t p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Truncate' t p -> ShowS #

show :: Truncate' t p -> String #

showList :: [Truncate' t p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Ceiling (t :: Type) #

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

>>> pz @(Ceiling Int) (23 % 5)
Val 5
Instances
Show (Ceiling t) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Ceiling t -> ShowS #

show :: Ceiling t -> String #

showList :: [Ceiling t] -> ShowS #

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Ceiling t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (Ceiling t :: Type) x

data Ceiling' t p #

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

Instances
(P p x, RealFrac (PP p x), Integral (PP t x), Show (PP t x), Show (PP p x)) => P (Ceiling' t p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Ceiling' t p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Ceiling' t p -> ShowS #

show :: Ceiling' t p -> String #

showList :: [Ceiling' t p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Floor (t :: Type) #

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

>>> pz @(Floor Int) (23 % 5)
Val 4
Instances
Show (Floor t) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Floor t -> ShowS #

show :: Floor t -> String #

showList :: [Floor t] -> ShowS #

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Floor t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (Floor t :: Type) x

data Floor' t p #

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

Instances
(P p x, RealFrac (PP p x), Integral (PP t x), Show (PP t x), Show (PP p x)) => P (Floor' t p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Floor' t p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Floor' t p -> ShowS #

show :: Floor' t p -> String #

showList :: [Floor' t p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Even #

similar to even

>>> pz @(Map Even) [9,-4,12,1,2,3]
Val [False,True,True,False,True,False]
>>> pz @(Map '(Even,Odd)) [9,-4,12,1,2,3]
Val [(False,True),(True,False),(True,False),(False,True),(True,False),(False,True)]
Instances
Show Even # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Even -> ShowS #

show :: Even -> String #

showList :: [Even] -> ShowS #

P EvenT x => P Even x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP Even x :: Type #

Methods

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

type PP Even x # 
Instance details

Defined in Predicate.Data.Numeric

type PP Even x = Bool

data Odd #

similar to odd

Instances
Show Odd # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Odd -> ShowS #

show :: Odd -> String #

showList :: [Odd] -> ShowS #

P OddT x => P Odd x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP Odd x :: Type #

Methods

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

type PP Odd x # 
Instance details

Defined in Predicate.Data.Numeric

type PP Odd x = Bool

data Div p q #

similar to div

>>> pz @(Div Fst Snd) (10,4)
Val 2
>>> pz @(Div Fst Snd) (10,0)
Fail "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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Div p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Div p q -> ShowS #

show :: Div p q -> String #

showList :: [Div p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Mod p q #

similar to mod

>>> pz @(Mod Fst Snd) (10,3)
Val 1
>>> pz @(Mod Fst Snd) (10,0)
Fail "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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Mod p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Mod p q -> ShowS #

show :: Mod p q -> String #

showList :: [Mod p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data DivMod p q #

similar to divMod

>>> pz @(DivMod Fst Snd) (10,3)
Val (3,1)
>>> pz @(DivMod Fst Snd) (10,-3)
Val (-4,-2)
>>> pz @(DivMod Fst Snd) (-10,3)
Val (-4,2)
>>> pz @(DivMod Fst Snd) (-10,-3)
Val (3,-1)
>>> pz @(DivMod Fst Snd) (10,0)
Fail "DivMod zero denominator"
>>> pl @(DivMod (Negate Id) 7) 23
Present (-4,5) (-23 `divMod` 7 = (-4,5))
Val (-4,5)
>>> pl @(DivMod Fst Snd) (10,-3)
Present (-4,-2) (10 `divMod` -3 = (-4,-2))
Val (-4,-2)
>>> pl @(DivMod Fst Snd) (10,0)
Error DivMod zero denominator
Fail "DivMod zero denominator"
>>> pl @(DivMod (9 - Fst) (Snd >> Last)) (10,[12,13])
Present (-1,12) (-1 `divMod` 13 = (-1,12))
Val (-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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (DivMod p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> DivMod p q -> ShowS #

show :: DivMod p q -> String #

showList :: [DivMod p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data QuotRem p q #

similar to quotRem

>>> pz @(QuotRem Fst Snd) (10,3)
Val (3,1)
>>> pz @(QuotRem Fst Snd) (10,-3)
Val (-3,1)
>>> pz @(QuotRem Fst Snd) (-10,-3)
Val (3,-1)
>>> pz @(QuotRem Fst Snd) (-10,3)
Val (-3,-1)
>>> pz @(QuotRem Fst Snd) (10,0)
Fail "QuotRem zero denominator"
>>> pl @(QuotRem (Negate Id) 7) 23
Present (-3,-2) (-23 `quotRem` 7 = (-3,-2))
Val (-3,-2)
>>> pl @(QuotRem Fst Snd) (10,-3)
Present (-3,1) (10 `quotRem` -3 = (-3,1))
Val (-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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (QuotRem p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> QuotRem p q -> ShowS #

show :: QuotRem p q -> String #

showList :: [QuotRem p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data Quot p q #

similar to quot

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Quot p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Quot p q -> ShowS #

show :: Quot p q -> String #

showList :: [Quot p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (Quot p q :: Type) x

data Rem p q #

similar to rem

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (Rem p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> Rem p q -> ShowS #

show :: Rem p q -> String #

showList :: [Rem p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (Rem p q :: Type) x

data LogBase p q #

similar to logBase

>>> pz @(Fst `LogBase` Snd >> Truncate Int) (10,12345)
Val 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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (LogBase p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> LogBase p q -> ShowS #

show :: LogBase p q -> String #

showList :: [LogBase p q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data p ^ q infixr 8 #

similar to 'GHC.Real.(^)'

>>> pz @(Fst ^ Snd) (10,4)
Val 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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p ^ q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p ^ q) -> ShowS #

show :: (p ^ q) -> String #

showList :: [p ^ q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data p ** q infixr 8 #

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

>>> pz @(Fst ** Snd) (10,4)
Val 10000.0
>>> pz @'(IsPrime,Id ^ 3,(FromIntegral _) ** (Lift (FromRational _) (1 % 2))) 4
Val (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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p ** q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p ** q) -> ShowS #

show :: (p ** q) -> String #

showList :: [p ** q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data DivI t p q #

divide for integrals

>>> pz @(On (+) (Id * Id) >> (Id ** (DivI Double 1 2))) (3,4)
Val 5.0
Instances
P (DivIT t p q) x => P (DivI t p q :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (DivI t p q) x :: Type #

Methods

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

Show (DivI t p q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> DivI t p q -> ShowS #

show :: DivI t p q -> String #

showList :: [DivI t p q] -> ShowS #

type PP (DivI t p q :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

type PP (DivI t p q :: Type) x

data RoundUp n p #

calculate the amount to roundup to the next n

>>> pl @(RoundUp Fst Snd) (3,9)
Present 0 (RoundUp 3 9 = 0)
Val 0
>>> pl @(RoundUp Fst Snd) (3,10)
Present 2 (RoundUp 3 10 = 2)
Val 2
>>> pl @(RoundUp Fst Snd) (3,11)
Present 1 (RoundUp 3 11 = 1)
Val 1
>>> pl @(RoundUp Fst Snd) (3,12)
Present 0 (RoundUp 3 12 = 0)
Val 0
>>> pl @(RoundUp 3 0) ()
Present 0 (RoundUp 3 0 = 0)
Val 0
>>> pl @(RoundUp 0 10) ()
Error RoundUp 'n' cannot be zero
Fail "RoundUp 'n' cannot be zero"
Instances
(Integral (PP n x), Show (PP n x), PP n x ~ PP p x, P n x, P p x) => P (RoundUp n p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (RoundUp n p) x :: Type #

Methods

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

Show (RoundUp n p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> RoundUp n p -> ShowS #

show :: RoundUp n p -> String #

showList :: [RoundUp n p] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (RoundUp n p :: Type) x = PP n x

rational numbers

data p % q infixl 8 #

creates a Rational value

>>> pz @(Id < 21 % 5) (-3.1)
Val True
>>> pz @(Id < 21 % 5) 4.5
Val False
>>> pz @(Fst % Snd) (13,2)
Val (13 % 2)
>>> pz @(13 % Id) 0
Fail "(%) zero denominator"
>>> pz @(4 % 3 + 5 % 7) "asfd"
Val (43 % 21)
>>> pz @(4 -% 7 * 5 -% 3) "asfd"
Val (20 % 21)
>>> pz @(Negate (14 % 3)) ()
Val ((-14) % 3)
>>> pz @(14 % 3) ()
Val (14 % 3)
>>> pz @(Negate (14 % 3) ==! Lift (FromIntegral _) (Negate 5)) ()
Val GT
>>> pz @(14 -% 3 ==! 5 -% 1) "aa"
Val GT
>>> pz @(Negate (14 % 3) ==! Negate 5 % 2) ()
Val LT
>>> pz @(14 -% 3 * 5 -% 1) ()
Val (70 % 3)
>>> pz @(14 % 3 ==! 5 % 1) ()
Val LT
>>> pz @(15 % 3 / 4 % 2) ()
Val (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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p % q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p % q) -> ShowS #

show :: (p % q) -> String #

showList :: [p % q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data p -% q infixl 8 #

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (p -% q) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> (p -% q) -> ShowS #

show :: (p -% q) -> String #

showList :: [p -% q] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data ToRational p #

toRational function

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (ToRational p) x :: Type #

Methods

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

Show (ToRational p) # 
Instance details

Defined in Predicate.Data.Numeric

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

Defined in Predicate.Data.Numeric

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

data FromRational (t :: Type) #

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

>>> pz @(FromRational Rational) 23.5
Val (47 % 2)
>>> pl @(FromRational Float) (4 % 5)
Present 0.8 (FromRational 0.8 | 4 % 5)
Val 0.8
Instances
Show (FromRational t) # 
Instance details

Defined in Predicate.Data.Numeric

P (FromRationalT t) x => P (FromRational t :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational t) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

type PP (FromRational t :: Type) x

data FromRational' t p #

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational' t p) a :: Type #

Methods

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

Show (FromRational' t p) # 
Instance details

Defined in Predicate.Data.Numeric

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

Defined in Predicate.Data.Numeric

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

read-show

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

Read a number using base 2 through a maximum of 36

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

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (ReadBase t n) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> ReadBase t n -> ShowS #

show :: ReadBase t n -> String #

showList :: [ReadBase t n] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (ReadBase t n :: Type) x

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

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 # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

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

Methods

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

Show (ReadBase' t n p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> ReadBase' t n p -> ShowS #

show :: ReadBase' t n p -> String #

showList :: [ReadBase' t n p] -> ShowS #

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

Defined in Predicate.Data.Numeric

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

data ShowBase (n :: Nat) #

Display a number at base 2 to 36, similar to showIntAtBase but passes the sign through

>>> pz @(ShowBase 16) 4077
Val "fed"
>>> pz @(ShowBase 16) (-255)
Val "-ff"
>>> pz @(ShowBase 2) 147
Val "10010011"
>>> pz @(Lift (ShowBase 2) (Negate 147)) "whatever"
Val "-10010011"
>>> pl @(ShowBase 16) (-123)
Present "-7b" (ShowBase(16) -7b | -123)
Val "-7b"
>>> pl @(ShowBase 16) 123
Present "7b" (ShowBase(16) 7b | 123)
Val "7b"
>>> pl @(ShowBase 16) 65504
Present "ffe0" (ShowBase(16) ffe0 | 65504)
Val "ffe0"
Instances
Show (ShowBase n) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

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

show :: ShowBase n -> String #

showList :: [ShowBase n] -> ShowS #

(2 <= n, n <= 36, KnownNat n, Integral x) => P (ShowBase n :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ShowBase n) x :: Type #

Methods

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

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

Defined in Predicate.Data.Numeric

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

data ShowBaseN n p #

Display a number at base >= 2 but just show as a list of ints: ignores the sign

>>> pl @(ShowBaseN 16 Id) (256*256*2+256*14+16*7+11)
Present [2,0,14,7,11] (ShowBaseN | 16 | 134779)
Val [2,0,14,7,11]
Instances
(PP p x ~ a, P p x, PP n x ~ b, P n x, Integral a, Integral b) => P (ShowBaseN n p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ShowBaseN n p) x :: Type #

Methods

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

Show (ShowBaseN n p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> ShowBaseN n p -> ShowS #

show :: ShowBaseN n p -> String #

showList :: [ShowBaseN n p] -> ShowS #

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

Defined in Predicate.Data.Numeric

type PP (ShowBaseN n p :: Type) x = [Int]

data UnShowBaseN n #

reverse ShowBaseN

>>> pz @(UnShowBaseN 2) [1,0,0,1,0]
Val 18
>>> pz @(UnShowBaseN 2) [1,1,1]
Val 7
>>> pz @(UnShowBaseN 16) [7,0,3,1]
Val 28721
>>> pz @(UnShowBaseN 16) [0]
Val 0
>>> pz @(UnShowBaseN 16) []
Val 0
Instances
(x ~ [a], PP n x ~ b, P n x, Integral a, Integral b) => P (UnShowBaseN n :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (UnShowBaseN n) x :: Type #

Methods

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

Show (UnShowBaseN n) # 
Instance details

Defined in Predicate.Data.Numeric

type PP (UnShowBaseN n :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

type PP (UnShowBaseN n :: Type) x = Integer

data ToBits p #

convert to bits

>>> pl @(ToBits 123 >> UnShowBaseN 2) ()
Present 123 ((>>) 123 | {UnShowBaseN | 2 | [1,1,1,1,0,1,1]})
Val 123
Instances
P (ToBitsT p) x => P (ToBits p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ToBits p) x :: Type #

Methods

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

Show (ToBits p) # 
Instance details

Defined in Predicate.Data.Numeric

Methods

showsPrec :: Int -> ToBits p -> ShowS #

show :: ToBits p -> String #

showList :: [ToBits p] -> ShowS #

type PP (ToBits p :: Type) x # 
Instance details

Defined in Predicate.Data.Numeric

type PP (ToBits p :: Type) x