module Sound.ALSA.Sequencer.Marshal.Address where
import qualified Sound.ALSA.Sequencer.Marshal.Client as Client
import qualified Sound.ALSA.Sequencer.Marshal.Port as Port
import qualified Sound.ALSA.Sequencer.Utility as U
import qualified Foreign.C.Types as C
import Foreign.Storable
(Storable, sizeOf, alignment, peek, poke, pokeByteOff, peekByteOff, )
data T = Cons
{ client :: !Client.T
, port :: !Port.T
} deriving (Eq, Ord)
instance Show T where
showsPrec prec (Cons c p) =
U.showsRecord prec "Address" [U.showsField c, U.showsField p]
exp :: T -> (C.CInt,C.CInt)
exp a = (Client.exp (client a), Port.exp (port a))
instance Storable T where
sizeOf _ = (2)
alignment _ = (1)
peek p = do cl <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
po <- (\hsc_ptr -> peekByteOff hsc_ptr 1) p
return Cons { client = cl, port = po }
poke p v = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p (client v)
>> (\hsc_ptr -> pokeByteOff hsc_ptr 1) p (port v)
unknown :: T
unknown =
Cons {
client = Client.unknown,
port = Port.unknown
}
subscribers :: T
subscribers =
Cons {
client = Client.subscribers,
port = Port.unknown
}
broadcast :: T
broadcast =
Cons {
client = Client.broadcast,
port = Port.unknown
}
systemTimer :: T
systemTimer =
Cons {
client = Client.system,
port = Port.systemTimer
}
systemAnnounce :: T
systemAnnounce =
Cons {
client = Client.system,
port = Port.systemAnnounce
}