\begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: portable
-- This module implements interface between Haskell representation and file
-- representation
module Music.Analysis.Interface where
import Music.Analysis.PF (mapL, concatL, (><), split, p1, p2)
import Music.Analysis.Base (Number)
import Music.Analysis.Abstract.Settings (Settings, getNumber)
import Music.Analysis.Abstract.Motive (Motive, toMotive, fromMotive)
import Music.Analysis.Abstract.Rhythm (RhythmNode, durationNode)
import Data.List (sum, (++))
import Data.Bool (Bool(..), otherwise)
import Data.Maybe (maybe)
import Data.Ord (Ord(..))
import Data.Tuple (uncurry)
import Data.Function ((.), id)
import Data.Char (String)
import Prelude (Num(..))
\end{code} This class define architecture to implements interfaces. \begin{code}
-- * Interface
-- | makes generic interface 
class Interface a where
    -- | reads interface
    input :: String -> a
    -- | prints interface
    output :: a -> String
\end{code} Measure computing are defined to output this information that is ignored on our model. \begin{code}
-- * Build/Consume Measures
-- | destroy measures
catMeasures :: Motive [a] -> Motive a
catMeasures = 
    toMotive .
        (id >< concatL) .
    fromMotive
-- | build measures
uncatMeasures :: Measure a => Motive a -> Motive [a]
uncatMeasures =
    toMotive .
        split p1 (uncurry (aux1 [])) .
    fromMotive 
    where
    aux1 :: Measure a => [a] -> Settings -> [a] -> [[a]]
    aux1 acc _ [] = [acc]
    aux1 acc s (h:t) | aux2 s acc h = aux1 (acc++[h]) s t
                     | otherwise = acc : aux1 [h] s t
    aux2 :: Measure a => Settings -> [a] -> a -> Bool
    aux2 s acc h = 
        (maybe 4 id . getNumber "CompassDown") s >= 
        (sum (mapL nodeDuration acc)) + nodeDuration h
-- | Measure class. 
class Measure a where
    nodeDuration :: a -> Number -- ^ computes node's duration
instance Measure RhythmNode where
    nodeDuration = durationNode
instance Measure (a, RhythmNode) where
    nodeDuration = nodeDuration . p2
instance Measure ((a,RhythmNode), b) where
    nodeDuration = nodeDuration . p2 . p1
instance Measure (((a, RhythmNode), b), c) where
    nodeDuration = nodeDuration . p2 . p1 . p1
\end{code}