| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Numeric
Contents
Description
promoted numeric functions
Synopsis
- data p + q
- data p - q
- data p * q
- data p / q
- data Negate p
- data Abs p
- data Signum p
- data FromInteger (t :: Type)
- data FromInteger' t n
- data FromIntegral (t :: Type)
- data FromIntegral' t n
- data Truncate (t :: Type)
- data Truncate' t p
- data Ceiling (t :: Type)
- data Ceiling' t p
- data Floor (t :: Type)
- data Floor' t p
- data Even
- data Odd
- data Div p q
- data Mod p q
- data DivMod p q
- data QuotRem p q
- data Quot p q
- data Rem p q
- data LogBase p q
- data p ^ q
- data p ** q
- data DivI t p q
- data RoundUp n p
- data p % q
- data p -% q
- data ToRational p
- data FromRational (t :: Type)
- data FromRational' t p
- data ReadBase (t :: Type) (n :: Nat)
- data ReadBase' t (n :: Nat) p
- data ShowBase (n :: Nat)
- data ShowBaseN n p
- data UnShowBaseN n
- data ToBits p
numeric
adds two values together pointed to by p and q
subtracts two values together pointed to by p and q
multiply two values together pointed to by p and q
fractional division
>>>pz @(Fst / Snd) (13,2)Val 6.5
>>>pz @(ToRational 13 / Id) 0Fail "(/) zero denominator"
>>>pz @(12 % 7 / 14 % 5 + Id) 12.4Val (3188 % 245)
similar to negate
>>>pz @(Negate Id) 14Val (-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)
similar to abs
>>>pz @(Abs Id) (-14)Val 14
>>>pz @(Abs Snd) ("xx",14)Val 14
>>>pz @(Abs Id) 0Val 0
>>>pz @(Abs (Negate 44)) "aaa"Val 44
similar to signum
>>>pz @(Signum Id) (-14)Val (-1)
>>>pz @(Signum Id) 14Val 1
>>>pz @(Signum Id) 0Val 0
data FromInteger (t :: Type) Source #
fromInteger function where you need to provide the type t of the result
>>>pz @(FromInteger (SG.Sum _)) 23Val (Sum {getSum = 23})
>>>pz @(44 >> FromInteger Rational) 12Val (44 % 1)
>>>pz @(FromInteger Rational) 12Val (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) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromInteger t -> ShowS # show :: FromInteger t -> String # showList :: [FromInteger t] -> ShowS # | |
| P (FromIntegerT t) x => P (FromInteger t :: Type) x Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromInteger t) x Source # Methods eval :: MonadEval m => proxy (FromInteger t) -> POpts -> x -> m (TT (PP (FromInteger t) x)) Source # | |
| type PP (FromInteger t :: Type) x Source # | |
Defined in Predicate.Data.Numeric | |
data FromInteger' t n Source #
fromInteger function where you need to provide a reference to the type t of the result
Instances
| (Num (PP t a), Integral (PP n a), P n a, Show (PP t a)) => P (FromInteger' t n :: Type) a Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromInteger' t n) a Source # Methods eval :: MonadEval m => proxy (FromInteger' t n) -> POpts -> a -> m (TT (PP (FromInteger' t n) a)) Source # | |
| Show (FromInteger' t n) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromInteger' t n -> ShowS # show :: FromInteger' t n -> String # showList :: [FromInteger' t n] -> ShowS # | |
| type PP (FromInteger' t n :: Type) a Source # | |
Defined in Predicate.Data.Numeric | |
data FromIntegral (t :: Type) Source #
fromIntegral function where you need to provide the type t of the result
>>>pz @(FromIntegral (SG.Sum _)) 23Val (Sum {getSum = 23})
>>>pz @(Pop1' (Proxy FromIntegral) 'Proxy 44) (1 % 0)Val (44 % 1)
Instances
| Show (FromIntegral t) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromIntegral t -> ShowS # show :: FromIntegral t -> String # showList :: [FromIntegral t] -> ShowS # | |
| P (FromIntegralT t) x => P (FromIntegral t :: Type) x Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromIntegral t) x Source # Methods eval :: MonadEval m => proxy (FromIntegral t) -> POpts -> x -> m (TT (PP (FromIntegral t) x)) Source # | |
| type PP (FromIntegral t :: Type) x Source # | |
Defined in Predicate.Data.Numeric | |
data FromIntegral' t n Source #
fromIntegral function where you need to provide a reference to the type t of the result
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 # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromIntegral' t n) a Source # Methods eval :: MonadEval m => proxy (FromIntegral' t n) -> POpts -> a -> m (TT (PP (FromIntegral' t n) a)) Source # | |
| Show (FromIntegral' t n) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromIntegral' t n -> ShowS # show :: FromIntegral' t n -> String # showList :: [FromIntegral' t n] -> ShowS # | |
| type PP (FromIntegral' t n :: Type) a Source # | |
Defined in Predicate.Data.Numeric | |
data Truncate (t :: Type) Source #
truncate function where you need to provide the type t of the result
>>>pz @(Truncate Int) (23 % 5)Val 4
truncate function where you need to provide a reference to 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
data Ceiling (t :: Type) Source #
ceiling function where you need to provide the type t of the result
>>>pz @(Ceiling Int) (23 % 5)Val 5
ceiling function where you need to provide a reference to the type t of the result
data Floor (t :: Type) Source #
floor function where you need to provide the type t of the result
>>>pz @(Floor Int) (23 % 5)Val 4
floor function where you need to provide a reference to the type t of the result
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)]
similar to odd
similar to div
>>>pz @(Div Fst Snd) (10,4)Val 2
>>>pz @(Div Fst Snd) (10,0)Fail "Div zero denominator"
similar to mod
>>>pz @(Mod Fst Snd) (10,3)Val 1
>>>pz @(Mod Fst Snd) (10,0)Fail "Mod zero denominator"
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) 23Present (-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)
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) 23Present (-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)
similar to quot
similar to rem
similar to logBase
>>>pz @(Fst `LogBase` Snd >> Truncate Int) (10,12345)Val 4
similar to 'GHC.Real.(^)'
>>>pz @(Fst ^ Snd) (10,4)Val 10000
similar to 'GHC.Float.(**)'
>>>pz @(Fst ** Snd) (10,4)Val 10000.0
>>>pz @'(IsPrime,Id ^ 3,(FromIntegral _) ** (Lift (FromRational _) (1 % 2))) 4Val (False,64,2.0)
divide for integrals
>>>pz @(On (+) (Id * Id) >> (Id ** (DivI Double 1 2))) (3,4)Val 5.0
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"
rational numbers
creates a Rational value
>>>pz @(Id < 21 % 5) (-3.1)Val True
>>>pz @(Id < 21 % 5) 4.5Val False
>>>pz @(Fst % Snd) (13,2)Val (13 % 2)
>>>pz @(13 % Id) 0Fail "(%) 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)
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)
data ToRational p Source #
toRational function
>>>pz @(ToRational Id) 23.5Val (47 % 2)
>>>pl @((ToRational 123 &&& Id) >> Fst + Snd) 4.2Present 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 Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (ToRational p) x Source # Methods eval :: MonadEval m => proxy (ToRational p) -> POpts -> x -> m (TT (PP (ToRational p) x)) Source # | |
| Show (ToRational p) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> ToRational p -> ShowS # show :: ToRational p -> String # showList :: [ToRational p] -> ShowS # | |
| type PP (ToRational p :: Type) x Source # | |
Defined in Predicate.Data.Numeric | |
data FromRational (t :: Type) Source #
fromRational function where you need to provide the type t of the result
>>>pz @(FromRational Rational) 23.5Val (47 % 2)
>>>pl @(FromRational Float) (4 % 5)Present 0.8 (FromRational 0.8 | 4 % 5) Val 0.8
Instances
| Show (FromRational t) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromRational t -> ShowS # show :: FromRational t -> String # showList :: [FromRational t] -> ShowS # | |
| P (FromRationalT t) x => P (FromRational t :: Type) x Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromRational t) x Source # Methods eval :: MonadEval m => proxy (FromRational t) -> POpts -> x -> m (TT (PP (FromRational t) x)) Source # | |
| type PP (FromRational t :: Type) x Source # | |
Defined in Predicate.Data.Numeric | |
data FromRational' t p Source #
fromRational function where you need to provide a reference to 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 Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (FromRational' t p) a Source # Methods eval :: MonadEval m => proxy (FromRational' t p) -> POpts -> a -> m (TT (PP (FromRational' t p) a)) Source # | |
| Show (FromRational' t p) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> FromRational' t p -> ShowS # show :: FromRational' t p -> String # showList :: [FromRational' t p] -> ShowS # | |
| type PP (FromRational' t p :: Type) a Source # | |
Defined in Predicate.Data.Numeric | |
read-show
data ReadBase (t :: Type) (n :: Nat) Source #
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
data ReadBase' t (n :: Nat) p Source #
Read a number using base 2 through a maximum of 36 with t a reference to a type
data ShowBase (n :: Nat) Source #
Display a number at base 2 to 36, similar to showIntAtBase but passes the sign through
>>>pz @(ShowBase 16) 4077Val "fed"
>>>pz @(ShowBase 16) (-255)Val "-ff"
>>>pz @(ShowBase 2) 147Val "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) 123Present "7b" (ShowBase(16) 7b | 123) Val "7b"
>>>pl @(ShowBase 16) 65504Present "ffe0" (ShowBase(16) ffe0 | 65504) Val "ffe0"
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]
data UnShowBaseN n Source #
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 Source # | |
Defined in Predicate.Data.Numeric Associated Types type PP (UnShowBaseN n) x Source # Methods eval :: MonadEval m => proxy (UnShowBaseN n) -> POpts -> x -> m (TT (PP (UnShowBaseN n) x)) Source # | |
| Show (UnShowBaseN n) Source # | |
Defined in Predicate.Data.Numeric Methods showsPrec :: Int -> UnShowBaseN n -> ShowS # show :: UnShowBaseN n -> String # showList :: [UnShowBaseN n] -> ShowS # | |
| type PP (UnShowBaseN n :: Type) x Source # | |
Defined in Predicate.Data.Numeric | |