module Music.Score.Part (
HasPart(..),
HasPart',
PartT(..),
extract,
extractParts,
mapPart,
mapAllParts,
mapParts,
getParts,
setParts,
modifyParts,
(</>),
moveParts,
moveToPart,
) where
import Control.Monad (ap, mfilter, join, liftM, MonadPlus(..))
import Data.Semigroup
import Data.String
import Data.Foldable
import Data.Typeable
import Data.Ord (comparing)
import Data.Traversable
import qualified Data.List as List
import Data.VectorSpace
import Data.AffineSpace
import Data.Ratio
import Music.Time
class HasPart a where
type Part a :: *
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, Typeable)
instance HasPart () where { type Part () = Integer ; getPart _ = 0 }
instance HasPart Double where { type Part Double = Integer ; getPart _ = 0 }
instance HasPart Float where { type Part Float = Integer ; getPart _ = 0 }
instance HasPart Int where { type Part Int = Integer ; getPart _ = 0 }
instance HasPart Integer where { type Part Integer = Integer ; getPart _ = 0 }
instance Integral a => HasPart (Ratio a) where { type Part (Ratio a) = Integer ; getPart _ = 0 }
type HasPart' a = (Ord (Part a), HasPart a)
extract :: (HasPart' a, MonadPlus s, Performable s) => s a -> [s a]
extract sc = fmap (`extract'` sc) (getParts sc)
where
extract' v = mfilter ((== v) . getPart)
extractParts :: (HasPart' a, MonadPlus s, Performable s) => s a -> [(Part a, s a)]
extractParts sc = fmap (`extractParts2` sc) (getParts sc)
where
extractParts2 v = (\x -> (v,x)) . mfilter ((== v) . getPart)
mapPart :: (Ord v, v ~ Part a, HasPart a, MonadPlus s, Performable s, Enum b) => b -> (s a -> s a) -> s a -> s a
mapPart n f = mapAllParts (zipWith ($) (replicate (fromEnum n) id ++ [f] ++ repeat id))
mapAllParts :: (HasPart' a, MonadPlus s, Performable s) => ([s a] -> [s b]) -> s a -> s b
mapAllParts f = msum . f . extract
mapParts :: (HasPart' a, MonadPlus s, Performable s) => (s a -> s b) -> s a -> s b
mapParts f = mapAllParts (fmap f)
getParts :: (HasPart' a, Performable s) => s a -> [Part a]
getParts = List.sort . List.nub . fmap getPart . toList'
setParts :: (HasPart a, Functor s) => Part a -> s a -> s a
setParts n = fmap (setPart n)
modifyParts :: (HasPart a, Functor s) => (Part a -> Part a) -> s a -> s a
modifyParts n = fmap (modifyPart n)
infixr 6 </>
(</>) :: (HasPart' a, Enum (Part a), Functor s, MonadPlus s, Performable s) => s a -> s a -> s a
a </> b = a `mplus` moveParts offset b
where
offset = succ $ maximum' 0 $ fmap fromEnum $ getParts a
moveParts :: (HasPart' a, Enum (Part a), Integral b, Functor s) => b -> s a -> s a
moveParts x = modifyParts (successor x)
moveToPart :: (HasPart' a, Enum (Part a), Functor s) => Part a -> s a -> s a
moveToPart v = moveParts (fromEnum v)
successor :: (Integral b, Enum a) => b -> a -> a
successor n | n < 0 = (!! fromIntegral (abs n)) . iterate pred
| n >= 0 = (!! fromIntegral n) . iterate succ
maximum' :: (Ord a, Foldable t) => a -> t a -> a
maximum' z = option z getMax . foldMap (Option . Just . Max)
minimum' :: (Ord a, Foldable t) => a -> t a -> a
minimum' z = option z getMin . foldMap (Option . Just . Min)