------------------------------------------------------------------------------

-- IOI.hs
-- created: Fri Oct  1 23:21:25 JST 2010

------------------------------------------------------------------------------

-- | This module contains functions related to IOI functions and IOI lists.

module Sound.Conductive.IOI where

import Control.Concurrent.MVar
import Data.List
import Data.List.Utils
import Data.Maybe
import Sound.Conductive.ConductiveBaseData
import Sound.Conductive.MusicalEnvironment
import Sound.Conductive.MusicalTime
import Sound.Conductive.Player

-- | Creates an infinite length list from a start time and a finite list of relative time deltas

makeIOIList :: (Num a) => a -> [a] -> [a]
makeIOIList start source = deltasToAbsolutes start $ cycle source

-- | An IOI function which gets an IOI from an IOI list

-- The problem in this function is the error that accumulates from using doubles;
-- the use of minDiff below solves this problem, but it's an ugly hack, I feel.

iOIFromList
  :: MVar MusicalEnvironment -> Player -> String -> IO Double
iOIFromList e p m = let
    minDiff = 0.125
    start = playerStartingBeat p
    b = playerBeat p
    nextBeat pb bs = find (> (pb-start)) bs
    beatDiff opb pb bs = (fromJust $ nextBeat pb bs) - (opb - start)
    in do   il <- getIOIList e m
            let thisBeatDiff = beatDiff b b $ il
            if (thisBeatDiff < minDiff)
                then do let nb = sum [minDiff,thisBeatDiff,b]
                        let newBeatDiff = (beatDiff b nb il)
                        return newBeatDiff
                else return thisBeatDiff

-- | Creates an IOI list, adds it to the environment, and adds a lookup function for it to the MusicalEnvironment.

newIOIFunctionAndIOIList
  :: MVar MusicalEnvironment
     -> String
     -> Double
     -> [Double]
     -> IO MusicalEnvironment
newIOIFunctionAndIOIList env name startingBeat deltas = let
    newFunc e p = iOIFromList e p name
    newIOIList = makeIOIList startingBeat deltas
    in do addIOIList env (name,newIOIList)
          addIOI env (name,newFunc)