-- | Allen Forte. /The Structure of Atonal Music/. Yale University
-- Press, New Haven, 1973.
module Music.Theory.Z12.Forte_1973 where

import qualified Music.Theory.Z.Forte_1973 as Z
import Music.Theory.Z12

-- * Prime form

-- | T-related rotations of /p/.
--
-- > t_rotations [0,1,3] == [[0,1,3],[0,2,11],[0,9,10]]
t_rotations :: [Z12] -> [[Z12]]
t_rotations = Z.t_rotations id

-- | T\/I-related rotations of /p/.
--
-- > ti_rotations [0,1,3] == [[0,1,3],[0,2,11],[0,9,10]
-- >                         ,[0,9,11],[0,2,3],[0,1,10]]
ti_rotations :: [Z12] -> [[Z12]]
ti_rotations = Z.ti_rotations id

-- | Forte prime form, ie. 'cmp_prime' of 'forte_cmp'.
--
-- > forte_prime [0,1,3,6,8,9] == [0,1,3,6,8,9]
-- > forte_prime [0,2,3,6,7] == [0,1,4,5,7]
forte_prime :: [Z12] -> [Z12]
forte_prime = Z.forte_prime id

-- | Transpositional equivalence prime form, ie. 't_cmp_prime' of
-- 'forte_cmp'.
--
-- > (forte_prime [0,2,3],t_prime [0,2,3]) == ([0,1,3],[0,2,3])
t_prime :: [Z12] -> [Z12]
t_prime = Z.t_prime id

-- * Set Class Table

type SC_Name = Z.SC_Name

-- | The set-class table (Forte prime forms).
--
-- > length sc_table == 224
sc_table :: [(SC_Name,[Z12])]
sc_table = Z.sc_table

-- | Lookup a set-class name.  The input set is subject to
-- 'forte_prime' before lookup.
--
-- > sc_name [0,2,3,6,7] == "5-Z18"
-- > sc_name [0,1,4,6,7,8] == "6-Z17"
sc_name :: [Z12] -> SC_Name
sc_name = Z.sc_name id

-- > sc_name_long [0,1,4,6,7,8] == "6-Z17[012478]"
sc_name_long :: [Z12] -> SC_Name
sc_name_long = Z.sc_name_long id

-- | Lookup a set-class given a set-class name.
--
-- > sc "6-Z17" == [0,1,2,4,7,8]
sc :: SC_Name -> [Z12]
sc = Z.sc

