hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Random.I_Ching

Description

YIJING / I-CHING

Synopsis

LINE

data Line Source #

Line, indicated as sum.

Constructors

L6 
L7 
L8 
L9 

Instances

Instances details
Show Line Source # 
Instance details

Defined in Music.Theory.Random.I_Ching

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Eq Line Source # 
Instance details

Defined in Music.Theory.Random.I_Ching

Methods

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

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

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))

i_ching_chart :: [Line_Stat] Source #

I-CHING chart as sequence of 4 Line_Stat.

line_unbroken :: Line -> Bool Source #

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

line_from_bit :: Bool -> Line Source #

If b then L7 else L8.

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).

four_coin_sequence :: [Line] Source #

Sequence of sum values assigned to ascending four bit numbers. Sequence is in ascending probablity, ie: 1×6,3×9,5×7,7×8.

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

HEXAGRAM

type Hexagram = [Line] Source #

Sequence of 6 Line.

hexagram_pp :: Hexagram -> String Source #

Hexagrams are drawn upwards.

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 (see also datacsvcombinatorics/yijing.csv)

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)

hexagram_from_binary_str :: String -> Hexagram Source #

Read binary form.

let h = hexagram_from_binary_str "100010"
putStrLn (hexagram_pp h)
hexagram_to_binary_str h == "100010"

TRIGRAM

trigram_unicode_sequence :: [Char] Source #

Unicode sequence of trigrams (unicode order).

import Data.List {- base -}
putStrLn (intersperse ' ' trigram_unicode_sequence)

trigram_chart :: [(Int, Char, String, Char, String, Char, String, Char)] Source #

(INDEX,UNICODE,BIT-SEQUENCE,NAME,NAME-TRANSLITERATION,NATURE-IMAGE,DIRECTION,ANIMAL)

map (T.read_bin_err . T.p8_third) trigram_chart == [7,6,5,4,3,2,1,0]