hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Random.I_Ching

Synopsis

Documentation

data Line Source #

Line, indicated as sum.

Constructors

L6 
L7 
L8 
L9 

Instances

Eq Line Source # 

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Show Line Source # 

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

type Line_Stat = (Line, (Rational, Rational, String, String, String)) Source #

(sum={6,7,8,9}, (yarrow probablity={1,3,5,7}/16, three-coin probablity={2,6}/16, name,signification,symbol))

line_unbroken :: Line -> Bool Source #

Lines L6 and L7 are unbroken (since L6 is becoming L7).

line_ascii_pp :: Line -> String Source #

Seven character ASCII string for line.

line_is_moving :: Line -> Bool Source #

Is line (ie. sum) moving (ie. 6 or 9).

line_complement :: Line -> Maybe Line Source #

Old yin (L6) becomes yang (L7), and old yang (L9) becomes yin (L8).

hexagram_pp :: Hexagram -> String Source #

Hexagrams are drawn upwards.

four_coin_sequence :: [Line] Source #

Sequence of sum values assigned to ascending four bit numbers.

import  Music.Theory.Bits 
zip (map (gen_bitseq_pp 4) [0::Int .. 15]) (map line_ascii_pp_err four_coin_sequence)

four_coin_gen_hexagram :: IO Hexagram Source #

Generate hexagram (ie. sequence of six lines given by sum) using four_coin_sequence.

four_coin_gen_hexagram >>= putStrLn . hexagram_pp

hexagram_complement :: Hexagram -> Maybe Hexagram Source #

If hexagram_has_complement then derive it.

h <- four_coin_gen_hexagram
putStrLn (hexagram_pp h)
maybe (return ()) (putStrLn . hexagram_pp) (hexagram_complement h)

hexagram_names :: [(String, String)] Source #

Names of hexagrams, in King Wen order.

length hexagram_names == 64

hexagram_unicode_sequence :: [Char] Source #

Unicode hexagram characters, in King Wen order.

import Data.List.Split {- split -}
mapM_ putStrLn (chunksOf 8 hexagram_unicode_sequence)