hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Z12

Description

Z12

Z12 are modulo 12 integers.

map signum [-1,0::Z12,1] == [1,0,1]
map abs [-1,0::Z12,1] == [11,0,1]

Aspects of the Enum instance are cyclic.

pred (0::Z12) == 11
succ (11::Z12) == 0

Bounded works

[minBound::Z12 .. maxBound] == [0::Z12 .. 11]

Synopsis

Documentation

type Z n = Mod Int n Source #

Mod Int.

type Z12 = Mod Int 12 Source #

Z 12.

map negate [0::Z12 .. 0xB] == [0,0xB,0xA,9,8,7,6,5,4,3,2,1]
map (+ 5) [0::Z12 .. 11] == [5,6,7,8,9,0xA,0xB,0,1,2,3,4]

enumFromThenTo_cyc :: KnownNat n => Z n -> Z n -> Z n -> [Z n] Source #

Cyclic form of enumFromThenTo.

[9::Z12,11 .. 3] == []
enumFromThenTo_cyc (9::Z12) 11 3 == [9,11,1,3]

enumFromTo_cyc :: KnownNat n => Z n -> Z n -> [Z n] Source #

Cyclic form of enumFromTo.

[9::Z12 .. 3] == []
enumFromTo_cyc (9::Z12) 3 == [9,10,11,0,1,2,3]

to_Z12 :: Integral i => i -> Z12 Source #

Convert integral to Z12.

map to_Z12 [-9,-3,0,13] == [3,9,0,1]

from_Z12 :: Integral i => Z12 -> i Source #

Convert Z12 to integral.

complement :: [Z12] -> [Z12] Source #

Z12 not in set.

complement [0,2,4,5,7,9,11] == [1,3,6,8,10]

z12_to_char :: Z12 -> Char Source #

Z12 to character (10 -> A, 11 -> B).

map z12_to_char [0 .. 11] == "0123456789AB"

char_to_z12 :: Char -> Z12 Source #

Z12 to character (10 -> A, 11 -> B).

map char_to_z12 "0123456789AB" == [0..11]

z12_set_pp :: [Z12] -> String Source #

Unordered set notation (braces).

z12_set_pp [0,1,3] == "{013}"

z12_seq_pp :: [Z12] -> String Source #

Ordered sequence notation (angle brackets).

z12_seq_pp [0,1,3] == "<013>"

z12_vec_pp :: [Z12] -> String Source #

Ordered vector notation (square brackets).

z12_vec_pp [0,1,3] == "[013]"