How to avoid floods of fromIntegral (in ALSA.Sequencer)

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?

It depends a bit: What is supposed to happen / what happens in your library when one of the numbers is larger than a Word8? That usually determines where / how the conversion fits in nicely. For example, if you already know that all the values in DtzEvent can only be Word8s, then they should probably already be Word8s and not Int. On 03/11/13 13:46, martin wrote:
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? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am 11/03/2013 03:35 PM, schrieb Niklas Hambüchen:
It depends a bit:
What is supposed to happen / what happens in your library when one of the numbers is larger than a Word8?
That usually determines where / how the conversion fits in nicely.
For example, if you already know that all the values in DtzEvent can only be Word8s, then they should probably already be Word8s and not Int.
Silly me, yes using Word8 instead of Ints got rid of most of the fromIntegrals. I didn't know that Word8 was an actual haskell type. Thought it was something private to ALSA.Sequencer. There is one remaining fromIntegral. This is "time" Couldn't match expected type `alsa-seq-0.6.0.2:Sound.ALSA.Sequencer.Marshal.Time.Tick' with actual type `T' This seems to be realy a private thing and I found to way other than fromIntegral to make the compiler happy.

For Word8, take a look at Data.Word - e.g.
http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Word.html
Doug
On Nov 3, 2013 12:36 PM, "martin"
Am 11/03/2013 03:35 PM, schrieb Niklas Hambüchen:
It depends a bit:
What is supposed to happen / what happens in your library when one of the numbers is larger than a Word8?
That usually determines where / how the conversion fits in nicely.
For example, if you already know that all the values in DtzEvent can only be Word8s, then they should probably already be Word8s and not Int.
Silly me,
yes using Word8 instead of Ints got rid of most of the fromIntegrals. I didn't know that Word8 was an actual haskell type. Thought it was something private to ALSA.Sequencer.
There is one remaining fromIntegral. This is "time"
Couldn't match expected type `alsa-seq-0.6.0.2:Sound.ALSA.Sequencer.Marshal.Time.Tick' with actual type `T'
This seems to be realy a private thing and I found to way other than fromIntegral to make the compiler happy.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You can factor out the fromIntegral t part using (***) from Control.Arrow. For functions,
(f *** g) (x,y) = (f x, g y)
Drop time (t) handling from render:
playSong :: DtzEvents -> IO() playSong events = runContT (foo "128:0" 120 (map (fromIntegral *** render) events)) print where render (NoteOn c n v) = noteOn c n v ...
-- Conal
On Sun, Nov 3, 2013 at 9:36 AM, martin
Am 11/03/2013 03:35 PM, schrieb Niklas Hambüchen:
It depends a bit:
What is supposed to happen / what happens in your library when one of the numbers is larger than a Word8?
That usually determines where / how the conversion fits in nicely.
For example, if you already know that all the values in DtzEvent can only be Word8s, then they should probably already be Word8s and not Int.
Silly me,
yes using Word8 instead of Ints got rid of most of the fromIntegrals. I didn't know that Word8 was an actual haskell type. Thought it was something private to ALSA.Sequencer.
There is one remaining fromIntegral. This is "time"
Couldn't match expected type `alsa-seq-0.6.0.2:Sound.ALSA.Sequencer.Marshal.Time.Tick' with actual type `T'
This seems to be realy a private thing and I found to way other than fromIntegral to make the compiler happy.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Conal Elliott
-
Doug Burke
-
martin
-
Niklas Hambüchen