Thanks to everyone, especially Bulat Ziganshin.
 
In http://haskell.org/haskellwiki/Modern_array_libraries there is enough information to do what I want.  It specifically mentions that it's OK to pass ByteArray# and MutableByteArray# to an "unsafe foreign" procedure as long as that procedure doesn't save the pointer, and that worked for me.
 
Here is what I ended up using, which worked great and the FFI usage for a couple of key functions sped up my code by a large factor:
import Data.Array.Base
import Data.Array.IO.Internals
import GHC.Exts
 
{-# INLINE unsafeByteArrayToPtr #-}
unsafeByteArrayToPtr :: IOUArray Int Word32 -> Ptr Word32
unsafeByteArrayToPtr (IOUArray (STUArray _ _ array#)) = Ptr (unsafeCoerce# array#)
 
Possibly a better thing to do would be to declare that the call takes a MutableByteArray# directly in the foreign import statement, which I believe would let me avoid using unsafeCoerce# at all, but this was good enough for my purposes.
 
Afterwards I used -ddump-simpl to check on the generated Core for the foreign call and it looked good.
 
  -- ryan