Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Euler plane diagrams as dot language graphs.
Synopsis
- rat_mul :: Rational -> Rational -> Rational
- rat_div :: Rational -> Rational -> Rational
- tun_seq :: Int -> Rational -> Rational -> [Rational]
- all_pairs :: [t] -> [u] -> [(t, u)]
- euler_align_rat :: T2 Rational -> T3 [Rational] -> T2 [T2 Rational]
- pc_pp :: (Integral i, Show i) => i -> String
- cents_pp :: Rational -> String
- type RAT_LABEL_OPT = (Int, Bool)
- rat_label :: RAT_LABEL_OPT -> Rational -> String
- rat_id :: Rational -> String
- rat_edge_label :: (Rational, Rational) -> String
- zip_sme :: (t, t, t) -> [u] -> [(t, u)]
- type Euler_Plane t = ([[t]], [(t, t)])
- euler_plane_r :: Ord t => Euler_Plane t -> [t]
- euler_plane_map :: (t -> u) -> Euler_Plane t -> Euler_Plane u
- euler_plane_to_dot :: (t -> String, t -> String, (t, t) -> String) -> Euler_Plane t -> [String]
- euler_plane_to_dot_rat :: RAT_LABEL_OPT -> Euler_Plane Rational -> [String]
Documentation
tun_seq :: Int -> Rational -> Rational -> [Rational] Source #
n = length, m = multiplier, r = initial ratio.
tun_seq 5 (3/2) 1 == [1/1,3/2,9/8,27/16,81/64]
all_pairs :: [t] -> [u] -> [(t, u)] Source #
All possible pairs of elements (x,y) where x is from p and y from q.
all_pairs "ab" "cde" == [('a','c'),('a','d'),('a','e'),('b','c'),('b','d'),('b','e')]
euler_align_rat :: T2 Rational -> T3 [Rational] -> T2 [T2 Rational] Source #
Give all pairs from (l2,l1) and (l3,l2) that are at interval ratios r1 and r2 respectively.
pc_pp :: (Integral i, Show i) => i -> String Source #
Pretty printer for pitch class (UNICODE).
unwords (map pc_pp [0..11]) == "C♮ C♯ D♮ E♭ E♮ F♮ F♯ G♮ A♭ A♮ B♭ B♮"
type RAT_LABEL_OPT = (Int, Bool) Source #
(unit-pitch-class,print-cents)
rat_label :: RAT_LABEL_OPT -> Rational -> String Source #
Dot label for ratio, k is the pitch-class of the unit ratio.
rat_label (0,False) 1 == "C♮\\n1:1" rat_label (3,True) (7/4) == "C♯=969\\n7:4"
rat_id :: Rational -> String Source #
Generate value dot node identifier for ratio.
rat_id (5/4) == "R_5_4"
rat_edge_label :: (Rational, Rational) -> String Source #
Printer for edge label between given ratio nodes.
zip_sme :: (t, t, t) -> [u] -> [(t, u)] Source #
Zip start-middle-end.
zip_sme (0,1,2) "abcd" == [(0,'a'),(1,'b'),(1,'c'),(2,'d')]
type Euler_Plane t = ([[t]], [(t, t)]) Source #
Euler diagram given as (h,v) duple, where h are the horizontal sequences and v are the vertical edges.
euler_plane_r :: Ord t => Euler_Plane t -> [t] Source #
Ratios at plane, sorted.
euler_plane_map :: (t -> u) -> Euler_Plane t -> Euler_Plane u Source #
Apply f at all nodes of the plane.
euler_plane_to_dot :: (t -> String, t -> String, (t, t) -> String) -> Euler_Plane t -> [String] Source #
Generate dot graph given printer functions and an Euler_Plane.
euler_plane_to_dot_rat :: RAT_LABEL_OPT -> Euler_Plane Rational -> [String] Source #
Variant with default printers and fixed node type.