------------------------------------------------------------------------------ -- /home/renick/haskell/conductive-0.3c/MusicalEnvironment.hs -- created: Sun Sep 16 22:19:28 JST 2012 ------------------------------------------------------------------------------ module Sound.Conductive.MusicalEnvironment where import Control.Concurrent.STM import Sound.Conductive.ConductiveBaseData import Sound.Conductive.MusicalTime import Sound.Conductive.MutableMap -- for getItem store item e = ... use -- (store e) ?@ item -- for withItem store func e item = ... use -- withKey (store e) item func -- | returns a list of the names of all Players stored in a MusicalEnvironment players :: MusicalEnvironment -> IO [String] players e = keys $ playerStore e -- | returns a list of the names of all TempoClocks stored in a MusicalEnvironment tempoClocks :: MusicalEnvironment -> IO [String] tempoClocks e = keys $ tempoClockStore e -- | returns a list of the names of all IOI functions stored in a MusicalEnvironment iOIs :: MusicalEnvironment -> IO [String] iOIs e = keys $ iOIStore e -- | returns a list of the names of all action functions stored in a MusicalEnvironment actions :: MusicalEnvironment -> IO [String] actions e = keys $ actionStore e -- | returns a list of the names of all interrupt functions stored in a MusicalEnvironment interrupts :: MusicalEnvironment -> IO [String] interrupts e = keys $ interruptStore e -- don't like this, but it really is more convenient than using withKey directly. what's a better way? withPlayer :: MusicalEnvironment -> (Player -> a) -> String -> IO (Maybe a) withPlayer e func k = withKey (playerStore e) func k withTempoClock :: MusicalEnvironment -> (TempoClock -> a) -> String -> IO (Maybe a) withTempoClock e func k = withKey (tempoClockStore e) func k withIOI :: MusicalEnvironment -> ((MusicalEnvironment -> Player -> Double -> Double -> IO Double) -> a) -> String -> IO (Maybe a) withIOI e func k = withKey (iOIStore e) func k withAction :: MusicalEnvironment -> ((MusicalEnvironment -> Player -> Double -> Double -> IO ()) -> a) -> String -> IO (Maybe a) withAction e func k = withKey (actionStore e) func k withInterrupt :: MusicalEnvironment -> ([IO ()] -> a) -> String -> IO (Maybe a) withInterrupt e func k = withKey (interruptStore e) func k --- ------------------------------------------------------------------------------ --- for these functions, now use modifyMMap --- changePlayers --- changeTempoClocks --- changeIOIs --- changeActions --- changeInterrupts --- --- ------------------------------------------------------------------------------ --- for these functions from 0.2, now use addVal --- addPlayer -- (playerStore e) +@ (k,Player) --- addTempoClock --- addIOI --- addAction --- addInterrupt --- --- ------------------------------------------------------------------------------ --- for these functions from 0.2, now use deleteVal --- deletePlayer -- (playerStore e) -@ (k,Player) --- addTempoClock --- deleteTempoClock --- deleteIOI --- deleteAction --- deleteInterrupt --- --- ------------------------------------------------------------------------------ --- -- not crazy about the prefixed "e" in these function names... -- instead of them, use withTempoClock like this: -- withTempoClock e elapsedTime clockKey --- --- -- | convenience function for returning elapsed time from a stored TempoClock --- --- eElapsedTime :: MVar MusicalEnvironment -> String -> IO Double --- eElapsedTime e clock = withTempoClock elapsedTime e clock --- --- -- | convenience function for returning elapsed beats from a stored TempoClock --- --- eElapsedBeats :: MVar MusicalEnvironment -> String -> IO Double --- eElapsedBeats e clock = withTempoClock elapsedBeats e clock --- --- -- | convenience function for returning elapsed MusicalTime from a stored TempoClock --- --- getCurrentTime --- :: MVar MusicalEnvironment -> String -> IO MusicalTime --- getCurrentTime e clock = withTempoClock currentMusicalTime e clock --- --- -- | convenience function for returning elapsed MusicalTime as a string from a stored TempoClock --- --- showCurrentTime :: MVar MusicalEnvironment -> String -> IO [Char] --- showCurrentTime e clock = withTempoClock currentMusicalTime2 e clock --- --- -- | convenience function for returning the current Tempo from a stored TempoClock --- --- eCurrentTempo :: MVar MusicalEnvironment -> String -> IO Double --- eCurrentTempo e clock = do --- c <- getItem tempoClockStore e clock --- return $ currentTempo c --- --- -- | convenience function for returning the current TimeSignature from a stored TempoClock --- --- eCurrentTimeSignature --- :: MVar MusicalEnvironment -> String -> IO Int --- eCurrentTimeSignature e clock = withTempoClock currentTimeSignature e clock --- -- -- is there a better way for these two? --- -- | convenience function for changing the current Tempo of a stored TempoClock eChangeTempo :: MusicalEnvironment -> String -> Double -> IO () eChangeTempo e clock nt = do Just tc <- (tempoClockStore e) ?@ clock ntc <- changeTempo tc nt (tempoClockStore e) +@ (clock,ntc) --- --- -- | convenience function for changing the current TimeSignature of a stored TempoClock eChangeTimeSignature :: MusicalEnvironment -> String -> Int -> IO () eChangeTimeSignature e clock nt = do Just tc <- (tempoClockStore e) ?@ clock ntc <- changeTimeSignature tc nt (tempoClockStore e) +@ (clock,ntc)