-------------------------------------------------------------------------------- -- | -- Module : Sound.ALSA.Sequencer.Marshal -- 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.Port where #include import qualified Sound.ALSA.Sequencer.Utility as U import Foreign.C.Types (CInt, CUInt, ) import Foreign.Storable (Storable, ) import Data.Bits ((.|.), ) import Data.Word (Word8, ) -- The type of client ports. newtype T = Cons Word8 deriving (Eq, Ord, Storable) instance Show T where showsPrec prec (Cons x) = U.showsRecord prec "Port" [U.showsField x] exp :: T -> CInt exp (Cons p) = fromIntegral p imp :: CInt -> T imp p = Cons (fromIntegral p) -- | Port capabilities. newtype Cap = Cap { unCap :: CUInt } deriving (Eq,Ord) -- | Port types. newtype Type = Type { unType :: CUInt } deriving (Eq,Ord) #{enum T, Cons , systemTimer = SND_SEQ_PORT_SYSTEM_TIMER , systemAnnounce = SND_SEQ_PORT_SYSTEM_ANNOUNCE , unknown = SND_SEQ_ADDRESS_UNKNOWN } #{enum Cap, Cap , capRead = SND_SEQ_PORT_CAP_READ , capWrite = SND_SEQ_PORT_CAP_WRITE , capSyncRead = SND_SEQ_PORT_CAP_SYNC_READ , capSyncWrite = SND_SEQ_PORT_CAP_SYNC_WRITE , capDuplex = SND_SEQ_PORT_CAP_DUPLEX , capSubsRead = SND_SEQ_PORT_CAP_SUBS_READ , capSubsWrite = SND_SEQ_PORT_CAP_SUBS_WRITE , capNoExport = SND_SEQ_PORT_CAP_NO_EXPORT } caps :: [Cap] -> Cap caps cs = Cap (foldl (.|.) 0 (map unCap cs)) #{enum Type, Type , typeSpecific = SND_SEQ_PORT_TYPE_SPECIFIC , typeMidiGeneric = SND_SEQ_PORT_TYPE_MIDI_GENERIC , typeMidiGM = SND_SEQ_PORT_TYPE_MIDI_GM , typeMidiGS = SND_SEQ_PORT_TYPE_MIDI_GS , typeMidiXG = SND_SEQ_PORT_TYPE_MIDI_XG , typeMidiMT32 = SND_SEQ_PORT_TYPE_MIDI_MT32 , typeMidiGM2 = SND_SEQ_PORT_TYPE_MIDI_GM2 , typeSynth = SND_SEQ_PORT_TYPE_SYNTH , typeDirectSample = SND_SEQ_PORT_TYPE_DIRECT_SAMPLE , typeSample = SND_SEQ_PORT_TYPE_SAMPLE , typeHardware = SND_SEQ_PORT_TYPE_HARDWARE , typeSoftware = SND_SEQ_PORT_TYPE_SOFTWARE , typeSynthesizer = SND_SEQ_PORT_TYPE_SYNTHESIZER , typePort = SND_SEQ_PORT_TYPE_PORT , typeApplication = SND_SEQ_PORT_TYPE_APPLICATION } types :: [Type] -> Type types cs = Type (foldl (.|.) 0 (map unType cs))