In the thread "Precise timing", in response to something ugly I was doing, Rohan Drape provided the following code:

import Control.Concurrent
import Control.Monad
import System.IO
import Sound.OSC

main = withMax $ mapM_ note (cycle [1,1,2])
withMax = withTransport (openUDP "127.0.0.1" 9000)
sin0 param val = sendMessage (Message "sin0" [string param,float val])
pause = liftIO . pauseThread . (* 0.1)
note n = do
sin0 "frq" 300
sin0 "amp" 1
pause n
sin0 "amp" 0
pause n

For days I have monkeyed with it, and studied the libraries it imports, and I  remain sorely confused.

How can the "a" in "IO a" be a handle?
Here are two type signatures:
openUDP :: String -> Int -> IO UDP
withTransport :: Transport t => IO t -> Connection t a -> IO a
Rohan's code makes clear that openUDP creates a handle representing the UDP connection. openUDP's type signature indicates that its output is an "IO UDP". How can I reconcile those two facts? When I read about the IO type, all sources seem to indicate that "IO a" represents a value of type "a" wrapped in an IO context. For instance, when putting Strings to the screen, one passes around "IO String" values. Until this OSC library, I had never seen the "a" in "IO a" represent a pipe; it had always represented data to be passed *through* a pipe.

Why the long signature?
When I ask for it, GHC provides the following additional type signatures:
  > :t pause pause :: Double -> transformers-0.3.0.0:Control.Monad.Trans.Reader.ReaderT UDP IO () 
What's up with that?

What type is note? (and related questions)
GHCI goes on:
    > :t sin0 sin0 :: (SendOSC m, Real n) => String -> n -> m () > :t note note :: Double -> transformers-0.3.0.0:Control.Monad.Trans.Reader.ReaderT UDP IO () 
note calls both sin0 and pause. It appears that note's type signature takes pause, but not sin0, into account, but I must be wrong about that.

sin0 returns a SendOSC. pause applies liftIO to pauseThread. The result must be a SendOSC too, because sin0 and pause are both called in the same do loop. SendOSC implements these three classes:
(Monad (ReaderT t io), Transport t, MonadIO io) => SendOSC (ReaderT t io)  
Is the liftIO that pause applies to pauseThread, then, the "default" liftIO defined in the MonadIO library?

How to read the "instances" portion of Hackage documentation?
In the Hackage documentation for the SendOSC type, how should I be reading this line?
(Monad (ReaderT t io), Transport t, MonadIO io) => SendOSC (ReaderT t io) 
I understand the middle two clauses: that io should be of type MonadIO, and t should be of type Transport. The outer two clauses, though, I don't know how to interpret. (I looked at the code and saw nothing that clearly corresponded to that line in the documentation.)