This module implements generic Motive. This specifications fits Melodic Motive, Rhythm Motive and so on. \begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: portable
-- This module implements a generic Motive
module Music.Analysis.Abstract.Motive where
import Music.Analysis.PF ((><), cataL, mapL, p1, p2, split,
    anaL, grd, (-|-), e2m)
import Music.Analysis.Abstract.Settings (Settings, union, empty)
import Data.Tuple (curry, uncurry)
import Data.List (zip, head, tail)
import Data.Function ((.), id, const)
import Data.Maybe (maybe)
import Data.Eq (Eq(..))
import Prelude (Show, Read) 
\end{code} Basic definition is product between Settings and Sequence of nodes. These nodes contains music information. \begin{code}
-- | Motive Definition
data Motive a = Motive (Settings, [a]) 
    deriving (Eq, Show, Read)
-- | make new motive
mkMotive :: Settings -> [a] -> Motive a
mkMotive = curry Motive 
-- | get Internal Motive representation 
fromMotive :: Motive a -> (Settings, [a])
fromMotive (Motive x) = x
-- | get Motive from internal representation
toMotive :: (Settings, [a]) -> Motive a
toMotive = Motive
\end{code} Function meta is responsible for update Settings, nodes will be same. Next functions, like cataMotive and mapMotive are catamorphism and mapping applied to Motive data type. These functions doesn't change metadata at Settings. \begin{code}
-- * Combinators
meta :: (Settings -> Settings) -> Motive a -> Motive a
meta f = toMotive . (f >< id) . fromMotive
-- | General cata 
cataMotive :: b -> (Settings -> (a, b) -> b) -> Motive a -> (Settings, b)
cataMotive z f = split p1 (\(s,x) -> cataL (maybe z (f s)) x) . fromMotive
-- | General map 
mapMotive :: (Settings -> a -> b) -> Motive a -> Motive b
mapMotive f = toMotive . (split p1 (\(s,x) -> mapL (f s) x)) . fromMotive
\end{code} These functions are used to reusing functions. \begin{code}
-- | join Pair of Motive into Motive of Pair
joinMotivePair :: (Motive a, Motive b) -> Motive (a,b)
joinMotivePair = 
    toMotive . 
    (uncurry union >< uncurry zip) . 
    split (p1 >< p1) (p2 >< p2) .
    (fromMotive >< fromMotive) 
-- | Split Motive of Pair into Pair of Motive
splitMotivePair :: Motive (a,b) -> (Motive a, Motive b)
splitMotivePair = split (mapMotive (const p1)) (mapMotive (const p2))
-- | join List of Motive into Motive of List
joinMotiveList :: [Motive a] -> Motive [a]
joinMotiveList = 
    toMotive .
    cataL (maybe (empty,[]) (\((a,b),(c,d)) -> (a`union`c, b:d))) .
    mapL fromMotive
-- | split Motive of List into List of Motive
splitMotiveList :: Eq a => Motive [a] -> [Motive a]
splitMotiveList  = 
    mapL toMotive .
    anaL (e2m . (const () -|- split (id >< head) (id >< tail)) . grd ((==[]) . p2)) . 
    fromMotive
\end{code}