Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Math functions.
Synopsis
- mod5 :: Integral i => i -> i
- mod7 :: Integral i => i -> i
- mod12 :: Integral i => i -> i
- mod16 :: Integral i => i -> i
- integral_and_fractional_parts :: (Integral i, RealFrac t) => t -> (i, t)
- integer_and_fractional_parts :: RealFrac t => t -> (Integer, t)
- fractional_part :: RealFrac a => a -> a
- real_floor :: (Real r, Integral i) => r -> i
- real_floor_int :: Real r => r -> Int
- real_round :: (Real r, Integral i) => r -> i
- real_round_int :: Real r => r -> Int
- round_int :: RealFrac t => t -> Int
- from_integral_to_int :: Integral i => i -> Int
- int_id :: Int -> Int
- zero_to_precision :: Real r => Int -> r -> Bool
- whole_to_precision :: Real r => Int -> r -> Bool
- sawtooth_wave :: RealFrac a => a -> a
- rational_simplifies :: Integral a => (a, a) -> Bool
- rational_nd :: Integral t => Ratio t -> (t, t)
- rational_whole :: Integral a => Ratio a -> Maybe a
- rational_whole_err :: Integral a => Ratio a -> a
- ratio_nd_sum :: Integral t => Ratio t -> t
- real_is_whole :: Real n => n -> Bool
- floor_f :: (RealFrac a, Num b) => a -> b
- round_to :: RealFrac n => n -> n -> n
- recip_m :: (Eq a, Fractional a) => a -> Maybe a
- oi_mod :: Integral a => a -> a -> a
- oi_divMod :: Integral t => t -> t -> (t, t)
- i_square_root :: Integral t => t -> t
- in_open_interval :: Ord a => (a, a) -> a -> Bool
- in_closed_interval :: Ord a => (a, a) -> a -> Bool
- in_left_half_open_interval :: Ord a => (a, a) -> a -> Bool
- in_right_half_open_interval :: Ord a => (a, a) -> a -> Bool
- nth_root :: (Floating a, Eq a) => a -> a -> a
- arithmetic_mean :: Fractional a => [a] -> a
- ns_mean :: Floating a => [a] -> a
- square :: Num a => a -> a
- totient :: Integral i => i -> i
- farey :: Integral i => i -> [Ratio i]
- farey_length :: Integral i => i -> i
- stern_brocot_tree_f :: Num n => [(n, n)] -> [[(n, n)]]
- stern_brocot_tree :: Num n => [[(n, n)]]
- stern_brocot_tree_lhs :: Num n => [[(n, n)]]
- stern_brocot_tree_f_r :: Integral n => [Ratio n] -> [[Ratio n]]
- outer_product :: (a -> b -> c) -> [a] -> [b] -> [[c]]
Documentation
integral_and_fractional_parts :: (Integral i, RealFrac t) => t -> (i, t) Source #
http://reference.wolfram.com/mathematica/ref/FractionalPart.html
i.e. properFraction
integral_and_fractional_parts 1.5 == (1,0.5)
integer_and_fractional_parts :: RealFrac t => t -> (Integer, t) Source #
Type specialised.
fractional_part :: RealFrac a => a -> a Source #
http://reference.wolfram.com/mathematica/ref/FractionalPart.html
import Sound.SC3.Plot {- hsc3-plot -} plot_p1_ln [map fractional_part [-2.0,-1.99 .. 2.0]]
real_floor :: (Real r, Integral i) => r -> i Source #
floor
of real_to_double
.
real_floor_int :: Real r => r -> Int Source #
Type specialised real_floor
.
real_round :: (Real r, Integral i) => r -> i Source #
round
of real_to_double
.
real_round_int :: Real r => r -> Int Source #
Type specialised real_round
.
from_integral_to_int :: Integral i => i -> Int Source #
Type-specialised fromIntegral
zero_to_precision :: Real r => Int -> r -> Bool Source #
Is r zero to k decimal places.
map (flip zero_to_precision 0.00009) [4,5] == [True,False] map (zero_to_precision 4) [0.00009,1.00009] == [True,False]
whole_to_precision :: Real r => Int -> r -> Bool Source #
Is r whole to k decimal places.
map (flip whole_to_precision 1.00009) [4,5] == [True,False]
sawtooth_wave :: RealFrac a => a -> a Source #
http://reference.wolfram.com/mathematica/ref/SawtoothWave.html
plot_p1_ln [map sawtooth_wave [-2.0,-1.99 .. 2.0]]
rational_simplifies :: Integral a => (a, a) -> Bool Source #
Predicate that is true if n/d
can be simplified, ie. where
gcd
of n
and d
is not 1
.
map rational_simplifies [(2,3),(4,6),(5,7)] == [False,True,False]
rational_nd :: Integral t => Ratio t -> (t, t) Source #
numerator
and denominator
of rational.
rational_whole_err :: Integral a => Ratio a -> a Source #
Erroring variant.
ratio_nd_sum :: Integral t => Ratio t -> t Source #
Sum of numerator & denominator.
real_is_whole :: Real n => n -> Bool Source #
Is n a whole (integral) value.
map real_is_whole [-1.0,-0.5,0.0,0.5,1.0] == [True,False,True,False,True]
round_to :: RealFrac n => n -> n -> n Source #
Round b to nearest multiple of a.
map (round_to 0.25) [0,0.1 .. 1] == [0.0,0.0,0.25,0.25,0.5,0.5,0.5,0.75,0.75,1.0,1.0] map (round_to 25) [0,10 .. 100] == [0,0,25,25,50,50,50,75,75,100,100]
recip_m :: (Eq a, Fractional a) => a -> Maybe a Source #
Variant of recip
that checks input for zero.
map recip [1,1/2,0,-1] map recip_m [1,1/2,0,-1] == [Just 1,Just 2,Nothing,Just (-1)]
One-indexed
oi_mod :: Integral a => a -> a -> a Source #
One-indexed mod
function.
map (`oi_mod` 5) [1..10] == [1,2,3,4,5,1,2,3,4,5]
oi_divMod :: Integral t => t -> t -> (t, t) Source #
One-indexed divMod
function.
map (`oi_divMod` 5) [1,3 .. 9] == [(0,1),(0,3),(0,5),(1,2),(1,4)]
I = integral
i_square_root :: Integral t => t -> t Source #
Integral square root (sqrt) function.
map i_square_root [0,1,4,9,16,25,36,49,64,81,100] == [0 .. 10] map i_square_root [4 .. 16] == [2,2,2,2,2,3,3,3,3,3,3,3,4]
Interval
in_open_interval :: Ord a => (a, a) -> a -> Bool Source #
(0,1) = {x | 0 < x < 1}
in_closed_interval :: Ord a => (a, a) -> a -> Bool Source #
- 0,1
- = {x | 0 ≤ x ≤ 1}
in_left_half_open_interval :: Ord a => (a, a) -> a -> Bool Source #
(p,q] (0,1] = {x | 0 < x ≤ 1}
in_right_half_open_interval :: Ord a => (a, a) -> a -> Bool Source #
[p,q) [0,1) = {x | 0 ≤ x < 1}
nth_root :: (Floating a, Eq a) => a -> a -> a Source #
Calculate nth root of x.
12 `nth_root` 2 == 1.0594630943592953
arithmetic_mean :: Fractional a => [a] -> a Source #
Arithmetic mean (average) of a list.
map arithmetic_mean [[-3..3],[0..5],[1..5],[3,5,7],[7,7],[3,9,10,11,12]] == [0,2.5,3,5,7,9]
ns_mean :: Floating a => [a] -> a Source #
Numerically stable mean
map ns_mean [[-3..3],[0..5],[1..5],[3,5,7],[7,7],[3,9,10,11,12]] == [0,2.5,3,5,7,9]
totient :: Integral i => i -> i Source #
The totient function phi(n), also called Euler's totient function.
import Sound.SC3.Plot {- hsc3-plot -} plot_p1_stp [map totient [1::Int .. 100]]
farey :: Integral i => i -> [Ratio i] Source #
The n-th order Farey sequence.
farey 1 == [0, 1] farey 2 == [0, 1/2, 1] farey 3 == [0, 1/3, 1/2, 2/3, 1] farey 4 == [0, 1/4, 1/3, 1/2, 2/3, 3/4, 1] farey 5 == [0, 1/5,1/4, 1/3, 2/5, 1/2, 3/5, 2/3, 3/4,4/5, 1] farey 6 == [0, 1/6,1/5,1/4, 1/3, 2/5, 1/2, 3/5, 2/3, 3/4,4/5,5/6, 1] farey 7 == [0, 1/7,1/6,1/5,1/4,2/7,1/3, 2/5,3/7,1/2,4/7,3/5, 2/3,5/7,3/4,4/5,5/6,6/7, 1] farey 8 == [0,1/8,1/7,1/6,1/5,1/4,2/7,1/3,3/8,2/5,3/7,1/2,4/7,3/5,5/8,2/3,5/7,3/4,4/5,5/6,6/7,7/8,1]
farey_length :: Integral i => i -> i Source #
The length of the n-th order Farey sequence.
map farey_length [1 .. 12] == [2,3,5,7,11,13,19,23,29,33,43,47] map (length . farey) [1 .. 12] == map farey_length [1 .. 12]
stern_brocot_tree_f :: Num n => [(n, n)] -> [[(n, n)]] Source #
stern_brocot_tree :: Num n => [[(n, n)]] Source #
The Stern-Brocot tree from (01,10).
let t = stern_brocot_tree t !! 0 == [(0,1),(1,0)] t !! 1 == [(0,1),(1,1),(1,0)] t !! 2 == [(0,1),(1,2),(1,1),(2,1),(1,0)] t !! 3 == [(0,1),(1,3),(1,2),(2,3),(1,1),(3,2),(2,1),(3,1),(1,0)]
map length (take 12 stern_brocot_tree) == [2,3,5,9,17,33,65,129,257,513,1025,2049] -- A000051
stern_brocot_tree_lhs :: Num n => [[(n, n)]] Source #
Left-hand (rational) side of the the Stern-Brocot tree, ie, from (01,11).
stern_brocot_tree_f_r :: Integral n => [Ratio n] -> [[Ratio n]] Source #
stern_brocot_tree_f
as Ratio
s, for finite subsets.
let t = stern_brocot_tree_f_r [0,1] t !! 1 == [0,1/2,1] t !! 2 == [0,1/3,1/2,2/3,1] t !! 3 == [0,1/4,1/3,2/5,1/2,3/5,2/3,3/4,1] t !! 4 == [0,1/5,1/4,2/7,1/3,3/8,2/5,3/7,1/2,4/7,3/5,5/8,2/3,5/7,3/4,4/5,1]
outer_product :: (a -> b -> c) -> [a] -> [b] -> [[c]] Source #
Outer product of vectors represented as lists, c.f. liftM2
outer_product (*) [2..5] [2..5] == [[4,6,8,10],[6,9,12,15],[8,12,16,20],[10,15,20,25]] liftM2 (*) [2..5] [2..5] == [4,6,8,10,6,9,12,15,8,12,16,20,10,15,20,25]