Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 20:27, Bas van Dijk  wrote:
> On 20 April 2011 18:34, Johan Tibell  wrote:
>> On Wed, Apr 20, 2011 at 6:11 PM, Bas van Dijk  wrote:
>>> I still need to add appropriate conditions for checking whether the
>>> program is using the threaded RTS. What is the recommended approach
>>> for this?
>>>
>>> I see GHC.Conc.IO uses a dynamic check:
>>>
>>> foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
>>>
>>> Is this also available to me as a library author?
>>
>> I think there's a ticket for adding something along the lines of
>>
>>    getSystemEventManager :: IO (Maybe EventManager)
>>
>> If that returns Just em, you're in the threaded RTS and have an EventManager.
>
> Whoever is proposing[1] that is a real genius! ;-)
>
> [1] 
> http://thread.gmane.org/gmane.comp.lang.haskell.libraries/15458/focus=15543
>
> Bas

I have now added the module System.USB.IO that automatically chooses
the asynchronous implementations when supported or the synchronous
otherwise:

https://github.com/basvandijk/usb/blob/async/System/USB/IO.hs

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 18:34, Johan Tibell  wrote:
> On Wed, Apr 20, 2011 at 6:11 PM, Bas van Dijk  wrote:
>> I still need to add appropriate conditions for checking whether the
>> program is using the threaded RTS. What is the recommended approach
>> for this?
>>
>> I see GHC.Conc.IO uses a dynamic check:
>>
>> foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
>>
>> Is this also available to me as a library author?
>
> I think there's a ticket for adding something along the lines of
>
>    getSystemEventManager :: IO (Maybe EventManager)
>
> If that returns Just em, you're in the threaded RTS and have an EventManager.

Whoever is proposing[1] that is a real genius! ;-)

[1] http://thread.gmane.org/gmane.comp.lang.haskell.libraries/15458/focus=15543

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Johan Tibell
On Wed, Apr 20, 2011 at 6:11 PM, Bas van Dijk  wrote:
> I still need to add appropriate conditions for checking whether the
> program is using the threaded RTS. What is the recommended approach
> for this?
>
> I see GHC.Conc.IO uses a dynamic check:
>
> foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
>
> Is this also available to me as a library author?

I think there's a ticket for adding something along the lines of

getSystemEventManager :: IO (Maybe EventManager)

If that returns Just em, you're in the threaded RTS and have an EventManager.

Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 17:55, Johan Tibell  wrote:
> On Wed, Apr 20, 2011 at 5:22 PM, Bas van Dijk  wrote:
>> On 20 April 2011 17:04, Johan Tibell  wrote:
>>> Not that evtRead and evtWrite maps to different things on different 
>>> platforms.
>>
>> Do you mean "Not" or "Note"?
>
> Yes, sorry.

Ok thanks.

I still need to add appropriate conditions for checking whether the
program is using the threaded RTS. What is the recommended approach
for this?

I see GHC.Conc.IO uses a dynamic check:

foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool

Is this also available to me as a library author?


BTW I have now a complete asynchronous implementation of the existing
synchronous API:
https://github.com/basvandijk/usb/blob/async/System/USB/IO/Asynchronous.hs

Be warned, it's still completely untested!


Next up are isochronous transfers. When that's done the usb library is
feature complete (i.e. it supports all the features of the underlying
libusb)!

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Johan Tibell
On Wed, Apr 20, 2011 at 5:22 PM, Bas van Dijk  wrote:
> On 20 April 2011 17:04, Johan Tibell  wrote:
>> Not that evtRead and evtWrite maps to different things on different 
>> platforms.
>
> Do you mean "Not" or "Note"?

