module Music.Score.Part (
Part,
HasPart(..),
HasPart',
PartT(..),
getParts,
) where
import Control.Applicative
import Control.Comonad
import Control.Monad.Plus
import Data.Default
import Data.Foldable
import qualified Data.List as List
import Data.Ord (comparing)
import Data.PairMonad
import Data.Ratio
import Data.Semigroup
import Data.Traversable
import Data.Typeable
import Music.Time
type family Part a :: *
class HasPart a where
getPart :: a -> Part a
setPart :: Part a -> a -> a
modifyPart :: (Part a -> Part a) -> a -> a
setPart n = modifyPart (const n)
modifyPart f x = x
newtype PartT n a = PartT { getPartT :: (n, a) }
deriving (Eq, Ord, Show, Functor, Applicative, Comonad, Monad, Typeable)
type instance Part () = Integer
type instance Part Double = Integer
type instance Part Float = Integer
type instance Part Int = Integer
type instance Part Integer = Integer
type instance Part (Ratio a) = Integer
instance HasPart () where { getPart _ = def }
instance HasPart Double where { getPart _ = def }
instance HasPart Float where { getPart _ = def }
instance HasPart Int where { getPart _ = def }
instance HasPart Integer where { getPart _ = def }
instance Integral a => HasPart (Ratio a) where { getPart _ = def }
type instance Part (PartT n a) = n
instance HasPart (PartT n a) where
getPart (PartT (v,_)) = v
modifyPart f (PartT (v,x)) = PartT (f v, x)
type instance Part (a,b) = Part b
instance HasPart b => HasPart (a,b) where
getPart (a,b) = getPart b
modifyPart f (a,b) = (a, modifyPart f b)
type HasPart' a = (Show (Part a), Ord (Part a), Default (Part a), HasPart a)
getParts :: (Foldable t, HasPart' a) => t a -> [Part a]
getParts = List.sort . List.nub . fmap getPart . toList