-- | -- example: (you need a Wavfile (44100Hz, 16Bit, mono or stereo) named \"bassdrum.wav\") -- -- @ ghci @ -- -- @ :m Sound.Hommage Sound.Hommage.DSPlayer.UnsafeSimpleControl @ -- load the modules -- -- @ startAudio 4 @ -- start direct sound with a buffersize of 4*512 -- -- @ let s1 p = L $ Mono $ zipWith (*) (playADSR FitADR Linear (1,1,0.3,3) 20000) $ sinus $ repeat $ noteToFrequency 12 p @ -- define a simple synthesizer -- -- @ next $ (\\x -> [x]:replicate 11 []) =<< [s1 12, s1 24, s1 16, s1 19, s1 24, s1 12, s1 16, s1 19]) @ -- run a simple bassline (1 bar = 96 ticks) -- -- @ importSample \"bassdrum.wav\" @ -- load the bassdrum sample -- -- @ let b1 = concat $ replicate 4 ([S 0 (1,0)] : replicate 23 []) @ -- define a beat -- -- @ fnext $ zipWith (++) b1 @ -- add the beat to the current playing bassline -- -- @ fnext $ map $ filter $ \\e -> case e of { S 0 _ -> False; _ -> True } @ -- remove the bassdrum sample events from the current playing loop -- -- @ next [] @ -- silence -- -- @ :q @ -- module Sound.Hommage.DSPlayer.UnsafeSimpleControl ( startAudio , stopAudio , importSample , killAllVoices , ev , next , after , once , fnext , fafter , current , setBPM , module Sound.Hommage.DSPlayer.SimpleControl , module Sound.Hommage.DSPlayer.SimplePlayer ) where import Sound.Hommage.DSPlayer.SimpleControl import Sound.Hommage.DSPlayer.SimplePlayer import Sound.Hommage.DSPlayer.AudioSample import Control.Concurrent import Data.IORef import System.IO.Unsafe ------------------------------------------------------------------------------ {-# NOINLINE ref_simplecontrol #-} ref_simplecontrol :: IORef SimpleControl ref_simplecontrol = unsafePerformIO $ newIORef undefined ------------------------------------------------------------------------------ -- | Start DirectSound and the sequencer loop startAudio :: Int -> IO () startAudio latency = forkIO (startSimpleControl latency >>= writeIORef ref_simplecontrol) >> return () -- | Don't use this - quit ghci instead... stopAudio :: IO () stopAudio = readIORef ref_simplecontrol >>= \c -> stopSC c -- | Load an audiosample into RAM. The number\/ID of the sample is shown. -- -- example: @ loadSample \"bassdrum.wav\" @ (shows for example \"Loading Sample Nr. 5\") importSample :: FilePath -> IO () importSample fp = do sc <- readIORef ref_simplecontrol nr <- loadAudioSample (poolSC sc) fp putStrLn ("Loading Sample Nr. " ++ show nr) -- | Kill all current playing voices (lists and samples) killAllVoices :: IO () killAllVoices = readIORef ref_simplecontrol >>= \sc -> killSP (playerSC sc) -- | Set Beats-Per-Minute, (based on a 4-4-beat - so its equal to loops-per-4-minutes) -- -- example: @ setBPM 133.33 @ setBPM :: Double -> IO () setBPM x = readIORef ref_simplecontrol >>= \sc -> fptSP (playerSC sc) (round(44100/((max 1 x)*24/60))) -- | run an event ev :: Event -> IO () ev e = readIORef ref_simplecontrol >>= \sc -> runEvent sc e -- | set next loop (starting at next bar) next :: [[Event]] -> IO () next es = readIORef ref_simplecontrol >>= \sc -> setOnZeroLS (sequencerSC sc) True es -- | set next loop (starting at first bar after current events are played) after :: [[Event]] -> IO () after es = readIORef ref_simplecontrol >>= \sc -> setOnZeroLS (sequencerSC sc) False es -- | add some events to be played only once once :: [[Event]] -> IO () once es = readIORef ref_simplecontrol >>= \sc -> setOnceLS (sequencerSC sc) es -- | update next loop fnext :: ([[Event]]->[[Event]]) -> IO () fnext f = readIORef ref_simplecontrol >>= \sc -> updOnZeroLS (sequencerSC sc) True f -- | update next loop fafter :: ([[Event]]->[[Event]]) -> IO () fafter f = readIORef ref_simplecontrol >>= \sc -> updOnZeroLS (sequencerSC sc) False f -- | get next loop current :: IO [[Event]] current = readIORef ref_simplecontrol >>= \sc -> getOnZeroLS (sequencerSC sc)