Re: Superclass defaults

2011-08-30 Thread Victor Nazarov
I was thinking about the design of superclass default instances. I
think that we can get relatively far using the following extensions
together:

1) Multiple instance declarations

instance (Functor[a], Monad [a])
  where
fmap = map
(=) = flip concatMap
return = (:[])

-- Declaration above is syntactic sugar for 2 declarations:
-- instance Functor[a]
--  where
--fmap = map
-- instance Monad [a]
--  where
--(=) = flip concatMap
--return = (:[])

2) Context synonyms

-- (MonadAndFunctor a) is synonym for (Functor a, Monad a)
context (Functor a, Monad a) = MonadAndFunctor a

-- Using synonims with multiple class declarations we can define instances like
instance MonadAndFunctor [a]
  where
fmap = map
(=) = flip concatMap
return = (:[])

-- Declaration above is syntactic sugar for
-- instance (Functor[a], Monad [a])
--  where
--fmap = map
--(=) = flip concatMap
--return = (:[])

3) And finally Default superclass instances

Class contains default instances for superclasses:

class Functor m = Monad m
  where
(=) :: m a - (a - m b) - m b
return :: a - m a

-- default superclass instance:
instance Functor m
  where
fmap f m = m = (return . f)

Default superclass implementations are used only when multiple
instance declarations are used:

-- no default superclass instance is used. Error is emitted when there
is no Functor instance
instance Monad [a]
  where
 ...

-- default superclass instance is used:
instance Functor [a], Monad [a]
  where
(=) = ...
return = ...

-- functor instance is generated automatically
-- fmap = ...

Suppose that we make Functor to be Monad's superclass.
Combination of this three extensions allows us to define compatibility modules:

module Control.Monad.Compat (Monad) where

import qualified Control.Monad (Monad(..), Functor(..)) as CM

context CM.Functor m, CM.Monad m = Monad m

When we have compilation failure in client code after our Monad
definition change: No Functor instance found for Foo:

instance Monad Foo
  where ...

, we simply add following two lines to the module:

import Prelude hiding (Monad)
import Control.Monad.Compat (Monad)

and compilation succeeds.

Pros:
Client code can remain Haskell 98/2010 and doesn't require any extensions.
Three extensions seems simple when separate (I think there are many
corner cases)

Cons:
Intervention is required into client code (But I think it is required anyway).

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


How to synchronously shutdown the event manager loop

2011-08-30 Thread Bas van Dijk
Hello,

In my (still unreleased) usb-1.0 (https://github.com/basvandijk/usb)
library I use the GHC event manager for managing events from the
underlying `libusb` C library.

To work with the library a user has to initialize it using:

newCtx ∷ IO Ctx

The `Ctx` then allows the user to see the USB devices attached to the
system using:

getDevices ∷ Ctx → IO [Device]

From thereon a user can open devices using:

openDevice ∷ Device → IO DeviceHandle

and perform IO with them:

readBulk ∷ DeviceHandle → EndpointAddress → Size → Timeout → IO
(B.ByteString, Status)

Internally the synchronous `readBulk` is implemented using
asynchronous IO: first a request to read bytes from a USB device is
asynchronously submitted. Then it waits on a lock (`takeMVar lock`).
When the bytes are read an event is fired on a certain file
descriptor. The GHC event manager then wakes up and calls a callback
which will release the lock (`putMVar lock ()`).

I choose to have one event loop per session (`Ctx`) with the usb
library. This means that I make a new `EventManager` in `newCtx`:

evtMgr ← EventManager.new

register the `libusb` file descriptors with the event manager and fork
a thread which will `loop` the `EventManager`:

tid - forkIOWithUnmask $ \unmask → unmask $ EventManager.loop evtMgr

The underlying `libusb` C library needs to be deinitialized when
you're done with it. However for safety and ease of use a user of my
Haskell library doesn't need to explicitly deinitialize the library.
Instead this happens automatically when the garbage collector collects
an unreferenced `Ctx` by registering (using
`Foreign.Concurrent.newForeignPtr`) the following finalizer with the
`Ctx` foreign pointer:

-- Stop the event handling loop by killing its thread:
killThread tid
...
-- Finally deinitialize libusb:
c'libusb_exit ctxPtr

As you see I also kill the thread which is running the event manager
loop. However I think this is not the right way to do it because when
I use the library I see the following message being continually
printed after the `Ctx` is finalized:

ghc: ioManagerWakeup: write: Bad file descriptor

Note that when I remove the `killThread tid` the messages disappear.

It seems that killing the event manager loop is not allowed. Is there
another way of shutting down the event manager loop?

I know I can shut it down by using the `shutdown` function. However
this function is asynchronous. This won't work because I need to make
sure the event loop is shutdown before I exit the `libusb` library
(because that will close the file descriptors that the event loop is
working with).

I see the event manager provides the `finished` function which will
poll the manager to see if it stopped looping. This function is not
exported however. Is it possible to export this function?

It would be even nicer to have a synchronous shutdown function so that
I don't need to setup a loop that waits till the manager has been shut
down.

Regards,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to synchronously shutdown the event manager loop

2011-08-30 Thread Bryan O'Sullivan
On Tue, Aug 30, 2011 at 6:49 AM, Bas van Dijk v.dijk@gmail.com wrote:


 As you see I also kill the thread which is running the event manager
 loop. However I think this is not the right way to do it because when
 I use the library I see the following message being continually
 printed after the `Ctx` is finalized:

 ghc: ioManagerWakeup: write: Bad file descriptor


I'm afraid we don't provide a way to shut down an event manager
synchronously at the moment. You'll have to submit a patch if you want to
add that capability.  Perhaps you could add a way to specify an onShutdown
:: IO () hook that would be called by the event manager thread once it
shuts down.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc-pkg unregister disobedience

2011-08-30 Thread Albert Y. C. Lai

On 11-08-29 02:39 PM, Albert Y. C. Lai wrote:

ghc-pkg unregister --user P drops the global package if P is not in user.

[etc]

Now as ticket http://hackage.haskell.org/trac/ghc/ticket/5442

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ghc fails to build due to trust issues

2011-08-30 Thread Bas van Dijk
Hello,

I'm trying to build recent ghc-HEAD using ghc-7.2.1 but get the following error:

libraries/filepath/System/FilePath/Internal.hs:81:1:
base:Data.List can't be safely imported! The package (base) the
module resides in isn't trusted.

I guess a -trust base flag has to be passed to ghc somewhere.

Regards,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc fails to build due to trust issues

2011-08-30 Thread austin seipp
7.2.1 shipped without explicitly trusting the `base' package (an
accident, IIRC.) You can fix this and resume your build by saying:

$ ghc-pkg-7.2.1 trust base

and everything should be OK.

On Tue, Aug 30, 2011 at 4:54 PM, Bas van Dijk v.dijk@gmail.com wrote:
 Hello,

 I'm trying to build recent ghc-HEAD using ghc-7.2.1 but get the following 
 error:

 libraries/filepath/System/FilePath/Internal.hs:81:1:
    base:Data.List can't be safely imported! The package (base) the
 module resides in isn't trusted.

 I guess a -trust base flag has to be passed to ghc somewhere.

 Regards,

 Bas

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




-- 
Regards,
Austin

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc fails to build due to trust issues

2011-08-30 Thread Bas van Dijk
On 30 August 2011 23:57, austin seipp a...@hacks.yi.org wrote:
 7.2.1 shipped without explicitly trusting the `base' package (an
 accident, IIRC.) You can fix this and resume your build by saying:

 $ ghc-pkg-7.2.1 trust base

 and everything should be OK.

Thanks that works!

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to synchronously shutdown the event manager loop

2011-08-30 Thread Bas van Dijk
On 30 August 2011 17:39, Bryan O'Sullivan b...@serpentine.com wrote:
 On Tue, Aug 30, 2011 at 6:49 AM, Bas van Dijk v.dijk@gmail.com wrote:

 As you see I also kill the thread which is running the event manager
 loop. However I think this is not the right way to do it because when
 I use the library I see the following message being continually
 printed after the `Ctx` is finalized:

 ghc: ioManagerWakeup: write: Bad file descriptor

 I'm afraid we don't provide a way to shut down an event manager
 synchronously at the moment. You'll have to submit a patch if you want to
 add that capability.

I see what I can do. I'm first going to export the 'finished' function
from GHC.Event and use that to wait till the loop finishes and see if
that solves my problem.

BTW to reproduce the problem (if you're interested) you can use the
following program: (make sure to use the latest usb sources from git)

import System.USB (newCtx)
import Control.Concurrent (threadDelay)
import System.Mem (performGC)

main :: IO ()
main = do
  _ - newCtx
  threadDelay 200
  performGC
  threadDelay 200

running this yields:

example: ioManagerWakeup: write: Bad file descriptor
example: ioManagerDie: write: Bad file descriptor

 Perhaps you could add a way to specify an onShutdown
 :: IO () hook that would be called by the event manager thread once it
 shuts down.

That's a possibility.

BTW is there a reason 'shutdown' needs to be asynchronous or was it
just easier to implement it this way? Otherwise I think a synchronous
'shutdown' is easier to work with.

Regards,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to synchronously shutdown the event manager loop

2011-08-30 Thread Bas van Dijk
On 31 August 2011 00:15, Bas van Dijk v.dijk@gmail.com wrote:
 I see what I can do. I'm first going to export the 'finished' function
 from GHC.Event and use that to wait till the loop finishes and see if
 that solves my problem.

Waiting till the loop finishes doesn't solve the problem.

Here's an isolated program with the same problem that doesn't use the
usb library:

import Control.Concurrent
import GHC.Event

main = do
  em - new
  forkIO $ loop em
  threadDelay 200
  shutdown em
  threadDelay 200

When executed it prints:

example: ioManagerWakeup: write: Bad file descriptor
example: ioManagerDie: write: Bad file descriptor

So it seems like a bug in GHC. I will create a ticket in the morning.

Regards,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users