Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type S = [Int]
- type R = (Int, S, [Int], [Int])
- type V = [Int]
- type T = [[Int]]
- p_cycle :: Int -> [Int] -> [Int]
- type E = (S, Int, Int)
- e_to_seq :: E -> [Int]
- e_from_seq :: [Int] -> E
- r_voices :: R -> [V]
- rr_voices :: [R] -> [V]
- t_retrograde :: T -> T
- t_normal :: T -> T
- r_from_t :: T -> [R]
- fromList :: MonadPlus m => [a] -> m a
- perfect_tilings_m :: MonadPlus m => [S] -> [Int] -> Int -> Int -> m T
- perfect_tilings :: [S] -> [Int] -> Int -> Int -> [T]
- elemOrd :: Ord a => a -> [a] -> Bool
- v_dot_star :: Int -> V -> String
- v_space_ix :: Int -> V -> String
- with_bars :: Int -> String -> String
- v_dot_star_m :: Int -> Int -> V -> String
- v_print :: Int -> [V] -> IO ()
- v_print_m :: Int -> Int -> [V] -> IO ()
- v_print_m_from :: Int -> Int -> Int -> [V] -> IO ()
Documentation
p_cycle :: Int -> [Int] -> [Int] Source #
Cycle at period.
take 9 (p_cycle 18 [0,2,5]) == [0,2,5,18,20,23,36,38,41]
e_to_seq :: E -> [Int] Source #
Resolve sequence from E
.
e_to_seq ([0,2,5],2,1) == [1,5,11] e_to_seq ([0,1],3,4) == [4,7] e_to_seq ([0],1,2) == [2]
e_from_seq :: [Int] -> E Source #
Infer E
from sequence.
e_from_seq [1,5,11] == ([0,2,5],2,1) e_from_seq [4,7] == ([0,1],3,4) e_from_seq [2] == ([0],1,2)
t_retrograde :: T -> T Source #
The normal form of T
is the min
of t and it's t_retrograde
.
let r = [[0,7,14],[1,5,9],[2,4,6],[3,8,13],[10,11,12]] t_normal [[0,7,14],[1,6,11],[2,3,4],[5,9,13],[8,10,12]] == r
Construction
perfect_tilings_m :: MonadPlus m => [S] -> [Int] -> Int -> Int -> m T Source #
Search for perfect tilings of the sequence S
using
multipliers from m to degree n with k parts.
perfect_tilings :: [S] -> [Int] -> Int -> Int -> [T] Source #
t_normal
of observeAll
of perfect_tilings_m
.
perfect_tilings [[0,1]] [1..3] 6 3 == []
let r = [[[0,7,14],[1,5,9],[2,4,6],[3,8,13],[10,11,12]]] perfect_tilings [[0,1,2]] [1,2,4,5,7] 15 5 == r
length (perfect_tilings [[0,1,2]] [1..12] 15 5) == 1
let r = [[[0,1],[2,5],[3,7],[4,6]], [[0,1],[2,6],[3,5],[4,7]] ,[[0,2],[1,4],[3,7],[5,6]]] perfect_tilings [[0,1]] [1..4] 8 4 == r
let r = [[[0,1],[2,5],[3,7],[4,9],[6,8]] ,[[0,1],[2,7],[3,5],[4,8],[6,9]] ,[[0,2],[1,4],[3,8],[5,9],[6,7]] ,[[0,2],[1,5],[3,6],[4,9],[7,8]] ,[[0,3],[1,6],[2,4],[5,9],[7,8]]] in perfect_tilings [[0,1]] [1..5] 10 5 == r
Johnson 2004, p.2
let r = [[0,6,12],[1,8,15],[2,11,20],[3,5,7],[4,9,14],[10,13,16],[17,18,19]] perfect_tilings [[0,1,2]] [1,2,3,5,6,7,9] 21 7 == [r]
let r = [[0,10,20],[1,9,17],[2,4,6],[3,7,11],[5,12,19],[8,13,18],[14,15,16]] perfect_tilings [[0,1,2]] [1,2,4,5,7,8,10] 21 7 == [t_retrograde r]
Display
v_dot_star :: Int -> V -> String Source #
A .*
diagram of n places of V
.
v_dot_star 18 [0,2..] == "*.*.*.*.*.*.*.*.*."
v_space_ix :: Int -> V -> String Source #
A white space and index diagram of n places of V
.
>>>
mapM_ (putStrLn . v_space_ix 9) [[0,2..],[1,3..]]
> > 0 2 4 6 8 > 1 3 5 7
with_bars :: Int -> String -> String Source #
Insert |
every n places.
with_bars 6 (v_dot_star 18 [0,2..]) == "*.*.*.|*.*.*.|*.*.*."