module Music.Theory.Z12 where
import Data.List
newtype Z12 = Z12 Int deriving (Eq,Ord,Integral,Real)
instance Enum Z12 where
pred = subtract 1
succ = (+) 1
toEnum = fromIntegral
fromEnum = fromIntegral
enumFromThenTo n m o =
let m' = m + (m n)
in if m' == o then [n,m,o] else n : enumFromThenTo m m' o
enumFromTo n m =
let n' = succ n
in if n' == m then [n,m] else n : enumFromTo n' m
instance Bounded Z12 where
minBound = Z12 0
maxBound = Z12 11
z12_modulo :: Z12
z12_modulo = Z12 12
z12_showsPrec :: Int -> Z12 -> ShowS
z12_showsPrec p (Z12 i) =
let x = showsPrec p i
in if i < 0 || i > 11
then showString "(Z12 " . x . showString ")"
else x
instance Show Z12 where showsPrec = z12_showsPrec
lift_unary_Z12 :: (Int -> Int) -> Z12 -> Z12
lift_unary_Z12 f (Z12 a) = Z12 (f a `mod` 12)
lift_binary_Z12 :: (Int -> Int -> Int) -> Z12 -> Z12 -> Z12
lift_binary_Z12 f (Z12 a) (Z12 b) = Z12 (mod (a `f` b) 12)
check_negative :: (Int -> Int) -> Z12 -> Z12
check_negative f (Z12 n) =
if n < 0
then error "check_negative: negative Z12"
else Z12 (f n)
instance Num Z12 where
(+) = lift_binary_Z12 (+)
() = lift_binary_Z12 ()
(*) = lift_binary_Z12 (*)
negate = lift_unary_Z12 negate
fromInteger n = Z12 (fromInteger n `mod` 12)
signum = check_negative signum
abs = check_negative abs
to_Z12 :: Integral i => i -> Z12
to_Z12 = fromIntegral
from_Z12 :: Integral i => Z12 -> i
from_Z12 = fromIntegral
complement :: [Z12] -> [Z12]
complement = (\\) [0 .. 11]