Yes, sorry.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 17:04, Johan Tibell  wrote:
> On Tue, Apr 19, 2011 at 10:36 PM, Bas van Dijk  wrote:
>> On 19 April 2011 15:06, John Obbele  wrote:
>>        -- Step 3 is the most important step. Submitting the transfer:
>>        handleUSBException $ c'libusb_submit_transfer transPtr
>>
>>        -- TODO: Now we need to do the complicated stuff described in:
>>        -- http://libusb.sourceforge.net/api-1.0/group__poll.html
>>        --
>>        -- First we need the function:
>>        -- getPollFds ∷ Ctx → IO [C'libusb_pollfd]
>>        --
>>        -- A C'libusb_pollfd:
>>        -- http://libusb.sourceforge.net/api-1.0/structlibusb__pollfd.html
>>        -- is a structure containing a file descriptor which should be
>>        -- polled by the GHC event manager and an abstract integer
>>        -- describing the event flags to be polled.
>>        --
>>        -- The idea is to call getPollFds and register the returned
>>        -- file descriptors and associated events with the GHC event
>>        -- manager using registerFd:
>>        -- 
>> http://hackage.haskell.org/packages/archive/base/4.3.1.0/doc/html/System-Event.html#v:registerFd
>>        --
>>        -- As the callback we use libusb_handle_events_timeout.
>>        --
>>        -- But here we run into a problem: We need to turn our
>>        -- concrete event integer into a value of the _abstract_ type
>>        -- Event. But the only way to create Events is by evtRead or
>>        -- evtWrite!
>>        --
>>        -- I would really like a solution for this.
>>        -- Bryan, Johan any ideas?
>
> Could you do something like:
>
> toEvent :: Int -> Event
> toEvent flag
>    | flag `xor` (#const POLLIN) = evtRead
>
> etc?

Yes I think I can. I currently copied the code from GHC.Event.Poll:
https://github.com/basvandijk/usb/blob/async/Poll.hsc

> Not that evtRead and evtWrite maps to different things on different platforms.

Do you mean "Not" or "Note"?

Thanks,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Johan Tibell
On Tue, Apr 19, 2011 at 10:36 PM, Bas van Dijk  wrote:
> On 19 April 2011 15:06, John Obbele  wrote:
>        -- Step 3 is the most important step. Submitting the transfer:
>        handleUSBException $ c'libusb_submit_transfer transPtr
>
>        -- TODO: Now we need to do the complicated stuff described in:
>        -- http://libusb.sourceforge.net/api-1.0/group__poll.html
>        --
>        -- First we need the function:
>        -- getPollFds ∷ Ctx → IO [C'libusb_pollfd]
>        --
>        -- A C'libusb_pollfd:
>        -- http://libusb.sourceforge.net/api-1.0/structlibusb__pollfd.html
>        -- is a structure containing a file descriptor which should be
>        -- polled by the GHC event manager and an abstract integer
>        -- describing the event flags to be polled.
>        --
>        -- The idea is to call getPollFds and register the returned
>        -- file descriptors and associated events with the GHC event
>        -- manager using registerFd:
>        -- 
> http://hackage.haskell.org/packages/archive/base/4.3.1.0/doc/html/System-Event.html#v:registerFd
>        --
>        -- As the callback we use libusb_handle_events_timeout.
>        --
>        -- But here we run into a problem: We need to turn our
>        -- concrete event integer into a value of the _abstract_ type
>        -- Event. But the only way to create Events is by evtRead or
>        -- evtWrite!
>        --
>        -- I would really like a solution for this.
>        -- Bryan, Johan any ideas?

Could you do something like:

toEvent :: Int -> Event
toEvent flag
| flag `xor` (#const POLLIN) = evtRead

etc?

Not that evtRead and evtWrite maps to different things on different platforms.

Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 14:10, Bas van Dijk  wrote:
> I haven't implemented asynchronous transfers yet that actually
> transfer user data...

And now I have:

asynchronously implemented readControl and writeControl:
https://github.com/basvandijk/usb/blob/async/System/USB/Internal.hs#L1360

Next up are readBulk, writeBulk, readInterrupt and writeInterrupt.

When that's done I will begin with isochronous transfers.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread Bas van Dijk
On 20 April 2011 12:16, John Obbele  wrote:
> On Tue, Apr 19, 2011 at 10:36:50PM +0200, Bas van Dijk wrote:
>> Great! I have wished for an asynchronous implementation since version
>> 0.1 of usb but didn't really had a need for it nor the time to
>> implement it. However recently at work I have begun using my usb
>> library in an application which should run on a resource constraint
>> device. So any CPU cycles saved by using an asynchronous
>> implementation is a win. Since we both have a need for it maybe we can
>> work together?
>
> Yes. Your help is very welcomed and I was hoping to integrate the
> code with System.USB anyway.
>
> Tight resource constraint and performance are not really my
> priorities (I'm trying to get isopackets transfers), so my code
> is far from being optimal. But at least, I've got some dumb
> control read and write requests working, that can be a start ,)

Indeed, support for isochronous transfers is the only thing still
missing from the usb library. Having direct support for asynchronous
transfers allows to add it.

>> > The issues are:
>> >
>> > 1) I don't know how to expose the asynchronous API to Haskell. (How would
>> > you 'functionalize' it ?)
>>
>> I also started with trying to come up with an asynchronous _interface_
>> but realized that's probably not what users need. An asynchronous
>> interface is difficult to program against. However an asynchronous
>> _implementation_ is desirable over a synchronous one because of
>> efficiency.
>>
>> [... fast-forwarding ...]
>>
>> What we actually want is a synchronous interface with the same API as
>> we have now but with an implementation that uses the asynchronous
>> interface from libusb and integrate that with the new GHC event
>> manager.
>
> Yep ! The asynchronous stuff is a necessary burden, but on the
> implementation side only. Client in Haskell should not have to
> think to much about callbacks.
>
> I'm just discovering the GHC event manager. It looks fine and I
> will try to replace my Epoll bindings with it. If I can in the
> same time, I'll try to merge what I've done with the source code
> available on your github ... but no promise since I've mainly
> worked with low-level bit twiddlings.

I have a first implementation of an asynchronously implemented
'control' function ready in the 'async' branch:

https://github.com/basvandijk/usb/tree/async

It differs slightly from my previous sketch in that I setup the event
handling in the newCtx function.

> You schematic code for control packets is ok, but the hard part
> will probably be in managing concurrent requests (from multiple
> forkIO computations or from a background iso-packets
> communication) and then redispatching processed events from
> libusb back to Haskell.
> ... and this without forgetting something to cancel requested URB :(

I haven't implemented asynchronous transfers yet that actually
transfer user data let alone isochronous transfers. (These are next on
my list though). However I don't think concurrent requests are hard.
Each request has it's own transfer structure. When a transfer
completes the blocked thread that is executing the request gets woken
up and continues.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-20 Thread John Obbele
On Tue, Apr 19, 2011 at 10:36:50PM +0200, Bas van Dijk wrote:
> Great! I have wished for an asynchronous implementation since version
> 0.1 of usb but didn't really had a need for it nor the time to
> implement it. However recently at work I have begun using my usb
> library in an application which should run on a resource constraint
> device. So any CPU cycles saved by using an asynchronous
> implementation is a win. Since we both have a need for it maybe we can
> work together?

Yes. Your help is very welcomed and I was hoping to integrate the
code with System.USB anyway.

Tight resource constraint and performance are not really my
priorities (I'm trying to get isopackets transfers), so my code
is far from being optimal. But at least, I've got some dumb
control read and write requests working, that can be a start ,)

> > The issues are:
> >
> > 1) I don't know how to expose the asynchronous API to Haskell. (How would
> > you 'functionalize' it ?)
> 
> I also started with trying to come up with an asynchronous _interface_
> but realized that's probably not what users need. An asynchronous
> interface is difficult to program against. However an asynchronous
> _implementation_ is desirable over a synchronous one because of
> efficiency.
> 
> [... fast-forwarding ...]
> 
> What we actually want is a synchronous interface with the same API as
> we have now but with an implementation that uses the asynchronous
> interface from libusb and integrate that with the new GHC event
> manager.

Yep ! The asynchronous stuff is a necessary burden, but on the
implementation side only. Client in Haskell should not have to
think to much about callbacks.

I'm just discovering the GHC event manager. It looks fine and I
will try to replace my Epoll bindings with it. If I can in the
same time, I'll try to merge what I've done with the source code
available on your github ... but no promise since I've mainly
worked with low-level bit twiddlings.

You schematic code for control packets is ok, but the hard part
will probably be in managing concurrent requests (from multiple
forkIO computations or from a background iso-packets
communication) and then redispatching processed events from
libusb back to Haskell.
... and this without forgetting something to cancel requested URB :(


/john

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-19 Thread Bas van Dijk
On 19 April 2011 15:06, John Obbele  wrote:
> I'm trying to implement an asynchronous interface to libusb, re-using
> the raw bindings-usb (by Maurício C. Antunes) and partially copying what
> can be found in the (great but synchronous-only) usb package (from Bas
> van Dijk).

Great! I have wished for an asynchronous implementation since version
0.1 of usb but didn't really had a need for it nor the time to
implement it. However recently at work I have begun using my usb
library in an application which should run on a resource constraint
device. So any CPU cycles saved by using an asynchronous
implementation is a win. Since we both have a need for it maybe we can
work together?

> The issues are:
>
> 1) I don't know how to expose the asynchronous API to Haskell. (How would
> you 'functionalize' it ?)

