------------------------------------------------------------------------------ -- MusicalEnvironment.hs -- created: Fri Oct 1 23:21:13 JST 2010 ------------------------------------------------------------------------------ module Sound.Conductive.MusicalEnvironment ( actions , addAction , addDoubleGenerator , addIOI , addIOIList , addInterrupt , addNewGenerator , addPlayer , addTempoClock , changeActions , changeDoubleGenerators , changeEnvironment , changeIOILists , changeIOIs , changeInterrupts , changePlayers , changeTempoClocks , deleteAction , deleteDoubleGenerator , deleteIOI , deleteIOIList , deleteInterrupt , deletePlayer , deleteTempoClock , doubleGenerators , eChangeTempo , eChangeTimeSignature , eCurrentTempo , eCurrentTimeSignature , eElapsedBeats , eElapsedTime , getAction , getCurrentTime , getDoubleGenerator , getIOI , getIOIList , getInterrupt , getPlayer , getTempoClock , iOIs , iOILists , interrupts , players , showCurrentTime , tempoClocks , withAction , withDoubleGenerator , withEnvironment , withIOI , withIOIList , withInterrupt , withPlayer , withTempoClock ) where import Control.Concurrent.MVar import Data.Map import Sound.Conductive.ConductiveBaseData import Sound.Conductive.Generator import Sound.Conductive.MusicalTime import Sound.Conductive.MVarUtils environmentStoreKeys :: MVar a -> (a -> Data.Map.Map k a1) -> IO [k] environmentStoreKeys e sRecord = wm e $ (\x -> keys $ sRecord x) -- | allows a pure function to be run on a MusicalEnvironment stored in an MVar withEnvironment :: MVar a -> (a -> a1) -> IO a1 withEnvironment e func = wm e func -- | used to update a MusicalEnvironment stored in an MVar changeEnvironment :: MVar a -> (a -> a) -> IO a changeEnvironment e func = wcm e func withStore :: (t -> a) -> (a -> b) -> t -> b withStore store func e = func $ store e -- | allows a pure function to be run on a store (first argument) in a MusicalEnvironment in an MVar withMEStore :: (a -> a1) -> (a1 -> b) -> MVar a -> IO b withMEStore store func e = withEnvironment e $ withStore store func getItem :: (Ord k) => (a -> Data.Map.Map k a1) -> k -> MVar a -> IO a1 getItem store item e = withMEStore store (\x -> x ! item) e ------------------------------------------------------------------------------ -- boilerplate -- functions to retrieve an item from a MusicalEnvironment in an MVar -- | returns a Player from a MusicalEnvironment in an MVar getPlayer :: MVar MusicalEnvironment -> String -> IO Player getPlayer e n = getItem playerStore n e -- | returns a TempoClock from a MusicalEnvironment in an MVar getTempoClock :: MVar MusicalEnvironment -> String -> IO TempoClock getTempoClock e n = getItem tempoClockStore n e -- | returns an IOI function from a MusicalEnvironment in an MVar getIOI :: MVar MusicalEnvironment -> String -> IO (MVar MusicalEnvironment -> Player -> IO Double) getIOI e n = getItem iOIStore n e -- | returns an action function from a MusicalEnvironment in an MVar getAction :: MVar MusicalEnvironment -> String -> IO (MVar MusicalEnvironment -> Player -> IO ()) getAction e n = getItem actionStore n e -- | returns an interrupt function from a MusicalEnvironment in an MVar getInterrupt :: MVar MusicalEnvironment -> String -> IO [IO ()] getInterrupt e n = getItem interruptStore n e -- | returns a double Generator from a MusicalEnvironment in an MVar getDoubleGenerator :: MVar MusicalEnvironment -> String -> IO (Generator Double) getDoubleGenerator e n = getItem doubleGeneratorStore n e -- | returns an IOI list from a MusicalEnvironment in an MVar getIOIList :: MVar MusicalEnvironment -> String -> IO [Double] getIOIList e n = getItem iOIListStore n e ------------------------------------------------------------------------------ withItem :: (Ord k) => (a -> Data.Map.Map k a1) -> k -> (a1 -> IO b) -> MVar a -> IO b withItem store item func e = getItem store item e >>= \i -> func i ------------------------------------------------------------------------------ -- irritating boilerplate -- functions to run a function on an item from a MusicalEnvironment in an MVar -- | runs a pure function on a stored Player withPlayer :: (Player -> IO b) -> MVar MusicalEnvironment -> String -> IO b withPlayer func e n = withItem playerStore n func e -- | runs a pure function on a stored TempoClock withTempoClock :: (TempoClock -> IO b) -> MVar MusicalEnvironment -> String -> IO b withTempoClock func e n = withItem tempoClockStore n func e -- | runs a pure function on a stored IOI function withIOI :: ((MVar MusicalEnvironment -> Player -> IO Double) -> IO b) -> MVar MusicalEnvironment -> String -> IO b withIOI func e n = withItem iOIStore n func e -- | runs a pure function on a stored action function withAction :: ((MVar MusicalEnvironment -> Player -> IO ()) -> IO b) -> MVar MusicalEnvironment -> String -> IO b withAction func e n = withItem actionStore n func e -- | runs a pure function on a stored interrupt function withInterrupt :: ([IO ()] -> IO b) -> MVar MusicalEnvironment -> String -> IO b withInterrupt func e n = withItem interruptStore n func e -- | runs a pure function on a stored double Generator withDoubleGenerator :: (Generator Double -> IO b) -> MVar MusicalEnvironment -> String -> IO b withDoubleGenerator func e n = withItem doubleGeneratorStore n func e -- | runs a pure function on a stored IOI List withIOIList :: ([Double] -> IO b) -> MVar MusicalEnvironment -> String -> IO b withIOIList func e n = withItem iOIListStore n func e ------------------------------------------------------------------------------ storeKeys :: (a -> Data.Map.Map k a1) -> MVar a -> IO [k] storeKeys store e = withMEStore store keys e ------------------------------------------------------------------------------ -- annoying boilerplate -- functions to get all items of a type from a MusicalEnvironment in an MVar -- | returns a list of the names of all Players stored in a MusicalEnvironment players :: MVar MusicalEnvironment -> IO [String] players e = storeKeys playerStore e -- | returns a list of the names of all TempoClocks stored in a MusicalEnvironment tempoClocks :: MVar MusicalEnvironment -> IO [String] tempoClocks e = storeKeys tempoClockStore e -- | returns a list of the names of all IOI functions stored in a MusicalEnvironment iOIs :: MVar MusicalEnvironment -> IO [String] iOIs e = storeKeys iOIStore e -- | returns a list of the names of all action functions stored in a MusicalEnvironment actions :: MVar MusicalEnvironment -> IO [String] actions e = storeKeys actionStore e -- | returns a list of the names of all interrupt functions stored in a MusicalEnvironment interrupts :: MVar MusicalEnvironment -> IO [String] interrupts e = storeKeys interruptStore e -- | returns a list of the names of all double Generators stored in a MusicalEnvironment doubleGenerators :: MVar MusicalEnvironment -> IO [String] doubleGenerators e = storeKeys doubleGeneratorStore e -- | returns a list of the names of all IOI lists stored in a MusicalEnvironment iOILists :: MVar MusicalEnvironment -> IO [String] iOILists e = storeKeys iOIListStore e ------------------------------------------------------------------------------ -- more annoying boilerplate -- functions operating on the various stores in a MusicalEnvironment stored in an MVar -- | runs a pure function on the Map in a MusicalEnvironment containing the Players changePlayers :: (Data.Map.Map String Player -> Data.Map.Map String Player) -> MusicalEnvironment -> MusicalEnvironment changePlayers func e = e { playerStore = func $ playerStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the TempoClocks changeTempoClocks :: (Data.Map.Map String TempoClock -> Data.Map.Map String TempoClock) -> MusicalEnvironment -> MusicalEnvironment changeTempoClocks func e = e { tempoClockStore = func $ tempoClockStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the IOI functions changeIOIs :: (Data.Map.Map String (MVar MusicalEnvironment -> Player -> IO Double) -> Data.Map.Map String (MVar MusicalEnvironment -> Player -> IO Double)) -> MusicalEnvironment -> MusicalEnvironment changeIOIs func e = e { iOIStore = func $ iOIStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the action functions changeActions :: (Data.Map.Map String (MVar MusicalEnvironment -> Player -> IO ()) -> Data.Map.Map String (MVar MusicalEnvironment -> Player -> IO ())) -> MusicalEnvironment -> MusicalEnvironment changeActions func e = e { actionStore = func $ actionStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the interrupt functions changeInterrupts :: (Data.Map.Map String [IO ()] -> Data.Map.Map String [IO ()]) -> MusicalEnvironment -> MusicalEnvironment changeInterrupts func e = e { interruptStore = func $ interruptStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the double Generators changeDoubleGenerators :: (Data.Map.Map String (Generator Double) -> Data.Map.Map String (Generator Double)) -> MusicalEnvironment -> MusicalEnvironment changeDoubleGenerators func e = e { doubleGeneratorStore = func $ doubleGeneratorStore e } -- | runs a pure function on the Map in a MusicalEnvironment containing the IOI lists changeIOILists :: (Data.Map.Map String [Double] -> Data.Map.Map String [Double]) -> MusicalEnvironment -> MusicalEnvironment changeIOILists func e = e { iOIListStore = func $ iOIListStore e } ------------------------------------------------------------------------------ -- will the boilerplate never end? -- functions to add an item to a store in a MusicalEnvironment in an MVar -- | Add a Player to a MusicalEnvironment in an MVar addPlayer :: MVar MusicalEnvironment -> (String, Player) -> IO MusicalEnvironment addPlayer e (k,v) = changeEnvironment e $ changePlayers (insert k v) -- | Add a TempoClock to a MusicalEnvironment in an MVar addTempoClock :: MVar MusicalEnvironment -> (String, TempoClock) -> IO MusicalEnvironment addTempoClock e (k,v) = changeEnvironment e $ changeTempoClocks (insert k v) -- | Add an IOI function to a MusicalEnvironment in an MVar addIOI :: MVar MusicalEnvironment -> (String, MVar MusicalEnvironment -> Player -> IO Double) -> IO MusicalEnvironment addIOI e (k,v) = changeEnvironment e $ changeIOIs (insert k v) -- | Add an action function to a MusicalEnvironment in an MVar addAction :: MVar MusicalEnvironment -> (String, MVar MusicalEnvironment -> Player -> IO ()) -> IO MusicalEnvironment addAction e (k,v) = changeEnvironment e $ changeActions (insert k v) -- | Add an interrupt function to a MusicalEnvironment in an MVar addInterrupt :: MVar MusicalEnvironment -> (String, [IO ()]) -> IO MusicalEnvironment addInterrupt e (k,v) = changeEnvironment e $ changeInterrupts (insert k v) -- | Add a double Generator to a MusicalEnvironment in an MVar addDoubleGenerator :: MVar MusicalEnvironment -> (String, Generator Double) -> IO MusicalEnvironment addDoubleGenerator e (k,v) = changeEnvironment e $ changeDoubleGenerators (insert k v) -- | Add an IOI list to a MusicalEnvironment in an MVar addIOIList :: MVar MusicalEnvironment -> (String, [Double]) -> IO MusicalEnvironment addIOIList e (k,v) = changeEnvironment e $ changeIOILists (insert k v) -- | Add a double Generator to a MusicalEnvironment in an MVar addNewGenerator :: MVar MusicalEnvironment -> (String, [Double]) -> IO MusicalEnvironment addNewGenerator e (n,x) = newGenerator x >>= \g -> addDoubleGenerator e (n,g) ------------------------------------------------------------------------------ -- functions to delete items from a MusicalEnvironment in an MVar deleteItem :: (Ord k) => ((Data.Map.Map k a -> Data.Map.Map k a) -> t -> t1) -> k -> t -> t1 deleteItem changeFunc k e = changeFunc (delete k) e -- | Delete a Player to a MusicalEnvironment in an MVar deletePlayer :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deletePlayer e k = changeEnvironment e $ deleteItem (changePlayers) k -- | Delete a Tempo Clock from a MusicalEnvironment in an MVar deleteTempoClock :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteTempoClock e k = changeEnvironment e $ deleteItem (changeTempoClocks) k -- | Delete an IOI function from a MusicalEnvironment in an MVar deleteIOI :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteIOI e k = changeEnvironment e $ deleteItem (changeIOIs) k -- | Delete an action function from a MusicalEnvironment in an MVar deleteAction :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteAction e k = changeEnvironment e $ deleteItem (changeActions) k -- | Delete an interrupt function from a MusicalEnvironment in an MVar deleteInterrupt :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteInterrupt e k = changeEnvironment e $ deleteItem (changeInterrupts) k -- | Delete a double Generator from a MusicalEnvironment in an MVar deleteDoubleGenerator :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteDoubleGenerator e k = changeEnvironment e $ deleteItem (changeDoubleGenerators) k -- | Delete an IOI list from a MusicalEnvironment in an MVar deleteIOIList :: MVar MusicalEnvironment -> String -> IO MusicalEnvironment deleteIOIList e k = changeEnvironment e $ deleteItem (changeIOILists) k ------------------------------------------------------------------------------ -- not crazy about the prefixed "e" in these function names... -- | 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 <- getTempoClock 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 -- | convenience function for changing the current Tempo of a stored TempoClock eChangeTempo :: MVar MusicalEnvironment -> String -> Double -> IO MusicalEnvironment eChangeTempo e clock nt = do tc <- getItem tempoClockStore clock e ntc <- changeTempo tc nt addTempoClock e (clock,ntc) -- | convenience function for changing the current TimeSignature of a stored TempoClock eChangeTimeSignature :: MVar MusicalEnvironment -> String -> Int -> IO MusicalEnvironment eChangeTimeSignature e clock nts = do tc <- getItem tempoClockStore clock e ntc <- changeTimeSignature tc nts addTempoClock e (clock,ntc)