{- | List of set classes (the set class universe).

> let r = [("0-1",[0,0,0,0,0,0])
>         ,("1-1",[0,0,0,0,0,0])
>         ,("2-1",[1,0,0,0,0,0])
>         ,("2-2",[0,1,0,0,0,0])
>         ,("2-3",[0,0,1,0,0,0])
>         ,("2-4",[0,0,0,1,0,0])
>         ,("2-5",[0,0,0,0,1,0])
>         ,("2-6",[0,0,0,0,0,1])
>         ,("3-1",[2,1,0,0,0,0])
>         ,("3-2",[1,1,1,0,0,0])
>         ,("3-3",[1,0,1,1,0,0])
>         ,("3-4",[1,0,0,1,1,0])
>         ,("3-5",[1,0,0,0,1,1])
>         ,("3-6",[0,2,0,1,0,0])
>         ,("3-7",[0,1,1,0,1,0])
>         ,("3-8",[0,1,0,1,0,1])
>         ,("3-9",[0,1,0,0,2,0])
>         ,("3-10",[0,0,2,0,0,1])
>         ,("3-11",[0,0,1,1,1,0])
>         ,("3-12",[0,0,0,3,0,0])
>         ,("4-1",[3,2,1,0,0,0])
>         ,("4-2",[2,2,1,1,0,0])
>         ,("4-3",[2,1,2,1,0,0])
>         ,("4-4",[2,1,1,1,1,0])
>         ,("4-5",[2,1,0,1,1,1])
>         ,("4-6",[2,1,0,0,2,1])
>         ,("4-7",[2,0,1,2,1,0])
>         ,("4-8",[2,0,0,1,2,1])
>         ,("4-9",[2,0,0,0,2,2])
>         ,("4-10",[1,2,2,0,1,0])
>         ,("4-11",[1,2,1,1,1,0])
>         ,("4-12",[1,1,2,1,0,1])
>         ,("4-13",[1,1,2,0,1,1])
>         ,("4-14",[1,1,1,1,2,0])
>         ,("4-Z15",[1,1,1,1,1,1])
>         ,("4-16",[1,1,0,1,2,1])
>         ,("4-17",[1,0,2,2,1,0])
>         ,("4-18",[1,0,2,1,1,1])
>         ,("4-19",[1,0,1,3,1,0])
>         ,("4-20",[1,0,1,2,2,0])
>         ,("4-21",[0,3,0,2,0,1])
>         ,("4-22",[0,2,1,1,2,0])
>         ,("4-23",[0,2,1,0,3,0])
>         ,("4-24",[0,2,0,3,0,1])
>         ,("4-25",[0,2,0,2,0,2])
>         ,("4-26",[0,1,2,1,2,0])
>         ,("4-27",[0,1,2,1,1,1])
>         ,("4-28",[0,0,4,0,0,2])
>         ,("4-Z29",[1,1,1,1,1,1])
>         ,("5-1",[4,3,2,1,0,0])
>         ,("5-2",[3,3,2,1,1,0])
>         ,("5-3",[3,2,2,2,1,0])
>         ,("5-4",[3,2,2,1,1,1])
>         ,("5-5",[3,2,1,1,2,1])
>         ,("5-6",[3,1,1,2,2,1])
>         ,("5-7",[3,1,0,1,3,2])
>         ,("5-8",[2,3,2,2,0,1])
>         ,("5-9",[2,3,1,2,1,1])
>         ,("5-10",[2,2,3,1,1,1])
>         ,("5-11",[2,2,2,2,2,0])
>         ,("5-Z12",[2,2,2,1,2,1])
>         ,("5-13",[2,2,1,3,1,1])
>         ,("5-14",[2,2,1,1,3,1])
>         ,("5-15",[2,2,0,2,2,2])
>         ,("5-16",[2,1,3,2,1,1])
>         ,("5-Z17",[2,1,2,3,2,0])
>         ,("5-Z18",[2,1,2,2,2,1])
>         ,("5-19",[2,1,2,1,2,2])
>         ,("5-20",[2,1,1,2,3,1])
>         ,("5-21",[2,0,2,4,2,0])
>         ,("5-22",[2,0,2,3,2,1])
>         ,("5-23",[1,3,2,1,3,0])
>         ,("5-24",[1,3,1,2,2,1])
>         ,("5-25",[1,2,3,1,2,1])
>         ,("5-26",[1,2,2,3,1,1])
>         ,("5-27",[1,2,2,2,3,0])
>         ,("5-28",[1,2,2,2,1,2])
>         ,("5-29",[1,2,2,1,3,1])
>         ,("5-30",[1,2,1,3,2,1])
>         ,("5-31",[1,1,4,1,1,2])
>         ,("5-32",[1,1,3,2,2,1])
>         ,("5-33",[0,4,0,4,0,2])
>         ,("5-34",[0,3,2,2,2,1])
>         ,("5-35",[0,3,2,1,4,0])
>         ,("5-Z36",[2,2,2,1,2,1])
>         ,("5-Z37",[2,1,2,3,2,0])
>         ,("5-Z38",[2,1,2,2,2,1])
>         ,("6-1",[5,4,3,2,1,0])
>         ,("6-2",[4,4,3,2,1,1])
>         ,("6-Z3",[4,3,3,2,2,1])
>         ,("6-Z4",[4,3,2,3,2,1])
>         ,("6-5",[4,2,2,2,3,2])
>         ,("6-Z6",[4,2,1,2,4,2])
>         ,("6-7",[4,2,0,2,4,3])
>         ,("6-8",[3,4,3,2,3,0])
>         ,("6-9",[3,4,2,2,3,1])
>         ,("6-Z10",[3,3,3,3,2,1])
>         ,("6-Z11",[3,3,3,2,3,1])
>         ,("6-Z12",[3,3,2,2,3,2])
>         ,("6-Z13",[3,2,4,2,2,2])
>         ,("6-14",[3,2,3,4,3,0])
>         ,("6-15",[3,2,3,4,2,1])
>         ,("6-16",[3,2,2,4,3,1])
>         ,("6-Z17",[3,2,2,3,3,2])
>         ,("6-18",[3,2,2,2,4,2])
>         ,("6-Z19",[3,1,3,4,3,1])
>         ,("6-20",[3,0,3,6,3,0])
>         ,("6-21",[2,4,2,4,1,2])
>         ,("6-22",[2,4,1,4,2,2])
>         ,("6-Z23",[2,3,4,2,2,2])
>         ,("6-Z24",[2,3,3,3,3,1])
>         ,("6-Z25",[2,3,3,2,4,1])
>         ,("6-Z26",[2,3,2,3,4,1])
>         ,("6-27",[2,2,5,2,2,2])
>         ,("6-Z28",[2,2,4,3,2,2])
>         ,("6-Z29",[2,2,4,2,3,2])
>         ,("6-30",[2,2,4,2,2,3])
>         ,("6-31",[2,2,3,4,3,1])
>         ,("6-32",[1,4,3,2,5,0])
>         ,("6-33",[1,4,3,2,4,1])
>         ,("6-34",[1,4,2,4,2,2])
>         ,("6-35",[0,6,0,6,0,3])
>         ,("6-Z36",[4,3,3,2,2,1])
>         ,("6-Z37",[4,3,2,3,2,1])
>         ,("6-Z38",[4,2,1,2,4,2])
>         ,("6-Z39",[3,3,3,3,2,1])
>         ,("6-Z40",[3,3,3,2,3,1])
>         ,("6-Z41",[3,3,2,2,3,2])
>         ,("6-Z42",[3,2,4,2,2,2])
>         ,("6-Z43",[3,2,2,3,3,2])
>         ,("6-Z44",[3,1,3,4,3,1])
>         ,("6-Z45",[2,3,4,2,2,2])
>         ,("6-Z46",[2,3,3,3,3,1])
>         ,("6-Z47",[2,3,3,2,4,1])
>         ,("6-Z48",[2,3,2,3,4,1])
>         ,("6-Z49",[2,2,4,3,2,2])
>         ,("6-Z50",[2,2,4,2,3,2])
>         ,("7-1",[6,5,4,3,2,1])
>         ,("7-2",[5,5,4,3,3,1])
>         ,("7-3",[5,4,4,4,3,1])
>         ,("7-4",[5,4,4,3,3,2])
>         ,("7-5",[5,4,3,3,4,2])
>         ,("7-6",[5,3,3,4,4,2])
>         ,("7-7",[5,3,2,3,5,3])
>         ,("7-8",[4,5,4,4,2,2])
>         ,("7-9",[4,5,3,4,3,2])
>         ,("7-10",[4,4,5,3,3,2])
>         ,("7-11",[4,4,4,4,4,1])
>         ,("7-Z12",[4,4,4,3,4,2])
>         ,("7-13",[4,4,3,5,3,2])
>         ,("7-14",[4,4,3,3,5,2])
>         ,("7-15",[4,4,2,4,4,3])
>         ,("7-16",[4,3,5,4,3,2])
>         ,("7-Z17",[4,3,4,5,4,1])
>         ,("7-Z18",[4,3,4,4,4,2])
>         ,("7-19",[4,3,4,3,4,3])
>         ,("7-20",[4,3,3,4,5,2])
>         ,("7-21",[4,2,4,6,4,1])
>         ,("7-22",[4,2,4,5,4,2])
>         ,("7-23",[3,5,4,3,5,1])
>         ,("7-24",[3,5,3,4,4,2])
>         ,("7-25",[3,4,5,3,4,2])
>         ,("7-26",[3,4,4,5,3,2])
>         ,("7-27",[3,4,4,4,5,1])
>         ,("7-28",[3,4,4,4,3,3])
>         ,("7-29",[3,4,4,3,5,2])
>         ,("7-30",[3,4,3,5,4,2])
>         ,("7-31",[3,3,6,3,3,3])
>         ,("7-32",[3,3,5,4,4,2])
>         ,("7-33",[2,6,2,6,2,3])
>         ,("7-34",[2,5,4,4,4,2])
>         ,("7-35",[2,5,4,3,6,1])
>         ,("7-Z36",[4,4,4,3,4,2])
>         ,("7-Z37",[4,3,4,5,4,1])
>         ,("7-Z38",[4,3,4,4,4,2])
>         ,("8-1",[7,6,5,4,4,2])
>         ,("8-2",[6,6,5,5,4,2])
>         ,("8-3",[6,5,6,5,4,2])
>         ,("8-4",[6,5,5,5,5,2])
>         ,("8-5",[6,5,4,5,5,3])
>         ,("8-6",[6,5,4,4,6,3])
>         ,("8-7",[6,4,5,6,5,2])
>         ,("8-8",[6,4,4,5,6,3])
>         ,("8-9",[6,4,4,4,6,4])
>         ,("8-10",[5,6,6,4,5,2])
>         ,("8-11",[5,6,5,5,5,2])
>         ,("8-12",[5,5,6,5,4,3])
>         ,("8-13",[5,5,6,4,5,3])
>         ,("8-14",[5,5,5,5,6,2])
>         ,("8-Z15",[5,5,5,5,5,3])
>         ,("8-16",[5,5,4,5,6,3])
>         ,("8-17",[5,4,6,6,5,2])
>         ,("8-18",[5,4,6,5,5,3])
>         ,("8-19",[5,4,5,7,5,2])
>         ,("8-20",[5,4,5,6,6,2])
>         ,("8-21",[4,7,4,6,4,3])
>         ,("8-22",[4,6,5,5,6,2])
>         ,("8-23",[4,6,5,4,7,2])
>         ,("8-24",[4,6,4,7,4,3])
>         ,("8-25",[4,6,4,6,4,4])
>         ,("8-26",[4,5,6,5,6,2])
>         ,("8-27",[4,5,6,5,5,3])
>         ,("8-28",[4,4,8,4,4,4])
>         ,("8-Z29",[5,5,5,5,5,3])
>         ,("9-1",[8,7,6,6,6,3])
>         ,("9-2",[7,7,7,6,6,3])
>         ,("9-3",[7,6,7,7,6,3])
>         ,("9-4",[7,6,6,7,7,3])
>         ,("9-5",[7,6,6,6,7,4])
>         ,("9-6",[6,8,6,7,6,3])
>         ,("9-7",[6,7,7,6,7,3])
>         ,("9-8",[6,7,6,7,6,4])
>         ,("9-9",[6,7,6,6,8,3])
>         ,("9-10",[6,6,8,6,6,4])
>         ,("9-11",[6,6,7,7,7,3])
>         ,("9-12",[6,6,6,9,6,3])
>         ,("10-1",[9,8,8,8,8,4])
>         ,("10-2",[8,9,8,8,8,4])
>         ,("10-3",[8,8,9,8,8,4])
>         ,("10-4",[8,8,8,9,8,4])
>         ,("10-5",[8,8,8,8,9,4])
>         ,("10-6",[8,8,8,8,8,5])
>         ,("11-1",[10,10,10,10,10,5])
>         ,("12-1",[12,12,12,12,12,6])]
> in let icvs = map icv scs in zip (map sc_name scs) icvs == r

-}
scs :: [[Z12]]
scs = Z.scs

-- | Cardinality /n/ subset of 'scs'.
--
-- > map (length . scs_n) [1..11] == [1,6,12,29,38,50,38,29,12,6,1]
scs_n :: Integral i => i -> [[Z12]]
scs_n = Z.scs_n

-- * BIP Metric

-- | Basic interval pattern, see Allen Forte \"The Basic Interval Patterns\"
-- /JMT/ 17/2 (1973):234-272
--
-- >>> pct bip 0t95728e3416
-- 11223344556
--
-- > bip [0,10,9,5,7,2,8,11,3,4,1,6] == [1,1,2,2,3,3,4,4,5,5,6]
-- > bip (pco "0t95728e3416") == [1,1,2,2,3,3,4,4,5,5,6]
bip :: [Z12] -> [Z12]
bip = map int_to_Z12 . Z.bip 12 . map int_from_Z12

-- * ICV Metric

-- | Interval class of Z12 interval /i/.
--
-- > map ic [5,6,7] == [5,6,5]
-- > map ic [-13,-1,0,1,13] == [1,1,0,1,1]
ic :: Z12 -> Z12
ic = int_to_Z12 . Z.ic 12 . int_from_Z12

-- | Forte notation for interval class vector.
--
-- > icv [0,1,2,4,7,8] == [3,2,2,3,3,2]
icv :: Integral i => [Z12] -> [i]
icv = map fromInteger . Z.icv 12 . map int_from_Z12

-- | Type specialise...
icv' :: [Z12] -> [Int]
icv' = icv

-- * Z-relation

-- | Locate /Z/ relation of set class.
--
-- > fmap sc_name (z_relation_of (sc "7-Z12")) == Just "7-Z36"
z_relation_of :: [Z12] -> Maybe [Z12]
z_relation_of = fmap (map int_to_Z12) . Z.z_relation_of 12 . map int_from_Z12