I also started with trying to come up with an asynchronous _interface_
but realized that's probably not what users need. An asynchronous
interface is difficult to program against. However an asynchronous
_implementation_ is desirable over a synchronous one because of
efficiency.

Note that the synchronous interface of the underlying libusb C library
is also implemented using the lower level and much more complicated
asynchronous interface. See the libusb_control_transfer function for
example: http://bit.ly/fboG9C However as you would expect the
implementation uses a busy loop to check when the transfer completes.

What we actually want is a synchronous interface with the same API as
we have now but with an implementation that uses the asynchronous
interface from libusb and integrate that with the new GHC event
manager.

Let me give a sketch of how I think we should design an asynchronous
implementation. For simplicity lets take the usb control function:

http://hackage.haskell.org/packages/archive/usb/0.8/doc/html/System-USB-IO-Synchronous.html#v:control

and give that an asynchronous implementation. Note that this is still
a sketch some parts need to be filled in:

-- First of all, note that the synchronous API remains the same:
control ∷ DeviceHandle → ControlAction (Timeout → IO ())
control devHndl reqType reqRecipient request value index timeout =

  -- Asynchronous IO consists of 5 steps. See:
  -- http://libusb.sourceforge.net/api-1.0/group__asyncio.html#asynctrf
  -- The following takes care of the first and last step:
  -- allocating and deallocating the transfer structure:
  -- (See allocTransfer below)
  bracket allocTransfer c'libusb_free_transfer $ \transPtr →

