[Haskell-cafe] How to avoid floods of fromIntegral (in ALSA.Sequencer)

martin martin.drautzburg at web.de
Sun Nov 3 13:46:53 UTC 2013


Hello all,

in my recent attempts to work with ALSA.Sequencer, I frequently stumble across the problem that this library uses
GHC.Word.Word8 (don't know where this comes from), but I am passing in plain Ints. Adding a fromIntegral solves this
issue, but I end up with code like the following:

type T = Int -- time
type C = Int -- channel
type N = Int -- note
type V = Int -- velocity
type L = Int -- LSB
type M = Int -- MSB
type P = Int -- program
type X = Int -- something

data DtzEvent = NoteOn C N V
          | NoteOff C N V
          | ProgChange C P
          | PitchBend C X
          | BankSelMsb C X
          | BankSelLsb C X
...

playSong :: DtzEvents -> IO()
playSong events = runContT (foo "128:0" 120 (map render events)) print
         where
             render (t,(NoteOn c n v)) = ((fromIntegral t), noteOn (fromIntegral c) (fromIntegral n) (fromIntegral v))
             render (t,(NoteOff c n v)) = ((fromIntegral t), noteOff (fromIntegral c) (fromIntegral n) (fromIntegral v))
             render (t,(ProgChange c p)) = ((fromIntegral t), progChange (fromIntegral c) (fromIntegral p))
             render (t,(PitchBend c x)) = ((fromIntegral t), pitchBend (fromIntegral c) (fromIntegral x))
             render (t,(BankSelMsb c x)) = ((fromIntegral t), bankSelMsb (fromIntegral c) (fromIntegral x))
             render (t,(BankSelLsb c x)) = ((fromIntegral t), bankSelLsb (fromIntegral c) (fromIntegral x))

The last piece looks pretty ugly. Is there a way to avoid this?


More information about the Haskell-Cafe mailing list