-------------------------------------------------------------------------------- -- | -- Module : Sound.ALSA.Sequencer.Marshal.QueueTimer -- Copyright : (c) Henning Thielemann, 2010 -- (c) Iavor S. Diatchki, 2007 -- License : BSD3 -- -- Maintainer: Henning Thielemann -- Stability : provisional -- -- PRIVATE MODULE. -- -- Here we have the various types used by the library, -- and how they are imported\/exported to C. -- -- NOTE: In the translations bellow we make the following assumptions -- about the sizes of C types. -- CChar = 8 bits -- CShort = 16 bit -- CInt = 32 bits -------------------------------------------------------------------------------- module Sound.ALSA.Sequencer.Marshal.QueueTimer where #include import Foreign.C.Types (CInt, ) data Type = Alsa | MidiClock | MidiTick deriving (Show, Eq, Ord, Enum) expType :: Type -> CInt expType t = case t of Alsa -> #{const SND_SEQ_TIMER_ALSA} MidiClock -> #{const SND_SEQ_TIMER_MIDI_CLOCK} MidiTick -> #{const SND_SEQ_TIMER_MIDI_TICK} impType :: CInt -> Type impType t = case t of #{const SND_SEQ_TIMER_ALSA} -> Alsa #{const SND_SEQ_TIMER_MIDI_CLOCK} -> MidiClock #{const SND_SEQ_TIMER_MIDI_TICK} -> MidiTick _ -> error ("QueueTimer.impType: unknown timer type (" ++ show t ++ ")")