-- Step 2 is filling the just allocated transfer structure with
-- the right information. The most important piece of information
-- is the buffer of data which you want to send to the device.
-- The following allocates this buffer and since we're doing a
-- control transfer we fill it with a control setup structure:
alloca $ \bufferPtr →
  poke bufferPtr $ C'libusb_control_setup
 (marshalRequestType reqType reqRecipient)
 request
 value
 index
 0

  -- The next piece of information in the transfer structure is
  -- the callback function. This function is called when the
  -- transfer terminates. This happens when either the transfer
  -- completes, timeouts, errors or when it is cancelled.
  --
  -- Because we want to provide a synchronous API the idea is to
  -- create a lock (a 'MVar ()'), submit the transfer, acquire the
  -- lock (which will block) and let the callback function release
  -- the lock (which causes the thread to continue when the
  -- transfer terminates). This way we don't need a busy loop and
  -- we save CPU cycles for other Haskell threads.

  lock ← newEmptyMVar
  let acquire lck = takeMVar lck
  release lck = putMVar lck ()

  let callback _ = release lock

  -- The 'callback' needs to be called from libusb so we have to
  -- turn it into a FunPtr: (See the FFI wrapper mkCallback below)
  bracket (mkCallback callback) freeHaskellFunPtr $ \cbPtr → do

-- Now it's time to actually fill the transfer structure with
-- the right information:
c'libusb_fill_control_transfer transPtr
   (getDevHndlPtr devHndl)
   bufferPtr
   cbPtr
   nullPtr -- unused user data
   (fromIntegral timeout)

-- Step 3 is the most important step. Submitting the transfer:
handleUSBException $ c'libusb_submit_transfer transPtr

-- TODO: Now we need to do the complicated stuff described in:
-- http://libusb.sourceforge.net/api-1.0/group__poll.html
--
-- First we need the function:
-- getPollFds ∷ Ctx → IO [C'libusb_pollfd]
--
-- A C'libusb_pollfd:

Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-19 Thread Antoine Latter
On Tue, Apr 19, 2011 at 9:35 AM, John Obbele  wrote:
> On Tue, Apr 19, 2011 at 08:52:44AM -0500, Antoine Latter wrote:
>> Maybe I'm misunderstanding something, but why why I want to use epoll
>> directly instead of just using forkIO plus threadWaitRead and
>> threadWaitWrite?
>>
>> http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Concurrent.html#v:threadWaitRead
>>
>> As a developer, the concurrency model offered by the
>> Control.Concurrency module has always been friendly to me.
>
> So instead of blindly following the C documentation on how to
> poll libusb, I should simply spawn a forkIO on each file
> descriptors and wait for the threadWait{Write,Read} to do their
> magic ?
>
> Something like:
>
> readAsyncIO = do $
>    zipfds <- getLibusbFileDescriptorsStruct
>    mapM_ (forkIO . monitor) zipfds
>
>  where monitor args@(readOrWrite, fd) = do
>        if isRead readOrWrite
>            then threadWaitRead fd
>            else threadWaitWrite fd
>        libusbHandleAllPendingsEvents
>        monitor args -- loop recursion
>
> Of course, I would have to use MVars or libusb lock API to verify
> that no two Haskell threads were trying to flush the events pool
> at the same time.
>

I'm not really familiar at all with libusb, and I'm not fmaliar with
the application code you're trying to write.

But as a Haskell application developer, the code I would want to write
to deal with USB devices in Haskell would be:

> handle <- aqcuireUsbDeve someParamsHere
> data <- getDataFromUsbDevice handle
>
> 
>
> putDataOnUsbDevice handle otherDataFromApp
>
> 
>
> moreData <- getDataFromUsbDevice handle
> ...

If I wanted to work with multiple devices simultaneously I would use
'forkIO' around different blocks of code, and then various concurrency
primitives to communicate between the different 'forkIO' threads
(IORefs, MVars, Chans and STM).

And I would expect everything to 'just work', because I would expect
'getDataFromUsbDevice' and 'putDataOnUsbDevice' to internally make
calls to 'threadWaitRead' and 'threadWaitWrite' which would place my
application-level code onto an epoll/kqueue/select struct for me, and
I can write my app-code in terms of idiomatic loops and recursion and
such.

And since in this example the USB operations are going through the
same global IO manager as everything else, if I'm working with both
USB devices and network devices, I will expect the GHC IO manager to
multiplex all of my 'forkIO' threads effectively, regardless of what
type of IO they are waiting on (or even if they're waiting on MVars or
STM or other Haskell things).

> hum ... wait, we don't use locks in Haskell, we use STM, don't we ?
>

MVars are great at locking things. Once I start needing multiple
permutations of multiple locks to handle what I want to do I start
looking at STM, as I'm much less likely to write buggy STM code than
buggy multiple-MVar code. That doesn't mean that STM doesn't have it's
own pitfalls.

>> Maybe there was something in the other thread I missed.

> I'm always lost in these long discussions about the overall
> merits of this one method or this another one.
>
> A (real) example helps me better to grasp the notions.
>

Hopefully what I wrote above helps! Again, I'm not sure wait type of
application you're trying to write - I don't have much background in
trying to make, for example, GUI software in Haskell.

> /john
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-19 Thread John Obbele
On Tue, Apr 19, 2011 at 08:52:44AM -0500, Antoine Latter wrote:
> Maybe I'm misunderstanding something, but why why I want to use epoll
> directly instead of just using forkIO plus threadWaitRead and
> threadWaitWrite?
> 
> http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Concurrent.html#v:threadWaitRead
> 
> As a developer, the concurrency model offered by the
> Control.Concurrency module has always been friendly to me.

So instead of blindly following the C documentation on how to
poll libusb, I should simply spawn a forkIO on each file
descriptors and wait for the threadWait{Write,Read} to do their
magic ?

Something like:

readAsyncIO = do $
zipfds <- getLibusbFileDescriptorsStruct
mapM_ (forkIO . monitor) zipfds

 where monitor args@(readOrWrite, fd) = do
if isRead readOrWrite
then threadWaitRead fd
else threadWaitWrite fd
libusbHandleAllPendingsEvents
monitor args -- loop recursion

Of course, I would have to use MVars or libusb lock API to verify
that no two Haskell threads were trying to flush the events pool
at the same time.

hum ... wait, we don't use locks in Haskell, we use STM, don't we ?

> Maybe there was something in the other thread I missed.
I'm always lost in these long discussions about the overall
merits of this one method or this another one.

A (real) example helps me better to grasp the notions.

/john

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-19 Thread Antoine Latter
On Tue, Apr 19, 2011 at 8:06 AM, John Obbele  wrote:
> I was reading the recent thread about select/poll, events
> handling and why forkIO is the only thing you should need (sorry
> if this is a horrible summary ;) and I'm realizing I could use
> some advice concerning my last project.
>
> I'm trying to implement an asynchronous interface to libusb, re-using
> the raw bindings-usb (by Maurício C. Antunes) and partially copying what
> can be found in the (great but synchronous-only) usb package (from Bas
> van Dijk).
>
> The issues are:
>
> 1) I don't know how to expose the asynchronous API to Haskell. (How would
> you 'functionalize' it ?)
>
> 2) I am messing with lots of FFI calls around epoll and libusb and would
> appreciate if someone could sanitize my approach.
>
> A pre-alpha-use-at-your-own-risk code preview is available there[1].
>
> [1]: https://patch-tag.com/r/obbele/usb-asynchronous/home
>
> So far, my answer to both issues was:
>
> Issue 1)
> Create an 'AsyncManager' data type to use in code like the following:
>
>>readAsyncIO = do $
>>       dev      <- getDeviceByVIDPID
>>       amanager <- newAsyncManager dev iface
>>       -- AsyncManager set a background thread to poll libusb for new events.
>>
>>       sendURB amanager dummyURB -- non-blocking call
>>       urb <- getURB amanager -- blocking
>>       putStr . pprintURB $ urb
>>
>>       closeAsyncManager amanager
>>
>>  where iface = 0
>>               dummyURB = newControlTransfer …
>
> Any opinions on this model ?
> (N.B.: to keep things simple, I do not yet plan to add a 'cancel'
> feature to this binding).
>
>
> Issue 2)
> What libusb asynchronous API requires is the following:
>
> 1. initialize resources, get device handles, etc.
>
> 2. get a set of file descriptors and select/poll them for read or write
>   access.
>
> 3. register USB transfers
>
> 4. when the transfers are completed, libusb will signal it on one of the
>   file descriptors. (but we don't know which one)
>
> 5. when your select/poll awakes from one event (it doesn't matter which
>   one), you call libusb_handle_events which will flush every pending
>   transfer by calling its associated callback function.
>
>   This results in the C runtime calling back an Haskell function (thus
>   the RTS will spawn an OS thread to handle it -- which doesn't bug
>   anymore since GHC 7.0.2.x :)
>
> 6. GOTO 3 or 4
>
> Complete libusb idiosyncrasies are explained in [2] and [3]:
> [2]: http://libusb.sourceforge.net/api-1.0/group__asyncio.html
> [3]: http://libusb.sourceforge.net/api-1.0/mtasync.html
>
> So far, I didn't find a 'blessed' FFI interface to select/poll the set
> of file descriptors and I'm currently using Toralf Wittner's Epoll
> package. (which is very fine albeit a linux-only hack).
>
> I am wondering if anyone know a magic wand (or abstraction model) to
> ease my headaches in Haskell.
>
> Something that could be more cross-platform ?
> Something that could be well-integrated with the (GHC) FFI ?
> Something that could be ... simple ?
>

Maybe I'm misunderstanding something, but why why I want to use epoll
directly instead of just using forkIO plus threadWaitRead and
threadWaitWrite?

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Concurrent.html#v:threadWaitRead

As a developer, the concurrency model offered by the
Control.Concurrency module has always been friendly to me.

Maybe there was something in the other thread I missed.

Antoine

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Need comments on a libusb asynchronous select/poll loop

2011-04-19 Thread John Obbele
I was reading the recent thread about select/poll, events
handling and why forkIO is the only thing you should need (sorry
if this is a horrible summary ;) and I'm realizing I could use
some advice concerning my last project.

I'm trying to implement an asynchronous interface to libusb, re-using
the raw bindings-usb (by Maurício C. Antunes) and partially copying what
can be found in the (great but synchronous-only) usb package (from Bas
van Dijk).

The issues are:

1) I don't know how to expose the asynchronous API to Haskell. (How would
you 'functionalize' it ?)

2) I am messing with lots of FFI calls around epoll and libusb and would
appreciate if someone could sanitize my approach.

A pre-alpha-use-at-your-own-risk code preview is available there[1].

[1]: https://patch-tag.com/r/obbele/usb-asynchronous/home

So far, my answer to both issues was:

Issue 1)
Create an 'AsyncManager' data type to use in code like the following:

>readAsyncIO = do $
>   dev  <- getDeviceByVIDPID
>   amanager <- newAsyncManager dev iface
>   -- AsyncManager set a background thread to poll libusb for new events.
>
>   sendURB amanager dummyURB -- non-blocking call
>   urb <- getURB amanager -- blocking
>   putStr . pprintURB $ urb
>
>   closeAsyncManager amanager
>
>  where iface = 0
>   dummyURB = newControlTransfer … 

Any opinions on this model ?
(N.B.: to keep things simple, I do not yet plan to add a 'cancel'
feature to this binding).


Issue 2)
What libusb asynchronous API requires is the following:

1. initialize resources, get device handles, etc.

2. get a set of file descriptors and select/poll them for read or write
   access.

3. register USB transfers

4. when the transfers are completed, libusb will signal it on one of the
   file descriptors. (but we don't know which one)

5. when your select/poll awakes from one event (it doesn't matter which
   one), you call libusb_handle_events which will flush every pending
   transfer by calling its associated callback function.

   This results in the C runtime calling back an Haskell function (thus
   the RTS will spawn an OS thread to handle it -- which doesn't bug
   anymore since GHC 7.0.2.x :)

6. GOTO 3 or 4

Complete libusb idiosyncrasies are explained in [2] and [3]:
[2]: http://libusb.sourceforge.net/api-1.0/group__asyncio.html
[3]: http://libusb.sourceforge.net/api-1.0/mtasync.html

So far, I didn't find a 'blessed' FFI interface to select/poll the set
of file descriptors and I'm currently using Toralf Wittner's Epoll
package. (which is very fine albeit a linux-only hack).

I am wondering if anyone know a magic wand (or abstraction model) to
ease my headaches in Haskell.

Something that could be more cross-platform ?
Something that could be well-integrated with the (GHC) FFI ?
Something that could be ... simple ?


any help appreciated ,)
/John


P.S.: and third question : how the heck am I supposed to debug threaded
FFI code in Haskell ? With GDB ?

Yes I'm particularly upset about background Haskell threads which die
silently (e.g. when encountering a segfault) and dead-lock the whole
RTS.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe