Re: Safe Haskell trust

2014-03-17 Thread Daniel Gorín
Hi Fabian,

In general, the behavior you get from hint should be more or less the same one 
you would observe in ghci, the mapping being roughly:

loadModules ~~~ :load
setImports  :module

In ghci, if you have a package installed (and is not hidden in your session), 
then I believe you can use :module to put any of its public modules in scope 
with (Safe or otherwise), am I right? If so, that should explain what you are 
observing…

Daniel

On 17 Mar 2014, at 14:10, Fabian Bergmark fabian.bergm...@gmail.com wrote:

 I downloaded aeson and modified Data.Aeson to be trustworthy and I can
 now use it with Hint and XSafe. I however stumbled upon some strange
 behavior. I use loadModules to import some modules from the same
 package, and then use setImports with a list of user provided modules.
 Some explanation about their difference would be appreciated, as the
 documentation is rather short. The modules loaded with loadModules
 seems to be checked, ie. can't import unsafe modules, but those
 imported with setImports are not, ie. the user can import unsafe
 modules.
 
 Have I misunderstood the documentation or is this a flaw in Hint?
 
 2014-03-16 18:34 GMT+01:00 Edward Kmett ekm...@gmail.com:
 Not directly. You can, however, make a Trustworthy module that re-exports
 the (parts of) the Unsafe ones you want to allow yourself to use.
 
 -Edward
 
 
 On Sun, Mar 16, 2014 at 12:57 PM, Fabian Bergmark
 fabian.bergm...@gmail.com wrote:
 
 Im using the Hint library in a project where users are able to upload
 and run code. As I don't want them to do any IO, I run the interpreter
 with -XSafe. However, some packages (in my case aeson) are needed and
 I therefore tried marking them as trusted with ghc-pkg trust aeson.
 This seems to have no effect however and the interpreter fails with:
 
 Data.Aeson: Can't be safely imported! The module itself isn't safe
 
 Is there any way to get XSafe-like guarantees with the ability of
 allowing certain packages?
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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


Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Daniel Gorín
Hi Iavor,

On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:

 Hello,
 
 
 On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín dgo...@dc.uba.ar wrote:
 On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
 
  How about (in Haskell98)
 
module Data.List ( foldr, ...)
import qualified Data.Foldable
foldr :: (a - b - b) - b - [a] - b
foldr = Data.Foldable.foldr
 
 It would not be the same! Using your example one will get that the following 
 fails to compile:
 
  import Data.List
  import Data.Foldable
  f = foldr
 
 The problem is that Data.List.foldr and Data.Foldable.foldr are here 
 different symbols with the same name.
 This is precisely why Foldable, Traversable, Category, etc are awkward to 
 use. The proposal is to make Data.List reexport Data.Foldable.foldr (with a 
 more specialized type) so that the module above can be accepted.
 
 
 I think that it is perfectly reasonable for this to fail to compile---to me, 
 this sort of implicit shadowing based on what extensions are turned on would 
 be very confusing.  It may seem obvious with a well-known example, such as 
 `foldr`, but I can easily imagine getting a headache trying to figure out a 
 new library that makes uses the proposed feature in anger :)

I understand your concern, but I don't quite see how a library could abuse this 
feature. I mean, a library could export the same symbol with different 
specialized types in various modules, but you, the user of the library, will 
see them as different symbols with conflicting name, just like now you see 
symbols Prelude.foldr and Data.Foldable.foldr exported by base... unless, of 
course, you specifically activate the extension (the one called 
MoreSpecificImports in my first mail). That is, it would be an opt-in feature.

 Also, using module-level language extensions does not seem like the right 
 tool for this task: what if I wanted to use the most general version of one 
 symbol, but the most specific version of another?

Do you have a particular example in mind? The more general version of every 
symbol can be used wherever the more specialized one fits, and in the 
(seemingly rare?) case where the extra polymorphism may harm you and that 
adding a type annotation is not convenient enough, you could just hide the 
import of more the general  version. Do you anticipate this to be a common 
scenario?

  One needs a more fine grained tool, and I think that current module system 
 already provides enough features to do so (e.g., explicit export lists, 
 `hiding` clauses`, and qualified imports).  For example, it really does not 
 seem that inconvenient (and, in fact, I find it helpful!) to write the 
 following:
 
 import Data.List hiding (foldr)
 import Data.Foldable

But this doesn't scale that well, IMO. In real code even restricted to the the 
base package the hiding clauses can get quite long and qualifying basic 
polymorphic functions starts to feel like polymorphism done wrong.

This can very well be just a matter of taste, but apparently so many people 
have strong feelings about this issue that it is seriously being proposed to 
move Foldable and Traversable to the Prelude, removing all the monomorphic 
counterparts (that is, make Prelude export the unspecialized versions). While 
this would be certainly convenient for me, I think it would be an unfortunate 
move: removing concrete (monomorphic) functions in favor of abstract versions 
will make a language that is already hard to learn, even harder (but there was 
a long enough thread in the libraries mailing list about this already!). In any 
case this proposal is an attempt to resolve this tension without penalizing 
any of the sides. 

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


Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-25 Thread Daniel Gorín
 Oh my!  Now it's getting complicated.  

Hopefully not so!

 * I suppose that if Data.List re-exports foldr, it would go with the more 
 specific type.  

Yes.

 * In your example, can I also use the more-polymorphic foldr, perhaps by 
 saying Data.Foldable.foldr?

Yes. More precisely, if you import both Data.List and Data.Foldable and try to 
use foldr, it will have the more general type that comes from Data.Foldable.

 * I wonder what would happen if Data.Foo specialised foldr in a different 
 way, and some module imported both Data.List and Data.Foo.  Maybe it would be 
 ok if one of the two specialised types was more specific than the other but 
 not if they were comparable?

Right, that is what I was proposing. If the specialization of foldr in 
Data.List is more general than the one in Data.Foo, the former is used. If the 
converse is the case, the latter is used. If none is more general, the module 
cannot be compiled. The solution in this case is to import also Data.Foldable, 
which provides a version of foldr that is more general than the ones in 
Data.List and Data.Foo.

 * What happens for classes?  Can you specialise the signatures there?  And 
 make instances of that specialised class?

No; I don't think that would be sound. The proposal was to extend the grammar 
for export lists allowing type signatures for qvars only.

 * Ditto data types

Datatypes are not covered by the proposal either.

 It feel a bit like a black hole to me.

As it is, the proposal should affect only the module system, where it is 
determined what the type of an imported symbol is. In particular, the 
typechecker would go unaware of it. In that sense, I see the proposal as a very 
mild extension.

Thanks,
Daniel.



 Simon
 | -Original Message-
 | From: Daniel Gorín [mailto:dgo...@dc.uba.ar]
 | Sent: 24 May 2013 08:42
 | To: Simon Peyton-Jones
 | Cc: glasgow-haskell-users@haskell.org
 | Subject: Re: A language extension for dealing with Prelude.foldr vs
 | Foldable.foldr and similar dilemmas
 | 
 | On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
 | 
 |  How about (in Haskell98)
 | 
 |module Data.List ( foldr, ...)
 |import qualified Data.Foldable
 |foldr :: (a - b - b) - b - [a] - b
 |foldr = Data.Foldable.foldr
 | 
 | It would not be the same! Using your example one will get that the following
 | fails to compile:
 | 
 |  import Data.List
 |  import Data.Foldable
 |  f = foldr
 | 
 | The problem is that Data.List.foldr and Data.Foldable.foldr are here 
 different
 | symbols with the same name.
 | This is precisely why Foldable, Traversable, Category, etc are awkward to 
 use.
 | The proposal is to make Data.List reexport Data.Foldable.foldr (with a more
 | specialized type) so that the module above can be accepted.
 | 
 | Thanks,
 | Daniel
 | 
 |  Simon
 | 
 |  | -Original Message-
 |  | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
 |  | users-boun...@haskell.org] On Behalf Of Daniel Gorín
 |  | Sent: 24 May 2013 01:27
 |  | To: glasgow-haskell-users@haskell.org
 |  | Subject: A language extension for dealing with Prelude.foldr vs
 | Foldable.foldr
 |  | and similar dilemmas
 |  |
 |  | Hi all,
 |  |
 |  | Given the ongoing discussion in the libraries mailing list on replacing 
 (or
 |  | removing) list functions in the Prelude in favor of the Foldable / 
 Traversable
 |  | generalizations, I was wondering if this wouldn't be better handled by a
 | mild
 |  | (IMO) extension to the module system.
 |  |
 |  | In a nutshell, the idea would be 1) to allow a module to export a 
 specialized
 |  | version of a symbol (e.g., Prelude could export Foldable.foldr but with 
 the
 |  | specialized type (a - b - b) - b - [a] - b) and 2) provide a
 | disambiguation
 |  | mechanism by which when a module imports several versions of the same
 |  | symbol (each, perhaps, specialized), a sufficiently general type is 
 assigned
 | to it.
 |  |
 |  | The attractive I see in this approach is that (enabling an extension) 
 one
 | could
 |  | just import and use Foldable and Traversable (and even Category!) 
 without
 |  | qualifying nor hiding anything; plus no existing code would break and
 | beginners
 |  | would still get  the friendlier error of the monomorphic functions. I 
 also
 | expect
 |  | it to be relatively easy to implement.
 |  |
 |  | In more detail, the proposal is to add two related language extensions,
 | which,
 |  | for the sake of having a name, I refer to here as MoreSpecificExports 
 and
 |  | MoreGeneralImports.
 |  |
 |  | 1) With MoreSpecificExports the grammar is extended to allow type
 |  | annotations on symbols in the export list of a module. One could then 
 have,
 |  | e.g., something like:
 |  |
 |  | {-# LANGUAGE MoreSpecificExports #-}
 |  | module Data.List (
 |  |  ...
 |  |  Data.Foldable.foldr :: (a - b - b) - b - [a] - b
 |  |, Data.Foldable.foldl :: (b - a - b) - b - [a] - b
 |  | ...
 |  | )
 |  |
 |  | where

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-24 Thread Daniel Gorín
On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:

 How about (in Haskell98)
 
   module Data.List ( foldr, ...)
   import qualified Data.Foldable
   foldr :: (a - b - b) - b - [a] - b
   foldr = Data.Foldable.foldr

It would not be the same! Using your example one will get that the following 
fails to compile:

 import Data.List
 import Data.Foldable
 f = foldr

The problem is that Data.List.foldr and Data.Foldable.foldr are here different 
symbols with the same name. 
This is precisely why Foldable, Traversable, Category, etc are awkward to use. 
The proposal is to make Data.List reexport Data.Foldable.foldr (with a more 
specialized type) so that the module above can be accepted.

Thanks,
Daniel 

 Simon
 
 | -Original Message-
 | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
 | users-boun...@haskell.org] On Behalf Of Daniel Gorín
 | Sent: 24 May 2013 01:27
 | To: glasgow-haskell-users@haskell.org
 | Subject: A language extension for dealing with Prelude.foldr vs 
 Foldable.foldr
 | and similar dilemmas
 | 
 | Hi all,
 | 
 | Given the ongoing discussion in the libraries mailing list on replacing (or
 | removing) list functions in the Prelude in favor of the Foldable / 
 Traversable
 | generalizations, I was wondering if this wouldn't be better handled by a 
 mild
 | (IMO) extension to the module system.
 | 
 | In a nutshell, the idea would be 1) to allow a module to export a 
 specialized
 | version of a symbol (e.g., Prelude could export Foldable.foldr but with the
 | specialized type (a - b - b) - b - [a] - b) and 2) provide a 
 disambiguation
 | mechanism by which when a module imports several versions of the same
 | symbol (each, perhaps, specialized), a sufficiently general type is 
 assigned to it.
 | 
 | The attractive I see in this approach is that (enabling an extension) one 
 could
 | just import and use Foldable and Traversable (and even Category!) without
 | qualifying nor hiding anything; plus no existing code would break and 
 beginners
 | would still get  the friendlier error of the monomorphic functions. I also 
 expect
 | it to be relatively easy to implement.
 | 
 | In more detail, the proposal is to add two related language extensions, 
 which,
 | for the sake of having a name, I refer to here as MoreSpecificExports and
 | MoreGeneralImports.
 | 
 | 1) With MoreSpecificExports the grammar is extended to allow type
 | annotations on symbols in the export list of a module. One could then have,
 | e.g., something like:
 | 
 | {-# LANGUAGE MoreSpecificExports #-}
 | module Data.List (
 |  ...
 |  Data.Foldable.foldr :: (a - b - b) - b - [a] - b
 |, Data.Foldable.foldl :: (b - a - b) - b - [a] - b
 | ...
 | )
 | 
 | where
 | 
 | import Data.Foldable
 | ...
 | 
 | instance Foldable [] where ...
 | 
 | 
 | For consistency, symbols defined in the module could also be exported
 | specialized. The type-checker needs to check that the type annotation is in 
 fact
 | a valid specialization of the original type, but this is, I think, 
 straightforward.
 | 
 | 
 | 2) If a module imports Data.List and Data.Foldable as defined above 
 *without*
 | the counterpart MoreGeneralImports extension, then Data.List.foldr and
 | Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would 
 be
 | an ambiguous symbol, just like it is now.
 | 
 | If on the other hand a module enables MoreGeneralImports and a symbol f is
 | imported n times with types T1, T2, ... Tn,  the proposal is to assign to f 
 the
 | most general type among T1... Tn, if such type exists (or fail otherwise). 
 So if in
 | the example above we enable MoreGeneralImports, foldr will have type
 | Foldable t = (a - b - b) - b - t a - b, as desired.
 | 
 | (It could be much more interesting to assign to f the least general
 | generalization of T1...Tn, but this seems to require much more work (unless
 | GHC already implements some anti-unification algorithm); also I'm not sure
 | whether this would interact well with GADTs or similar features and in any 
 case
 | this could be added at a later stage without breaking existing programs).
 | 
 | 
 | Would something like this address the problem? Are there any interactions 
 that
 | make this approach unsound? Any obvious cons I'm not seeing? Feedback is
 | most welcome!
 | 
 | Thanks,
 | Daniel
 | ___
 | Glasgow-haskell-users mailing list
 | Glasgow-haskell-users@haskell.org
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-23 Thread Daniel Gorín
Hi all,

Given the ongoing discussion in the libraries mailing list on replacing (or 
removing) list functions in the Prelude in favor of the Foldable / Traversable 
generalizations, I was wondering if this wouldn't be better handled by a mild 
(IMO) extension to the module system. 

In a nutshell, the idea would be 1) to allow a module to export a specialized 
version of a symbol (e.g., Prelude could export Foldable.foldr but with the 
specialized type (a - b - b) - b - [a] - b) and 2) provide a 
disambiguation mechanism by which when a module imports several versions of the 
same symbol (each, perhaps, specialized), a sufficiently general type is 
assigned to it.

The attractive I see in this approach is that (enabling an extension) one could 
just import and use Foldable and Traversable (and even Category!) without 
qualifying nor hiding anything; plus no existing code would break and beginners 
would still get  the friendlier error of the monomorphic functions. I also 
expect it to be relatively easy to implement.

In more detail, the proposal is to add two related language extensions, which, 
for the sake of having a name, I refer to here as MoreSpecificExports and 
MoreGeneralImports.

1) With MoreSpecificExports the grammar is extended to allow type annotations 
on symbols in the export list of a module. One could then have, e.g., something 
like:

{-# LANGUAGE MoreSpecificExports #-}
module Data.List (
 ...
 Data.Foldable.foldr :: (a - b - b) - b - [a] - b
   , Data.Foldable.foldl :: (b - a - b) - b - [a] - b
...
)

where

import Data.Foldable
...

instance Foldable [] where ...


For consistency, symbols defined in the module could also be exported 
specialized. The type-checker needs to check that the type annotation is in 
fact a valid specialization of the original type, but this is, I think, 
straightforward.


2) If a module imports Data.List and Data.Foldable as defined above *without* 
the counterpart MoreGeneralImports extension, then Data.List.foldr and 
Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would be 
an ambiguous symbol, just like it is now.

If on the other hand a module enables MoreGeneralImports and a symbol f is 
imported n times with types T1, T2, ... Tn,  the proposal is to assign to f the 
most general type among T1... Tn, if such type exists (or fail otherwise). So 
if in the example above we enable MoreGeneralImports, foldr will have type 
Foldable t = (a - b - b) - b - t a - b, as desired.

(It could be much more interesting to assign to f the least general 
generalization of T1...Tn, but this seems to require much more work (unless GHC 
already implements some anti-unification algorithm); also I'm not sure whether 
this would interact well with GADTs or similar features and in any case this 
could be added at a later stage without breaking existing programs).


Would something like this address the problem? Are there any interactions that 
make this approach unsound? Any obvious cons I'm not seeing? Feedback is most 
welcome!

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


Re: [Haskell-cafe] ghc-mtl, hint, mueval for ghc-7.6 ?

2012-10-08 Thread Daniel Gorín
Hi Johannes,

The repository version of ghc-mtl already compiles with ghc 7.6.1. I'm working 
at the moment on making hint compile again as well (am I the only one on this 
list that doesn't get excited with every new release of ghc? :)), then I'll 
upload both to hackage.

Thanks,
Daniel

On Oct 8, 2012, at 2:21 PM, Johannes Waldmann wrote:

 While porting some code to 7.6, I'm stuck here:
 
 Preprocessing library ghc-mtl-1.0.1.1...
 [1 of 1] Compiling Control.Monad.Ghc ( Control/Monad/Ghc.hs,
 dist/build/Control/Monad/Ghc.o )
 
 Control/Monad/Ghc.hs:29:48:
No instance for (DynFlags.HasDynFlags Ghc)
 
 this seems to block hint and mueval.
 Is there a known workaround for this problem,
 or a sugggested replacement package?
 
 Thanks - J.W.
 
 
 
 
 ___
 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] hint and type synonyms

2012-04-01 Thread Daniel Gorín
Hi

I think I see now what the problem you observe is. It is not related with type 
synonyms but with module scoping. Let me briefly discuss what hint is doing 
behind the scenes and why, this may give a better understanding of what kind of 
things will and will not work.

While hint is directly tied to ghc, it should be possible to implement 
something similar for any self-hosting Haskell compiler. Essentially, you need 
the compiler to provide a function compileExpr that given a string with a 
Haskell expression, returns a value of some type, say CompiledExpr (or an error 
if the string is not a valid expression, etc). So, for instance, 'compileExpr 
not True' will produce something of type CompiledExpr, but we know that it is 
safe to unsafeCoerce this value into one of type Bool.

Now, what happens if one unsafeCoerces to a Bool the result of running 
compileExpr on [True]? This is, of course, equivalent to running 
'(unsafeCoerce [True]) :: Bool' and sounds dangerous. Indeed, if your compiler 
were to keep type information in its CompiledExprs and check for type 
correctness on each operation (akin to what the interpreters for dynamic 
languages (like Perl, Ruby, etc.) do) then you may get a gracious runtime 
error; but most (if not all) of Haskell compilers eliminate all type 
information from the compiled representation (which is a good thing for 
performance), so the result of a bad cast like the one above will surely result 
in an ugly (uninformative) crash.

So how does we deal with this in hint? When you write 'interpret not True (as 
:: Bool)' we want a runtime guarantee that not True is in fact a value of 
type Bool. We do this by calling compileExpr with (not True) :: Bool instead 
of just with not True. This way, an incorrect cast is caught at runtime by 
compileExpr (e.g. ([True]) :: Bool will fail to compile). In order to do 
this, the type parameter must be an instance of Data.Typeable and we use the 
typeOf function to obtain the type (e.g. show $ Data.Typeable.typeOf True == 
Bool)

This is, as you've noticed, a little fragile. For this to work, the type 
expression returned by Data.Typeable.typeOf must correspond to something that 
is visible to the complieExpr function. You do this in hint adding the relevant 
modules with the setImports function. It may be a little inconvenient, but I 
think it is unavoidable.

I wouldn't ever recommend writing bogus instances of Typeable as in your 
original example. If you find a situation where this looks as the more sensible 
thing to do I'd like to know! Also, in the example from Rc43 you cite below, 
instead of running setImport on HReal.Core.Prelude you need to run setImport on 
all the modules that are exported by HReal.Core.Prelude (this can be abstracted 
in a function, I guess).

Since I am on this, I'd like to point out that this solution is, sadly, not 
100% safe. There is still one way in which things can go wrong and people often 
trip over this. The problem roughly comes when your program defines a type T on 
module M and ends up running compileExpr on an expression of type M.T but in a 
way such that module M gets to be compiled from scratch. When this happens, the 
type M.T on your program and the type M.T used in compileExpr may end up having 
two incompatible representations and the unsafeCoerce will lead to a crash. 
This typically happens when using hint to implement some form of plugin system. 
Imagine you have a project organized as follows:

project/
project/src/M.hs
project/src/main.hs
project/plugins/P.hs
dist/build/M.o
dist/build/main.o
dist/build/main

where M.hs defines T;  P.hs imports M and exports a function f :: T; and 
main.hs imports M and runs an interpreter that sets src as the searchPat, 
loads plugins/P.hs, interprets f as a T and does something with it. Assume 
dist/build/main is run from the project dir. When hint tries to load 
plugins/P.hs the import M will force the compiler to search for module M.hs 
in project/src and compile it again (just like ghci would do). This can be bad! 
The robust solution in this case is to put all the definitions that you want to 
be shared by your program and your dynamically loaded code in a library (and 
make sure that it is installed before running the program).

Hope this helps...

Daniel




On Mar 31, 2012, at 8:06 PM, Claude Heiland-Allen wrote:

 Hi Daniel, cafe,
 
 On 31/03/12 17:47, Daniel Gorín wrote:
 Could you provide a short example of the code you'd like to write but gives 
 you problems? I'm not able to infer it from your workaround alone...
 
 This problem originally came up on #haskell, where Rc43 had a problem making 
 a library with a common module that re-exports several other modules:
 
 http://hpaste.org/66281
 
 My personal interest is somewhat secondary, having not yet used hint in a 
 real project, but code I would like to write at some point in the future is 
 much like the 'failure' below, unrolled it looks like:
 
 main = (print

Re: [Haskell-cafe] efficient chop

2011-09-14 Thread Daniel Gorín
On Sep 14, 2011, at 5:29 AM, Kazu Yamamoto (山本和彦) wrote:

 Hello,
 
 Of course, I use ByteString or Text for real programming. But I would
 like to know whether or not there are any efficient methods to remove
 a tail part of a list.
 
 --Kazu

In that case, I would prefer this version, since it is lazier:

lazyChop :: String - String
lazyChop s = pref ++ if null s' then [] else (mid_sp ++ lazyChop s')
  where
(pref,sp_suf) = break isSpace s
(mid_sp,s')   = span isSpace sp_suf

By lazier I mean:

*Main chopReverse $ hello world  ++ undefined
*** Exception: Prelude.undefined
*Main chopFoldr $ hello world  ++ undefined
*** Exception: Prelude.undefined
*Main lazyChop $ hello world  ++ undefined
hello world*** Exception: Prelude.undefined

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


Re: [Haskell-cafe] ghc-mtl and ghc-7.2.1

2011-09-07 Thread Daniel Gorín
Hi Romildo, you can try the darcs version of ghc-mtl [1], I don't know if that 
will be enough to build lambdabot, though

Best,
Daniel

[1] http://darcsden.com/jcpetruzza/ghc-mtl

On Sep 7, 2011, at 1:34 PM, José Romildo Malaquias wrote:

 Hello.
 
 In order to compile ghc-mtl-1.0.1.0 (the latest released version) with
 ghc-7.2.1, I would apply the attached patch, which removes any
 references to WarnLogMonad.
 
 ghc-7.2.1 does not have the monad WarnLogMonad anymore.
 
 As I do not know the details of the GHC api, I am not sure if this is
 enough to use ghc-mtl with ghc-7.2.1.
 
 I want ghc-mtl in order do build lambdabot.
 
 Any thoughts?
 
 Romildo
 ghc-mtl-1.0.1.0-gcc721.patch___
 Haskell-Cafe mailing list
 haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] ghc-mtl and ghc-7.2.1

2011-09-07 Thread Daniel Gorín
Hi Romildo, you can try the darcs version of ghc-mtl [1], I don't know if that 
will be enough to build lambdabot, though

Best,
Daniel

[1] http://darcsden.com/jcpetruzza/ghc-mtl

On Sep 7, 2011, at 1:34 PM, José Romildo Malaquias wrote:

 Hello.
 
 In order to compile ghc-mtl-1.0.1.0 (the latest released version) with
 ghc-7.2.1, I would apply the attached patch, which removes any
 references to WarnLogMonad.
 
 ghc-7.2.1 does not have the monad WarnLogMonad anymore.
 
 As I do not know the details of the GHC api, I am not sure if this is
 enough to use ghc-mtl with ghc-7.2.1.
 
 I want ghc-mtl in order do build lambdabot.
 
 Any thoughts?
 
 Romildo
 ghc-mtl-1.0.1.0-gcc721.patch___
 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] External system connections

2011-07-11 Thread Daniel Gorín

On Jul 11, 2011, at 10:48 PM, Alistair Bayley wrote:

 12 July 2011 05:49, Michael Snoyman mich...@snoyman.com wrote:
 
 As for Bryan's resource-pool: currently I would strongly recommend
 *against* using it for any purpose. It is based on
 MonadCatchIO-transformers[2], which is a subtly broken package. In
 particular, when I tried using it for pool/persistent in the first
 place, I ended up with double-free bugs from SQLite.
 
 Do you have a reference explaining this brokenness? e.g. a mailing
 list message? I wasn't aware of this. Are the other MonadCatchIO-*
 packages also broken?
 

http://www.haskell.org/pipermail/haskell-cafe/2010-October/084890.html


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


Re: [Haskell-cafe] generic putback

2011-05-15 Thread Daniel Gorín
I think you need to change the type of putback slightly:

import Data.IORef

putback :: a - IO a - IO (IO a)
putback a action =
   do next - newIORef a
  return (do r - readIORef next; writeIORef next = action; return r)

main =
   do getChar' - putback 'a' getChar
  str - sequence $ take 10 $ repeat getChar'
  putStrLn str

Thanks,
Daniel

On May 15, 2011, at 4:33 PM, Sergey Mironov wrote:

 Hi Cafe. I wonder if it is possible to write a IO putback function
 with following interface
 
 putback :: a - IO a - IO a
 putback x io = ???
 
 
 where io is some action like reading from file or socket.
 I want putback to build new action which will return x on first call,
 and continue executing io after that.
 
 Thanks in advance!
 Sergey.
 
 ___
 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


problem running ghc-api code in ghci 7.0.x

2011-03-02 Thread Daniel Gorín
Hi

I have code using the ghc-api that could be run in interactive mode prior to 
version 7 but now makes ghci crash with a linker error. Everything works fine 
if compiled before running. I don't know if this is a known issue or if I'm 
just using the api in the wrong way, but I thought that I might ask.

To illustrate the problem, consider this simple example:

t.hs:
 import qualified GHC
 import qualified GHC.Paths
 
 main = GHC.runGhcT (Just GHC.Paths.libdir) $ do
-- begin initialize
df0 - GHC.getSessionDynFlags
let df1 = df0{GHC.ghcMode= GHC.CompManager,
  GHC.hscTarget  = GHC.HscInterpreted,
  GHC.ghcLink= GHC.LinkInMemory,
  GHC.verbosity  = 0}
_ - GHC.setSessionDynFlags df1 
-- begin reset
GHC.setContext [] []
GHC.setTargets []
_ - GHC.load GHC.LoadAllTargets
return ()

I then see:

# ghci-6.12.1 -package ghc t.hs
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
[...]
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main ( dint.hs, interpreted )
Ok, modules loaded: Main.
*Main main
Loading package ghc-paths-0.1.0.6 ... linking ... done.
*Main 

# ghci-7.0.1 -package ghc t.hs
GHCi, version 7.0.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
[...]
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main ( dint.hs, interpreted )
Ok, modules loaded: Main.
*Main main
Loading package ghc-paths-0.1.0.8 ... linking ... done.


GHCi runtime linker: fatal error: I found a duplicate definition for symbol
   ___stginit_ghczmprim_GHCziBool
whilst processing object file
   
/Library/Frameworks/GHC.framework/Versions/7.0.1-i386/usr/lib/ghc-7.0.1/ghc-prim-0.2.0.0/libHSghc-prim-0.2.0.0.a
This could be caused by:
   * Loading two different object files which export the same symbol
   * Specifying the same object file twice on the GHCi command line
   * An incorrect `package.conf' entry, causing some object to be
 loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.

# ghc-7.0.1 --make -package ghc t.hs
[1 of 1] Compiling Main ( t.hs, t.o )
Linking t ..
# ./t
#

(that is, no error)


I'm using ghc for mac (intel 32 bits), downloaded in binary form from the ghc 
page.

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


panic parsing a stmt in ghc 7 (possible regression?)

2011-01-31 Thread Daniel Gorín
Hi

I'm trying to make the hint library work also with ghc 7 and I'm having 
problems with some test-cases that are now raising exceptions. I've been able 
to reduce the problem to a small example. The program below runs ghc in 
interpreter-mode and attempts to parse an statement using ghc's parseStmt 
function; the particular statement is a let-expression with a \n in the middle. 
The observed behaviour is:

 $ ghc-6.12.1 -fforce-recomp --make -package ghc -cpp -Wall d.hs  ./d 
 [1 of 1] Compiling Main ( d.hs, d.o )
 Linking d ...
 let {e = let x = ()
 in x ;} in e
 Ok
 $ ghc-7.0.1 -fforce-recomp --make -package ghc -cpp -Wall d.hs  ./d 
 [1 of 1] Compiling Main ( d.hs, d.o )
 Linking d ...
 let {e = let x = ()
 in x ;} in e
 d: d: panic! (the 'impossible' happened)
   (GHC version 7.0.1 for i386-apple-darwin):
   srcLocCol no location info
 
 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

Is it a regression or should I be doing this some other way?

Thanks,
Daniel

-- d.hs
import qualified GHC
import qualified MonadUtils as GHC ( liftIO )
import qualified StringBuffer as GHC
import qualified Lexer as GHC
import qualified Parser as GHC
import qualified GHC.Paths

main :: IO ()
main = GHC.runGhcT (Just GHC.Paths.libdir) $ do
   -- initialize
   df0 - GHC.getSessionDynFlags
   _ - GHC.setSessionDynFlags df0{GHC.ghcMode= GHC.CompManager,
   GHC.hscTarget  = GHC.HscInterpreted,
   GHC.ghcLink= GHC.LinkInMemory,
   GHC.verbosity  = 0}
   df1 - GHC.getSessionDynFlags
  -- runParser
   let expr = let {e = let x = ()\nin x ;} in e
   GHC.liftIO $ putStrLn expr
   buf - GHC.liftIO $ GHC.stringToStringBuffer expr
   let p_res = GHC.unP GHC.parseStmt (mkPState df1 buf GHC.noSrcLoc)
   case  p_res of
 GHC.POk{} - GHC.liftIO $ putStrLn Ok
 GHC.PFailed{} - GHC.liftIO $ putStrLn Failed
where
#if __GLASGOW_HASKELL__ = 700
  mkPState = GHC.mkPState
#else
  mkPState = \a b c - GHC.mkPState b c a
#endif


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


Re: [Haskell-cafe] Re: All binary strings of a given length

2010-10-15 Thread Daniel Gorín
I expect this one to run in constant space:

import Data.Bits

genbin :: Int - [String]
genbin n = map (showFixed n) [0..2^n-1::Int]
where showFixed n i = map (bool '1' '0' . testBit i) [n-1,n-2..0]
  bool t f b = if b then t else f

Daniel

On Oct 15, 2010, at 9:43 AM, Eugene Kirpichov wrote:

 Actually my ghci doesn't crash for genbin 25 (haven't tried further),
 though it eats quite a bit of memory.
 How are you going to use these bit strings? Do you need all of them at once?
 
 2010/10/15 Aleksandar Dimitrov aleks.dimit...@googlemail.com:
 On Fri, 15 Oct 2010 14:34:42 +0200, rgowka1 rgow...@gmail.com wrote:
 
 Amazing, will never find this in any other languagw. But ghci crashes
 for bigger input. Like genbin 20. How to scale this function?
 
 Well, scaling this isn't really possible, because of its complexity. It
 generates all permutations of a given string with two states for each
 position. In regular languages, this is the language {1,0}^n, n being the
 length of the string. This means that there are 2^n different strings in the
 language. For 20, that's already 1048576 different Strings! Strings are
 furthermore not really the best way to encode your output. Numbers (i.e.
 bytes) would be much better. You could generate them, and only translate
 into strings when needed.
 
 HTH,
 Aleks
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 -- 
 Eugene Kirpichov
 Senior Software Engineer,
 Grid Dynamics http://www.griddynamics.com/
 ___
 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] ghc api printing of types

2010-07-04 Thread Daniel Gorín

I believe the way is done in hint is something like this (untested):

showType t =
  do -- Unqualify necessary types
 -- (i.e., do not expose internals)
  unqual - GHC.getPrintUnqual
 return $ GHC.showSDocForUser unqual (GHC.pprTypeForUser False   
t) -- False means 'drop explicit foralls'


Hope that helps

Daniel




On Jul 4, 2010, at 8:36 AM, Phyx wrote:

I was wondering how given a Type I can get a pretty printed type out  
of it.


I’m currently using showSDocUnqual . pprType . snd . tidyOpenType  
emptyTidyEnv
But this has the problem that predicates don’t get printed, anyone  
know how GHCi does this?


Thanks,
Phyx
___
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] Using Hint with a socket server

2010-06-17 Thread Daniel Gorín

Hi Tom,

There is probably more than one way to do this. Did you try using the  
package hint-server? [1] It has a very simple interface: you start a  
server and obtain a handle;  then you can run an interpreter action   
using the handle. Something like this:


 runIn handle (interpret msg (as :: MyType))

This expression has type IO (Either InterpreterError MyType). You can  
also run an interpreter action in the background.


Keep in mind that the ghc-api is not thread safe, though, so you  
should start only one server and put the handle in an MVar


Hope that helps

Daniel

[1] http://hackage.haskell.org/package/hint-server

On Jun 17, 2010, at 6:35 PM, Tom Jordan wrote:

I'm trying to receive small segments of Haskell code over a socket,  
and be able to evaluate them in real time in GHCI.
I've already downloaded Hint and have run the test code, and it's  
working great.  I'm also using the socket server code from Ch.27 of  
Real World Haskell

and that is working well also.

 directly below is the function from the socket server code that  
handles the incoming messages.
 Instead of doing this: putStrLn msg... I want to send  
whatever is captured in msg to the GHC interpreter that is used in  
the Hint code, something like this:  eval msg.
 I'm not sure how to combine both of these functionalities to  
get them to work with each other..


  -- A simple handler that prints incoming packets
  plainHandler :: HandlerFunc
  plainHandler addr msg =
 putStrLn msg


Below is the full  code for the socket server, then below that is  
SomeModule used in the Hint example test below that.


-- file: ch27/syslogserver.hs
import Data.Bits
import Network.Socket
import Network.BSD
import Data.List

type HandlerFunc = SockAddr - String - IO ()

serveLog :: String  -- ^ Port number or name; 514 is  
default
 - HandlerFunc -- ^ Function to handle incoming  
messages

 - IO ()
serveLog port handlerfunc = withSocketsDo $
do -- Look up the port.  Either raises an exception or returns
   -- a nonempty list.
   addrinfos - getAddrInfo
(Just (defaultHints {addrFlags = [AI_PASSIVE]}))
Nothing (Just port)
   let serveraddr = head addrinfos

   -- Create a socket
   sock - socket (addrFamily serveraddr) Datagram defaultProtocol

   -- Bind it to the address we're listening to
   bindSocket sock (addrAddress serveraddr)

   -- Loop forever processing incoming data.  Ctrl-C to abort.
   procMessages sock
where procMessages sock =
  do -- Receive one UDP packet, maximum length 1024 bytes,
 -- and save its content into msg and its source
 -- IP and port into addr
 (msg, _, addr) - recvFrom sock 1024
 -- Handle it
 handlerfunc addr msg
 -- And process more messages
 procMessages sock

-- A simple handler that prints incoming packets
plainHandler :: HandlerFunc
plainHandler addr msg =
putStrLn msg


-- main = serveLog 8008 plainHandler


module SomeModule(g, h) where

f = head

g = f [f]

h = f



import Control.Monad
import Language.Haskell.Interpreter

main :: IO ()
main = do r - runInterpreter testHint
  case r of
Left err - printInterpreterError err
Right () - putStrLn that's all folks

-- observe that Interpreter () is an alias for InterpreterT IO ()
testHint :: Interpreter ()
testHint =
do
  say Load SomeModule.hs
  loadModules [SomeModule.hs]
  --
  say Put the Prelude, Data.Map and *SomeModule in scope
  say Data.Map is qualified as M!
  setTopLevelModules [SomeModule]
  setImportsQ [(Prelude, Nothing), (Data.Map, Just M)]
  --
  say Now we can query the type of an expression
  let expr1 = M.singleton (f, g, h, 42)
  say $ e.g. typeOf  ++ expr1
  say = typeOf expr1
  --
  say $ Observe that f, g and h are defined in SomeModule.hs,   
++

but f is not exported. Let's check it...
  exports - getModuleExports SomeModule
  say (show exports)
  --
  say We can also evaluate an expression; the result will be a  
string

  let expr2 = length $ concat [[f,g],[h]]
  say $ concat [e.g. eval , show expr1]
  a - eval expr2
  say (show a)
  --
  say Or we can interpret it as a proper, say, int value!
  a_int - interpret expr2 (as :: Int)
  say (show a_int)
  --
  say This works for any monomorphic type, even for function  
types

  let expr3 = \\(Just x) - succ x
  say $ e.g. we interpret  ++ expr3 ++
 with type Maybe Int - Int and apply it on Just 7
  

Re: [Haskell-cafe] How efficient is read?

2010-05-08 Thread Daniel Gorín

On May 9, 2010, at 12:32 AM, Tom Hawkins wrote:

I have a lot of structured data in a program written in a different
language, which I would like to read in and analyze with Haskell.  And
I'm free to format this data in any shape or form from the other
language.

Could I define a Haskell type for this data that derives the default
Read, then simply print out Haskell code from the program and 'read'
it in?  Would this be horribly inefficient?  It would save me some
time of writing a parser.

-Tom


If your types contain infix constructors, the derived Read instances  
may be almost unusable; see http://hackage.haskell.org/trac/ghc/ticket/1544


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


Re: [Haskell-cafe] Hint causes GHCi linker error under Windows

2009-12-12 Thread Daniel Gorín

Hi, Martin

Do you have a complete example one can use to reproduce this behavior?  
(preferably a short one! :P)


In any case, I'm resending your message to the glasgow-haskell-users  
list to see if a ghc guru recognize the error message. It is strange  
that the problem only manifests on Windows


Daniel


On Dec 11, 2009, at 7:04 AM, Martin Hofmann wrote:


The following hint code causes GHCi to crash under Windows:


runInterpreter $ loadModules [SomeModule.hs]


The error message is:

GHCi runtime linker: fatal error: I found a duplicate definition for
symbol _hs_gtWord64 whilst processing object file
  C:\Programme\Haskell Platform\2009.2.0.2\ghc-prim-0.1.0.0
HSghc-prim-0.1.0.o
This could be caused by:
  * Loading two different object files which export the same symbol
  * Specifying the same object file twice on the GHCi command line
  * An incorrect `package.conf' entry, causing some object to be
loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.

The problem does not occur under Unix or with a compiled program. IMHO
hint tries to start a second instance of GHCi which is not
allowed/possible under Windows. If this is the case a more telling  
error

message would be helpful.

I used the Haskell Platform, version 2009.2.0.2 under Windows XP. My
package.conf is:

C:/Programme/Haskell Platform/2009.2.0.2\package.conf:
   Cabal-1.6.0.3, GHood-0.0.3, GLUT-2.1.1.2, HTTP-4000.0.6,
   HUnit-1.2.0.3, MonadCatchIO-mtl-0.2.0.0, OpenGL-2.2.1.1,
   QuickCheck-1.2.0.0, Win32-2.2.0.0, ansi-terminal-0.5.0,
   ansi-wl-pprint-0.5.1, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0,
   bimap-0.2.4, bytestring-0.9.1.4, cgi-3001.1.7.1,
   containers-0.2.0.1, cpphs-1.9, directory-1.0.0.3, (dph-base-0.3),
   (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3),
   (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0,
   fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-mtl-1.0.1.0,
   ghc-paths-0.1.0.6, ghc-prim-0.1.0.0, haddock-2.4.2,
   haskeline-0.6.2.2, haskell-src-1.0.1.3, haskell-src-exts-1.3.4,
   haskell98-1.0.1.0, hint-0.3.2.1, hpc-0.5.0.3, html-1.0.1.2,
   integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1,
   old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1,
   parsec-2.1.0.1, pointless-haskell-0.0.1, pretty-1.0.1.0,
   process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2,
   regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2,
   syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4,
   utf8-string-0.3.6, xhtml-3000.2.0.1, zlib-0.5.0.0

Thanks,

Martin

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


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


Re: [Haskell-cafe] Hint causes GHCi linker error under Windows

2009-12-12 Thread Daniel Gorín

Hi, Martin

Do you have a complete example one can use to reproduce this behavior?  
(preferably a short one! :P)


In any case, I'm resending your message to the glasgow-haskell-users  
list to see if a ghc guru recognize the error message. It is strange  
that the problem only manifests on Windows


Daniel


On Dec 11, 2009, at 7:04 AM, Martin Hofmann wrote:


The following hint code causes GHCi to crash under Windows:


runInterpreter $ loadModules [SomeModule.hs]


The error message is:

GHCi runtime linker: fatal error: I found a duplicate definition for
symbol _hs_gtWord64 whilst processing object file
  C:\Programme\Haskell Platform\2009.2.0.2\ghc-prim-0.1.0.0
HSghc-prim-0.1.0.o
This could be caused by:
  * Loading two different object files which export the same symbol
  * Specifying the same object file twice on the GHCi command line
  * An incorrect `package.conf' entry, causing some object to be
loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.

The problem does not occur under Unix or with a compiled program. IMHO
hint tries to start a second instance of GHCi which is not
allowed/possible under Windows. If this is the case a more telling  
error

message would be helpful.

I used the Haskell Platform, version 2009.2.0.2 under Windows XP. My
package.conf is:

C:/Programme/Haskell Platform/2009.2.0.2\package.conf:
   Cabal-1.6.0.3, GHood-0.0.3, GLUT-2.1.1.2, HTTP-4000.0.6,
   HUnit-1.2.0.3, MonadCatchIO-mtl-0.2.0.0, OpenGL-2.2.1.1,
   QuickCheck-1.2.0.0, Win32-2.2.0.0, ansi-terminal-0.5.0,
   ansi-wl-pprint-0.5.1, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0,
   bimap-0.2.4, bytestring-0.9.1.4, cgi-3001.1.7.1,
   containers-0.2.0.1, cpphs-1.9, directory-1.0.0.3, (dph-base-0.3),
   (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3),
   (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0,
   fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-mtl-1.0.1.0,
   ghc-paths-0.1.0.6, ghc-prim-0.1.0.0, haddock-2.4.2,
   haskeline-0.6.2.2, haskell-src-1.0.1.3, haskell-src-exts-1.3.4,
   haskell98-1.0.1.0, hint-0.3.2.1, hpc-0.5.0.3, html-1.0.1.2,
   integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1,
   old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1,
   parsec-2.1.0.1, pointless-haskell-0.0.1, pretty-1.0.1.0,
   process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2,
   regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2,
   syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4,
   utf8-string-0.3.6, xhtml-3000.2.0.1, zlib-0.5.0.0

Thanks,

Martin

___
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] Problems with Language.Haskell.Interpreter and errors

2009-11-11 Thread Daniel Gorín


On Nov 11, 2009, at 5:39 AM, Martin Hofmann wrote:


I still have problems and your code won't typecheck on my machine
printing the following error:

[...]

I assume we are using different versions of some packages. Could you
please send me the output of your 'ghc-pkg list'.

Thanks,

Martin



Sure.

Global:
Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3,
OpenGL-2.2.1.1, QuickCheck-1.2.0.0, array-0.2.0.0, base-3.0.3.1,
base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1,
containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3),
(dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3),
(dph-prim-seq-0.3), (dph-seq-0.3), editline-0.2.1.0,
extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2,
(ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3,
haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1,
mtl-1.1.0.2, network-2.2.1.2, network-2.2.1.4, old-locale-1.0.0.1,
old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1,
parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1,
regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3,
rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1,
time-1.1.2.4, time-1.1.4, unix-2.3.2.0, xhtml-3000.2.0.1,
zlib-0.5.0.0

User:
  MonadCatchIO-mtl-0.2.0.0, ghc-mtl-1.0.1.0, ghc-paths-0.1.0.5,  
hint-0.3.2.0, utf8-string-0.3.5.


Hope that helps

Daniel


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


Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-11-10 Thread Daniel Gorín


On Sep 30, 2009, at 2:20 AM, Martin Hofmann wrote:


Thanks a lot.


You ought to be able to add a Control.Monad.CatchIO.catch clause to
your interpreter to catch this kind of errors, if you want.


I forgot to mention that this didn't work for me either.


Thanks for the report!


You are welcome. If you come up with a work around or a fix, I would  
appreciate if you let me know.


Cheers,

Martin


Apologies for a very very very late follow-up on this thread (http://thread.gmane.org/gmane.comp.lang.haskell.cafe/64013 
).


It turns out that Control.Monad.CatchIO.catch was the right thing to  
use; you were probably bitten, just like me, by the fact that eval  
builds a thunk and returns it, but does not execute it. The following  
works fine for me:


import Prelude hiding ( catch )
import Language.Haskell.Interpreter
import Control.Monad.CatchIO ( catch )
import Control.Exception.Extensible hiding ( catch )

main :: IO ()
main = print = (runInterpreter (code `catch` handler))
where s= let lst [a] = a in lst []
  code = do setImports [Prelude]
forceM $ eval s
  handler (PatternMatchFail _) = return catched!

forceM :: Monad m = m a - m a
forceM a = a = (\x - return $! x)

When run, it prints  'Right catched!'. Notice that if you change the  
line 'forceM $ eval s' by an 'eval s', then the offending thunk is  
reduced by the print statement and the exception is thrown outside the  
catch.


Hope this helps

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


Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-09-29 Thread Daniel Gorín

On Sep 29, 2009, at 8:56 AM, Martin Hofmann wrote:


Hi,

The API of Language.Haskell.Interpreter says, that 'runInterpreter'

runInterpreter :: (MonadCatchIO m, Functor m) =
InterpreterT m a -
m (Either InterpreterError a)

returns 'Left' in case of errors and 'GhcExceptions from the  
underlying

GHC API are caught and rethrown as this'.


What kind of errors do a generate here, why are they not caught by
runInterpreter and how can I catch them? I assumed to get a 'Left
InterpreterError' from the first and an error in MonadCatchIO in the
second.


:m +Language.Haskell.Interpreter
let estr1 = let lst [a] = a; lst _ = error \foo\ in lst []
let estr1 = let lst [a] = a; in lst []
runInterpreter (setImportsQ [(Prelude, Nothing)]  eval estr1 )

Right *** Exception: foo

runInterpreter ( eval estr2)
Right *** Exception: interactive:1:101-111: Non-exhaustive  
patterns in function lst



Thanks a lot




InterpreterErrors are those that prevent your to-be-interpreted code  
from compiling/typechecking. In this case, estr1 is interpreted just  
fine; but the interpreted value is an exception. So I think  Ritght...  
is ok.


You ought to be able to add a Control.Monad.CatchIO.catch clause to  
your interpreter to catch this kind of errors, if you want. I just  
tried it and failed, though, so this is probably a bug. I'll try to  
track it down in more detail.


Thanks for the report!

Daniel

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


Re: Using the ghc-api to run more than one instance of ghc simultaneously

2009-07-14 Thread Daniel Gorín


On Jul 13, 2009, at 10:53 PM, Marc Weber wrote:


Yes, it is a known limitation.  It ought to be documented somewhere.

There are two problems:

 1. GHC is not thread-safe.  [...]

 2. There is only one RTS linker with a single symbol table.  [...]


Are there already bug tracker items for these two problems?
I've tried finding them but didn't succeed. This would be a fast way  
to

document this issue even if its unlikely to be fixed soon.

Marc Weber


For the record, now there are:

http://hackage.haskell.org/trac/ghc/ticket/3372
http://hackage.haskell.org/trac/ghc/ticket/3373

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


Using the ghc-api to run more than one instance of ghc simultaneously

2009-07-12 Thread Daniel Gorín

Hi

I'm trying to use the GHC API to have several instances of GHC's  
interpreter loaded simultaneously; each with its own loaded modules,  
etc. However, this doesn't seem to work well when two instances have  
loaded modules with the same name. I'm including the code of a  
small(ish) example of this at the end of the message.


The example launches two threads (with forkIO) and fires GHC in  
interpreted mode on each thread (with GHC.runGhc); then it  
sequentially loads file TestMain1.hs in the first and TestMain2.hs in  
the second one and finally tries to evaluate expression test1 defined  
in the first one followed by test2 defined in the second one. The  
output is:


#./Main
1: Load succeded
2: Load succeded
3: (1,2,3)
4: Main:
During interactive linking, GHCi couldn't find the following symbol:
  Main_test1_closure
This may be due to you not asking GHCi to load extra object files,
archives or DLLs needed by your current session.  Restart GHCi,  
specifying

the missing library using the -L/path/to/object/dir and -lmissinglibname
flags, or simply by naming the relevant files on the GHCi command line.
Alternatively, this link failure might indicate a bug in GHCi.
If you suspect the latter, please send a bug report to:
  glasgow-haskell-b...@haskell.org

Main: thread blocked indefinitely
#

The thread blocked indefinitely message is not important (comes from  
simplifying the original example). I tried this both in ghc 6.10.1 and  
ghc 6.11.20090607 with the same results.


Is this a known limitation? Or should I be doing it some other way?

Thanks,
Daniel

{-# LANGUAGE MagicHash #-}
module Main where

import Prelude hiding ( init )

import Control.Monad ( join, forever )
import Control.Concurrent ( forkIO )
import Control.Concurrent.Chan


import GHC ( Ghc )
import qualified GHC
import qualified MonadUtils as GHC

import qualified GHC.Paths
import qualified GHC.Exts

main :: IO ()
main = do let test1 = TestMain1.hs
  let test2 = TestMain2.hs
  writeFile test1 module Main where test1 = (1,2,3)
  writeFile test2 module Main where test1 = (3,2,1)
  --
  ghc_1 - newGhcServer
  ghc_2 - newGhcServer
  line 1 $ runInServer ghc_1 $ load (test1, Main)
  line 2 $ runInServer ghc_2 $ load (test2, Main)
  line 3 $ runInServer ghc_1 $ eval test1
  line 4 $ runInServer ghc_2 $ eval test1
  where line n a = putStr (n ++ : )  a

type ModuleName = String
type GhcServerHandle = Chan (Ghc ())

newGhcServer :: IO GhcServerHandle
newGhcServer = do pChan - newChan
  let be_a_server = forever $ join (GHC.liftIO $  
readChan pChan)

  forkIO $ ghc be_a_server
  return pChan
  where ghc action = GHC.runGhc (Just GHC.Paths.libdir) (init   
action)

init = do df - GHC.getSessionDynFlags
  GHC.setSessionDynFlags df{GHC.ghcMode=  
GHC.CompManager,
GHC.hscTarget  =  
GHC.HscInterpreted,
GHC.ghcLink=  
GHC.LinkInMemory,

GHC.verbosity  = 0}


runInServer :: GhcServerHandle - Ghc a - IO a
runInServer h action = do me - newChan
  writeChan h $ action = (GHC.liftIO .  
writeChan me)

  readChan me


load :: (FilePath,ModuleName) - Ghc ()
load (f,mn) = do target - GHC.guessTarget f Nothing
 GHC.setTargets [target]
 res - GHC.load GHC.LoadAllTargets
 GHC.liftIO $ putStrLn (Load  ++ showSuccessFlag res)
 --
 m - GHC.findModule (GHC.mkModuleName mn) Nothing
 GHC.setContext [m] []
where showSuccessFlag GHC.Succeeded = succeded
  showSuccessFlag GHC.Failed= failed

eval :: String - Ghc ()
eval e = do show_e - GHC.compileExpr $ (show (++ e ++)) :: String
GHC.liftIO $ putStrLn (GHC.Exts.unsafeCoerce# show_e)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] .hi inconsistency bug.

2009-03-18 Thread Daniel Gorín
So, if I understand correctly, the interpreter is compiling  
MainTypes twice?


No, the interpreter is trying to compile types that were already  
compiled by the compiler when building your application. The resulting  
types are incompatible.


Could this be a result of having two outputs (one executable and one  
library) in my .cabal file? it _does_ compile those things twice...  
If I create a second cabal file which separates these two different  
packages, would that fix it?


I don't think so. If you already have your application split in  
library part + executable part, then everything should be fine (as  
long as the library is installed before running your application).


The issue is, the (dynamic) interpreter part of my code is part of  
the main loop of the program, and is (as far as I can see)  
inseparable from the rest of the code.


What you need to separate is the code you are planning to interpret in  
runtime. For example, say you have:


src/HackMail/Main.hs
src/HackMail/Data/Types.hs
src/SomePlugin.hs

and SomePlugin.hs is loaded by the interpreter, then you may want to  
reorganize your files like

this:

src/HackMail/Main.hs
src/HackMail/Data/Types.hs
plugins/SomePlugin.hs

and set the source path to plugins directory (using something like  
unsafeSetGhcOption -i./plugins, or set [searchPath := [./ 
plugins]], if using the darcs version).


Daniel

I'll give the cabal thing a try, given the incredible triviality of  
doing everything with cabal, I should be done testing the solution  
before I hit the send button... Cabal guys, you rock.


Thanks again, Dan.

/Joe

Daniel Gorín wrote:

Hi

Just a wild guess but maybe the interpreter is recompiling (in  
runtime) code that has already been compiled to build your  
application (in compile-time). This may lead to inconsistencies  
since a type such as HackMail.Data.Main.Types.Filter may refer to  
two different (and incompatible) types.


To see if this is the case, make sure your dynamic code is not  
located together with your base code (i.e., move it to another  
directory, and set the src file directory for the interpreter  
accordingly). Now you may get another runtime error, something  
along the lines of Module not found: HackMail.Data.MainTypes.  
This basically means that you need to make your (already compiled)  
types available to the interpreter. I think the simplest way is to  
put all your support types in a package, register it with ghc, link  
your application to it, and ask the interpreter to use this package  
(with a -package  flag).


Hope this helps!

Daniel

On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote:


List,

I've got this project, source on patch-tag here[1]

It's a nice little project, I've got the whole thing roughly  
working, it compiles okay, everything seems to work, until I try  
to run it, specifically when I run it in ghci, or when I run the  
main executable (which uses hint), and look at any type involving  
my Email type, it gives me the following error:


Type syonym HackMail.Data.MainTypes.Filter:
  Can't find interface-file declaration for type constructor or  
class HackMail.Data.ParseEmail.Email

Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the  
error


As far as I understand, it wants to find the interface-file  
declaration for a specific type (Email) exported by the ParseEmail  
module, all of the exports (I think) are in order. I've tried  
mucking around with it a bit, but I don't fully understand what  
the error even means, much less how to fix it.


Other relevant info, Email is exported in a roundabout way, namely  
by importing a module MainTypes, which exports a module Email,  
which exports a the ParseEmail Module, which exports the datatype  
Email.


The Filter delcaration it _actually_ complains about (it's just  
the first place the email type is invoked) is:


type Filter a = ReaderT (Config, Email) IO a

nothing particularly special.

Any help fixing this is greatly appreciated, I did find this bug  
report[2] which seems like it might be relevant.


But trying to unregister - cabal clean - cabal install doesn't  
fix it. I've also tried manually removing the dist/ folder, and  
also unregistering the package.


Thanks again.

/Joe

[1] http://patch-tag.com/repo/Hackmail/browse
[2] http://hackage.haskell.org/trac/ghc/ticket/2057
jfredett.vcf___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




jfredett.vcf


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


Re: [Haskell-cafe] .hi inconsistency bug.

2009-03-17 Thread Daniel Gorín

Hi

Just a wild guess but maybe the interpreter is recompiling (in  
runtime) code that has already been compiled to build your application  
(in compile-time). This may lead to inconsistencies since a type such  
as HackMail.Data.Main.Types.Filter may refer to two different (and  
incompatible) types.


To see if this is the case, make sure your dynamic code is not  
located together with your base code (i.e., move it to another  
directory, and set the src file directory for the interpreter  
accordingly). Now you may get another runtime error, something along  
the lines of Module not found: HackMail.Data.MainTypes. This  
basically means that you need to make your (already compiled) types  
available to the interpreter. I think the simplest way is to put all  
your support types in a package, register it with ghc, link your  
application to it, and ask the interpreter to use this package (with a  
-package  flag).


Hope this helps!

Daniel

On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote:


List,

I've got this project, source on patch-tag here[1]

It's a nice little project, I've got the whole thing roughly  
working, it compiles okay, everything seems to work, until I try to  
run it, specifically when I run it in ghci, or when I run the main  
executable (which uses hint), and look at any type involving my  
Email type, it gives me the following error:


  Type syonym HackMail.Data.MainTypes.Filter:
Can't find interface-file declaration for type constructor or  
class HackMail.Data.ParseEmail.Email

  Probable cause: bug in .hi-boot file, or inconsistent .hi file
  Use -ddump-if-trace to get an idea of which file caused the  
error


As far as I understand, it wants to find the interface-file  
declaration for a specific type (Email) exported by the ParseEmail  
module, all of the exports (I think) are in order. I've tried  
mucking around with it a bit, but I don't fully understand what the  
error even means, much less how to fix it.


Other relevant info, Email is exported in a roundabout way, namely  
by importing a module MainTypes, which exports a module Email, which  
exports a the ParseEmail Module, which exports the datatype Email.


The Filter delcaration it _actually_ complains about (it's just  
the first place the email type is invoked) is:


  type Filter a = ReaderT (Config, Email) IO a

nothing particularly special.

Any help fixing this is greatly appreciated, I did find this bug  
report[2] which seems like it might be relevant.


But trying to unregister - cabal clean - cabal install doesn't fix  
it. I've also tried manually removing the dist/ folder, and also  
unregistering the package.


Thanks again.

/Joe

[1] http://patch-tag.com/repo/Hackmail/browse
[2] http://hackage.haskell.org/trac/ghc/ticket/2057
jfredett.vcf___
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] .hi inconsistency bug.

2009-03-17 Thread Daniel Gorín

Hi

Just a wild guess but maybe the interpreter is recompiling (in  
runtime) code that has already been compiled to build your application  
(in compile-time). This may lead to inconsistencies since a type such  
as HackMail.Data.Main.Types.Filter may refer to two different (and  
incompatible) types.


To see if this is the case, make sure your dynamic code is not  
located together with your base code (i.e., move it to another  
directory, and set the src file directory for the interpreter  
accordingly). Now you may get another runtime error, something along  
the lines of Module not found: HackMail.Data.MainTypes. This  
basically means that you need to make your (already compiled) types  
available to the interpreter. I think the simplest way is to put all  
your support types in a package, register it with ghc, link your  
application to it, and ask the interpreter to use this package (with a  
-package  flag).


Hope this helps!

Daniel

On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote:


List,

I've got this project, source on patch-tag here[1]

It's a nice little project, I've got the whole thing roughly  
working, it compiles okay, everything seems to work, until I try to  
run it, specifically when I run it in ghci, or when I run the main  
executable (which uses hint), and look at any type involving my  
Email type, it gives me the following error:


 Type syonym HackMail.Data.MainTypes.Filter:
   Can't find interface-file declaration for type constructor or  
class HackMail.Data.ParseEmail.Email

 Probable cause: bug in .hi-boot file, or inconsistent .hi file
 Use -ddump-if-trace to get an idea of which file caused the error

As far as I understand, it wants to find the interface-file  
declaration for a specific type (Email) exported by the ParseEmail  
module, all of the exports (I think) are in order. I've tried  
mucking around with it a bit, but I don't fully understand what the  
error even means, much less how to fix it.


Other relevant info, Email is exported in a roundabout way, namely  
by importing a module MainTypes, which exports a module Email, which  
exports a the ParseEmail Module, which exports the datatype Email.


The Filter delcaration it _actually_ complains about (it's just  
the first place the email type is invoked) is:


 type Filter a = ReaderT (Config, Email) IO a

nothing particularly special.

Any help fixing this is greatly appreciated, I did find this bug  
report[2] which seems like it might be relevant.


But trying to unregister - cabal clean - cabal install doesn't fix  
it. I've also tried manually removing the dist/ folder, and also  
unregistering the package.


Thanks again.

/Joe

[1] http://patch-tag.com/repo/Hackmail/browse
[2] http://hackage.haskell.org/trac/ghc/ticket/2057
jfredett.vcf___
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] Hint and Ambiguous Type issue

2009-03-06 Thread Daniel Gorín
I think you can achieve what you want but you need to use the correct  
types for it. Remember that when you write:


getFilterMainStuff :: Deliverable a = FilePath - Interpreter (Path,  
Filter a)


the proper way to read the signature is the caller of  
getFilterMainStuff is entitled to pick the type of a, as long as it  
picks an instance of Deliverable. Contrast this with a method  
declaration in Java where:


public Set getKeys()

is to be read: The invoked object may pick the type of the result, as  
long as it is a subclass of (or implements) Set.


When you say that you want to apply fMain to a (Config, Email) and  
get back a Deliverable a, I think you mean that fMain picks the type  
for a (and has to be an instance of Deliverable). There two ways to do  
this in Haskell:


1) You don't. If you know that your possible Deliverables are just  
FlatEmail and MaildirEmail, then the idiomatic way of doing this would  
be to turn Deliverable into an ADT:


data Deliverable = FlatEmail  | MaildirEmail  deriving  
(Typeable)

getFilterMainStuff :: FilePath - Interpreter (Path, Filter Deliverable)

2) Existential types. If, for some reason, you need your dynamic  
code to be able to define new deliverables, then you need to use  
the extension called existential types.


-- using GADT syntax
data SomeDeliverable where Wrap :: Deliverable a = a - SomeDeliverable

getFilterMainStuff :: FilePath - Interpreter (Path, Filter  
SomeDeliverable)


This basically resembles the contract of the Java world: if you run  
fMain you will get a value of type SomeDeliverable; you can pattern- 
match it and will get something whose actual type you don't know, but  
that it is an instance of class Deliverable.


See http://www.haskell.org/haskellwiki/Existential_type

Good luck!

Daniel

On Mar 6, 2009, at 2:33 AM, Joseph Fredette wrote:

Okay, I think I understand... I got so hung up thinking the error  
had to be in the Interpreter code, I didn't bother to look in the  
caller...


But every answer breeds another question... The practical reason for  
inferring fMain as being of type Deliverable a = Filter a, is to  
apply it (via runReader) to a (Config, Email) and get back a  
Deliverable a, then to use the deliverIO method on the result -- my  
question is, it appears I have to know the specific type of a in  
order to get the thing to typecheck, but in order to use it, I need  
to not know it...


Perhaps, in fact, I'm doing this wrong. Thanks for the help Daniel,  
everyone...


/Joe

Daniel Gorín wrote:

Ok, so I've pulled the latest version and the error I get now is:

Hackmain.hs:70:43:
   Ambiguous type variable `a' in the constraint:
 `Deliverable a'
   arising from a use of `getFilterMainStuff' at Hackmain.hs: 
70:43-60
   Probable fix: add a type signature that fixes these type  
variable(s)


Function getFilterMainStuff compiles just fine . The offending line  
is in buildConf and reads:


 (inboxL, fMain) - runUnsafeInterpreter . getFilterMainStuff $  
filterMainL


The problem is that GHC can't figure out the type of fMain. It  
infers (Filter a), but doesn't know what is a and therefore how to  
build a proper dictionary to pass to getFilterMainStuff.


Observe that you would get a similar error message if you just  
defined:


 f = show . read

I can get it to compile by providing a type annotation for fMain:

 (inboxL, fMain) - runUnsafeInterpreter . getFilterMainStuff $  
filterMainL

 let _ = fMain :: Filter MaildirEmail

So once you use fMain somewhere and GHC can infer it's type,  
everything should work fine.


Daniel

On Mar 5, 2009, at 11:26 PM, Joseph Fredette wrote:

Oh, crap- I must have never pushed the latest patches, I did put  
the typeable instances in all the appropriate places. And provided  
a (maybe incorrect? Though I'm fairly sure that shouldn't affect  
the bug I'm having now) Typeable implementation for Reader, but I  
still get this ambiguous type. I'll push the current version asap.


Thanks.

/Joe

Daniel Gorín wrote:

Hi

I've downloaded Hackmain from patch-tag, but I'm getting a  
different error. The error I get is:


Hackmain.hs:63:10:
  No instance for (Data.Typeable.Typeable2
 Control.Monad.Reader.Reader)
arising from a use of `interpret' at Hackmain.hs:63:10-67

Hint requires the interpreted values to be an instance of  
Typeable in order to check, in runtime, that the interpreted  
value matches the type declared at compile. Therefore, you need  
to make  sure that (Filter a) is indeed an instance of Typeable.


Since you have Filter a = Reader (Config, Email) a, you probably  
need to


- Derive Config and Email instances for Filter,

- Manually provide Typeable instances for Reader a b, something  
along the lines of:


instance (Typeable a, Typeable b) = Typeable (Reader a b) where...

(I don't know why this isn't done in the mtl)

- Change the signature to:

getFilterMain :: (Typeable a, Deliverable a) = FilePath

Re: [Haskell-cafe] Hint and Ambiguous Type issue

2009-03-05 Thread Daniel Gorín

Hi

I've downloaded Hackmain from patch-tag, but I'm getting a different  
error. The error I get is:


Hackmain.hs:63:10:
No instance for (Data.Typeable.Typeable2
   Control.Monad.Reader.Reader)
  arising from a use of `interpret' at Hackmain.hs:63:10-67

Hint requires the interpreted values to be an instance of Typeable in  
order to check, in runtime, that the interpreted value matches the  
type declared at compile. Therefore, you need to make  sure that  
(Filter a) is indeed an instance of Typeable.


Since you have Filter a = Reader (Config, Email) a, you probably need to

- Derive Config and Email instances for Filter,

- Manually provide Typeable instances for Reader a b, something along  
the lines of:


instance (Typeable a, Typeable b) = Typeable (Reader a b) where...

(I don't know why this isn't done in the mtl)

- Change the signature to:

getFilterMain :: (Typeable a, Deliverable a) = FilePath -  
Interpreter (Filter a)


Also, you can try using infer instead of as :: 

Hope that helps

Daniel

On Mar 5, 2009, at 8:47 PM, Joseph Fredette wrote:

So, I tried both of those things, both each alone and together. No  
dice. Same error, so I reverted back to the

original.  :(
However, I was, after some random type signature insertions, able to  
convert the problem into a different one, via:


getFilterMain :: Deliverable a = FilePath - Interpreter (Filter  
a)  getFilterMain MainLoc = do
  loadModules [fMainLoc]; setTopLevelModules [(takeWhile (/='.')  
fMainLoc)]   fMain  - (interpret  
(filterMain) infer)

  return (fMain :: Deliverable a = Filter a)

 Inferred type is less polymorphic than expected
Quantified type variable `a' is mentioned in the environment:
  fMain :: Filter a (bound at Hackmain.hs:77:1)
  In the first argument of `return', namely
  `(fMain :: (Deliverable a) = Filter a)'
  In the expression: return (fMain :: (Deliverable a) = Filter a)
  In the expression:
  do loadModules [fMainLoc]
 setTopLevelModules [(takeWhile (/= '.') fMainLoc)]
 fMain - (interpret (filterMain) infer)
 return (fMain :: (Deliverable a) = Filter a)
  I'm 
 thinking that this might be more easily solved -- I do think I  
understand the issue. somehow, I need to tell the compiler
that the 'a' used in the return statement (return (fMain :: ...)) is  
the same as the 'a' in the type sig for the whole function.


While I ponder this, and hopefully receive some more help -- thanks  
again Dan, Ryan -- Are there any other options besides Hint that  
might -- at least in the short term -- make this easier? I'd really  
like to finish this up. I'm _so_ close to getting it done.


Thanks,

/Joe

Ryan Ingram wrote:

So, by using the Haskell interpreter, you're using the
not-very-well-supported dynamically-typed subset of Haskell.  You can
tell this from the type signature of interpret:



interpret :: Typeable a = String - a - Interpreter a





as :: Typeable a = a
as = undefined



(from 
http://hackage.haskell.org/packages/archive/hint/0.2.1/doc/html/src/Language-Haskell-Interpreter-GHC.html)

In particular, the as argument to interpret is specifying what type
you want the interpreted result to be typechecked against; the
interpretation fails if it doesn't match that type.  But you need the
result type to be an instance of Typeable; (forall a. Deliverable a  
=

Filter a) most certainly is not.


Off the top of my head, you have a couple of directions you can  
take this.


(1) Make Typeable a superclass of Deliverable, saying that all
deliverable things must be dynamically typeable.  Then derive  
Typeable

on Filter, and have the result be of type Filter a using
ScopedTypeVariables as suggested before. (You can also pass infer  
to
the interpreter and let the compiler try to figure out the result  
type

instead of passing (as :: SomeType).)

(2) Make a newtype wrapper around Filter and give it an instance of
Typeable, and add a constraint to filterMain that the result type in
the filter is also typeable.  Then unwrap the newtype after the
interpreter completes.

Good luck; I've never tried to use the Haskell interpreter before, so
I'm curious how well it works and what problems you have with it!


 -- ryan

2009/3/5 Joseph Fredette jfred...@gmail.com:

I've been working on a little project, and one of the things I  
need to do is
dynamically compile and import a Haskell Source file containing  
filtering
definitions. I've written a small monad called Filter which is  
simply:


 type Filter a = Reader (Config, Email) a

To encompass all the email filtering. The method I need to import,
filterMain, has type:

 filterMain :: Deliverable a = Filter a

where Deliverable is a type class which abstracts over delivery to  
a path in

the file system. The notion is that I can write a type 

Re: [Haskell-cafe] Hint and Ambiguous Type issue

2009-03-05 Thread Daniel Gorín

Ok, so I've pulled the latest version and the error I get now is:

Hackmain.hs:70:43:
Ambiguous type variable `a' in the constraint:
  `Deliverable a'
arising from a use of `getFilterMainStuff' at Hackmain.hs: 
70:43-60
Probable fix: add a type signature that fixes these type  
variable(s)


Function getFilterMainStuff compiles just fine . The offending line is  
in buildConf and reads:


 (inboxL, fMain) - runUnsafeInterpreter . getFilterMainStuff $  
filterMainL


The problem is that GHC can't figure out the type of fMain. It infers  
(Filter a), but doesn't know what is a and therefore how to build a  
proper dictionary to pass to getFilterMainStuff.


Observe that you would get a similar error message if you just defined:

 f = show . read

I can get it to compile by providing a type annotation for fMain:

 (inboxL, fMain) - runUnsafeInterpreter . getFilterMainStuff $  
filterMainL

 let _ = fMain :: Filter MaildirEmail

So once you use fMain somewhere and GHC can infer it's type,  
everything should work fine.


Daniel

On Mar 5, 2009, at 11:26 PM, Joseph Fredette wrote:

Oh, crap- I must have never pushed the latest patches, I did put the  
typeable instances in all the appropriate places. And provided a  
(maybe incorrect? Though I'm fairly sure that shouldn't affect the  
bug I'm having now) Typeable implementation for Reader, but I still  
get this ambiguous type. I'll push the current version asap.


Thanks.

/Joe

Daniel Gorín wrote:

Hi

I've downloaded Hackmain from patch-tag, but I'm getting a  
different error. The error I get is:


Hackmain.hs:63:10:
   No instance for (Data.Typeable.Typeable2
  Control.Monad.Reader.Reader)
 arising from a use of `interpret' at Hackmain.hs:63:10-67

Hint requires the interpreted values to be an instance of Typeable  
in order to check, in runtime, that the interpreted value matches  
the type declared at compile. Therefore, you need to make  sure  
that (Filter a) is indeed an instance of Typeable.


Since you have Filter a = Reader (Config, Email) a, you probably  
need to


- Derive Config and Email instances for Filter,

- Manually provide Typeable instances for Reader a b, something  
along the lines of:


instance (Typeable a, Typeable b) = Typeable (Reader a b) where...

(I don't know why this isn't done in the mtl)

- Change the signature to:

getFilterMain :: (Typeable a, Deliverable a) = FilePath -  
Interpreter (Filter a)


Also, you can try using infer instead of as :: 

Hope that helps

Daniel

On Mar 5, 2009, at 8:47 PM, Joseph Fredette wrote:

So, I tried both of those things, both each alone and together. No  
dice. Same error, so I reverted back to the

original.  :(
However, I was, after some random type signature insertions, able  
to convert the problem into a different one, via:


getFilterMain :: Deliverable a = FilePath - Interpreter (Filter  
a)  getFilterMain MainLoc = do
 loadModules [fMainLoc]; setTopLevelModules [(takeWhile (/ 
='.') fMainLoc)]   fMain  -  
(interpret (filterMain) infer)

 return (fMain :: Deliverable a = Filter a)

Inferred type is less polymorphic than expected
   Quantified type variable `a' is mentioned in the environment:
 fMain :: Filter a (bound at Hackmain.hs:77:1)
 In the first argument of `return', namely
 `(fMain :: (Deliverable a) = Filter a)'
 In the expression: return (fMain :: (Deliverable a) = Filter a)
 In the expression:
 do loadModules [fMainLoc]
setTopLevelModules [(takeWhile (/= '.') fMainLoc)]
fMain - (interpret (filterMain) infer)
return (fMain :: (Deliverable a) = Filter a)
 I'm 
 thinking that this might be more easily solved -- I do think I  
understand the issue. somehow, I need to tell the compiler
that the 'a' used in the return statement (return (fMain :: ...))  
is the same as the 'a' in the type sig for the whole function.


While I ponder this, and hopefully receive some more help --  
thanks again Dan, Ryan -- Are there any other options besides Hint  
that might -- at least in the short term -- make this easier? I'd  
really like to finish this up. I'm _so_ close to getting it done.


Thanks,

/Joe

Ryan Ingram wrote:

So, by using the Haskell interpreter, you're using the
not-very-well-supported dynamically-typed subset of Haskell.  You  
can

tell this from the type signature of interpret:



interpret :: Typeable a = String - a - Interpreter a





as :: Typeable a = a
as = undefined



(from 
http://hackage.haskell.org/packages/archive/hint/0.2.1/doc/html/src/Language-Haskell-Interpreter-GHC.html)

In particular, the as argument to interpret is specifying what  
type

you want the interpreted result to be typechecked against; the
interpretation fails if it doesn't match that type.  But you need  
the
result type to be an instance

Re: length of module name affecting performance??

2009-02-09 Thread Daniel Gorín

http://hackage.haskell.org/trac/ghc/ticket/2884

On Feb 9, 2009, at 10:53 AM, Wolfgang Jeltsch wrote:


Am Montag, 29. Dezember 2008 12:54 schrieb Simon Peyton-Jones:
What a great bug -- I would never have predicted it, but in  
retrospect it

makes perfect sense. Record selectors had better get fixed.


Can I read somewhere about what caused this bug? What is its trac URL?

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


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


Re: [Haskell-cafe] Newtype deriving with functional dependencies

2009-02-01 Thread Daniel Gorín

On Feb 2, 2009, at 1:06 AM, Louis Wasserman wrote:


Is there any sensible way to make

newtype FooT m e = FooT (StateT Bar m e) deriving (MonadState)

work to give instance MonadState Bar (FooT m e)?

That is, I'm asking if there would be a semantically sensible way of  
modifying GeneralizedNewtypeDeriving to handle multi-parameter type  
classes when there is a functional dependency involved, assuming by  
default that the newtype is the more general of the types, perhaps?


Louis Wasserman
wasserman.lo...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



did you try this?

newtype FooT m e = FooT (StateT Bar m e) deriving (Monad, MonadState  
Bar)___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


length of module name affecting performance??

2008-12-15 Thread Daniel Gorín

Hi

While trying to see if I could make some code run faster I stumbled  
upon something that looks weird to me: 2x-3x performance loss when a  
module is renamed to a longer name!


Here's what I see with the attached examples:

#diff long-modname-ver.hs short-modname-ver.hs
2c2
 import VeryLongModuleName
---
 import ShortM

#diff VeryLongModuleName.hs ShortM.hs
1c1
 module VeryLongModuleName
---
 module ShortM

#ghc --make -O2 -Wall long-modname-ver.hs

#ghc --make -O2 -Wall short-modname-ver.hs

#time -p ./long-modname-ver  /dev/null
real 55.90
user 55.17
sys 0.51

#time -p ./short-modname-ver  /dev/null
real 22.23
user 21.97
sys 0.10

I'm using GHC 6.10.1 on OS X. Any ideas on what may be going on?

Thanks
Daniel



files.tgz
Description: Binary data


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


Re: length of module name affecting performance??

2008-12-15 Thread Daniel Gorín

On Dec 15, 2008, at 10:43 PM, Don Stewart wrote:


dons:

Running time as a function of module name length,

   http://galois.com/~dons/images/results.png

10 is the magic threshold, where indirections start creeping in.

Codegen cost heuristic fail?


Given this, could you open a bug ticket for it, with all the info we
have,

   http://hackage.haskell.org/trac/ghc/newticket?type=bug

E.g. the graph, the code, the asm diff.

Cheers,
 Don


done! http://hackage.haskell.org/trac/ghc/ticket/2884

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


Re: [Haskell-cafe] propogation of Error

2008-12-05 Thread Daniel Gorín

i would expect to get back the Error from the *first* function in the
sequence of functions in checkHeader (oggHeaderError from the  
oggHeader

function). but instead i always see the Error from the *last* function
in the sequence, OggPacketFlagError from the OggPacketFlag function.  
why
is this? is there any way i can get the desired behavior...i.e. see  
the

Error from the first function in the sequence that fails?



Hi

You are essentially asking why this function:

checkHeader handle = ((oggHeader handle)   
  (oggStreamFlag handle)   
  (oggHeaderFlag handle)   
  (skipBytes handle 20)
  (oggPageSecCount handle) 
  (oggPacketFlag handle))

returns the last error (OggPacketFlagError) instead of the first one.  
Some type annotations might help you see what is going on. So let's  
ask ghci the type of, e.g. oggHeaderFlag


*File.Ogg :t oggHeaderFlag
oggHeaderFlag :: SIO.Handle - IO (Either OggParseErrorType [Char])

oggHeaderFlag takes a handle, and computes either an error or a  
string. But since you are using , the computed value is not passed  
to the next function in the pipe! There is no way checkHeader can stop  
early simply because it is ignoring the intermediate results altogether.


Since you are importing Control.Monad.Error, I believe you would  
probably want oggHeaderFlag et al to have type:


SIO.Handle - ErrorT OggParseErrorType IO [Char]

This will propagate errors correctly.

You can see a version of your code using ErrorT here: http://hpaste.org/12705#a1

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


Re: GADT Type Checking GHC 6.10 versus older GHC

2008-11-21 Thread Daniel Gorín


On Nov 21, 2008, at 2:04 PM, Jason Dagit wrote:


Hello,

[...]

My understanding was that from 6.6 to 6.8, GADT type checking was
refined to fill some gaps in the soundness.  Did that happen again
between 6.8 and 6.10 or is 6.10 being needlessly strict here?

Thanks,
Jason


typing rules for gadts changed in 6.10. try:

 http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] using ghc as a library

2008-10-26 Thread Daniel Gorín


On Oct 25, 2008, at 8:39 PM, Anatoly Yakovenko wrote:


so I am trying to figure out how to use ghc as a library.  following
this example, http://www.haskell.org/haskellwiki/GHC/As_a_library, i
can load a module and examine its symbols:
[...]

given Test.hs:

module Test where

hello = hello
world = world
one = 1
two = 2

i get this output:

$ ./Main ./Test.hs
[]
[Test.hello, Test.one, Test.two, Test.world]

which is what i expect.  My question is, how do manipulate the symbols
exported by Test?  Is there a way to test the types?  lets say i
wanted to sum all the numbers and concatenate all the strings in
Test.hs, how would i do that?


Hi, Anatoly

Sorry for don't answering your question in the first place, but for  
this kind of tasks I believe you might be better off using some  
lightweight wrapper of the GHC Api. For instance, using   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hint 
 you write:


import Language.Haskell.Interpreter.GHC
import Control.Monad.Trans ( liftIO  )
import Control.Monad   ( filterM )

test_module = Test

main :: IO ()
main = do s - newSession
  withSession s $ do
  loadModules [test_module]-- loads Test.hs...
  setTopLevelModules [test_module] -- ...and puts it in  
scope
  setImports [Prelude]   -- put the Prelude in  
scope too

  --
  exports - getModuleExports Test -- get Test's symbols
  let ids = [f | Fun f - exports]
  --
  strings - filterM (hasType [Char]) ids
  conc - concat `fmap` mapM (\e - interpret e infer)  
strings

  liftIO $ putStrLn conc
  --
  ns - filterM (hasType Integer) ids
  sum_ns - sum `fmap` mapM (\e - interpret e (as ::  
Integer)) ns

  liftIO $ putStrLn (show sum_ns)


hasType :: String - Id - Interpreter Bool
hasType t e = do type_of_e - typeOf e
 return (type_of_e == t)

$ ./Main
helloworld
3

The version in hackage of hint works only with GHC 6.6.x and 6.8.x,  
mind you, but a new version is coming soon


Good luck,

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


Re: gadt changes in ghc 6.10

2008-10-15 Thread Daniel Gorín

Hi, Simon

Thanks a lot for your mail. It turns out I could have resolved this by  
myself (with the help of this thread http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153 
, to be honest). What I was missing was this key part:



bind :: forall a b t. W t a - (a - W t b) - W_ t b
--- the forall brings a,b,t into scope inside bind



So, while I had turned on the ScopedTypeVariables extension, none of  
the type variables in question was actually in scope. How embarrassing!


I can't blame anyone but me for this but, anyway, I feel that it may  
have helped me if the introduction of Section 8.7.6 of the user manual  
were a little more explicit about this. Although the example reads  
f :: forall a. [a] - [a], and the text below says The type  
signature for f brings the type variable into scope, the role of the  
forall is not mentioned until Section 8.7.6.2 (and since I already  
knew what the extension was about, and was only looking for the proper  
extension name, I didn't make it that far :))


Also, since you are always willing to get examples of confusing error  
messages, I wanted to bring this one into attention:



In your case the error message was:

GADT.hs:26:56:
   GADT pattern match with non-rigid result type `Maybe a'
 Solution: add a type signature
   In a case alternative: I1 m' - m'
   In the expression: case w' S of { I1 m' - m' }
   In a case alternative: Wrap w' - case w' S of { I1 m' - m' }



This is when ScopedTypeVariables is off. Now, what I found very  
confusing at first is that I thought the a in 'Maybe a' was  
referring to the a in 'W t a - (a - W t b) - W_ t b', and I  
couldn't see how that could be happening. Once ScopedTypeVariables is  
on, one gets 'GADT pattern match with non-rigid result type `Maybe  
a1' and everything makes more sense :)


And maybe the add a type signature can be more explicit? Like add a  
type signature that makes the type of the result known at the matching  
point. Just a suggestion...


I hope this helps. I'm still trying to find a really good way to  
explain the reasoning here.  Do pls  augment the wiki page with what  
you have learned!




I've put some of this in the Upgrading packages wiki, and added a  
link to the previous thread which I found to be very clear.


Thanks again!

Daniel

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


gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín

Hi

After installing ghc 6.10-rc, I have a program that no longer  
compiles. I get the dreaded GADT pattern match error, instead :)


Here is a boiled-down example:

{-# OPTIONS_GHC -XGADTs -XEmptyDataDecls #-}
module T where

data S
data M

data Wit t where
S :: Wit S
M :: Wit M

data Impl t a where
I1 :: Maybe a - Impl S a
I2 :: [a] - Impl M a

type W_ t a = Wit t - Impl t a

newtype W t a = Wrap (W_ t a)

bind :: W t a - (a - W t b) - W_ t b
bind (Wrap w) f = \wit -
case wit of
  S - case w S of
  I1 m - I1 $ do a - m
  case f a of
Wrap w' - case w' S of
  I1 m' - m'
  M- case w M of
  I2 m - I2 $ do a - m
  case f a of
Wrap w' - case w' M of
  I2 m' - m'

While in ghc 6.8.3 this compiles fine, with ghc 6.10 i get:

$ ghc --make T.hs
[1 of 1] Compiling T( T.hs, T.o )

T.hs:26:57:
GADT pattern match with non-rigid result type `Maybe a'
  Solution: add a type signature
In a case alternative: I1 m' - m'
In the expression: case w' S of { I1 m' - m' }
In a case alternative: Wrap w' - case w' S of { I1 m' - m' }

I've tried adding some signatures (together with - 
XScopedTypeVariables), but with no luck. Why is it that this no longer  
compiles? More importantly, how can I make it compile again? :)


Thanks!

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


Re: gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín

On Oct 14, 2008, at 7:48 PM, Don Stewart wrote:


dgorin:

I've tried adding some signatures (together with -
XScopedTypeVariables), but with no luck. Why is it that this no  
longer

compiles? More importantly, how can I make it compile again? :)



If you work out how to make it compile, can you document the soln.  
here,


   http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching

Cheers,
   Don


Sure, but I must say I'm still kind of lost, here
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghci and source files

2008-07-29 Thread Daniel Gorín

Hi

If you just want to compile from (Eclipse) edit buffers instead of  
source files, I think you can do this with the ghc api. Look at the  
Target type.


The following is pasted from main/HscTypes.lhs

-- | A compilation target.
--
-- A target may be supplied with the actual text of the
-- module.  If so, use this instead of the file contents (this
-- is for use in an IDE where the file hasn't been saved by
-- the user yet).
data Target = Target TargetId (Maybe (StringBuffer,ClockTime))

Hope this helps

Daniel

On Jul 29, 2008, at 11:12 AM, Johannes Waldmann wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Dear all, how does ghci (actually, the ghc API functions)
access the file system?
(It needs to check whether source files had been updated.)
Is it possible to insert an abstraction layer there?
E.g. imagine the sources are not on the file system,
but in Eclipse edit buffers. - Any hints appreciated. J.W.
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.9 (GNU/Linux)
Comment: Using GnuPG with SUSE - http://enigmail.mozdev.org

iEUEARECAAYFAkiPJUEACgkQDqiTJ5Q4dm99LQCXcaCtKnvEsmoGdJ+UQ93A2x0Z
2ACbBfaSZsvU0xHeh/jQbZZjI5VAEdQ=
=eQ4p
-END PGP SIGNATURE-
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


Re: ghci and source files

2008-07-29 Thread Daniel Gorín

On Jul 29, 2008, at 2:43 PM, Johannes Waldmann wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1



data Target = Target TargetId (Maybe (StringBuffer,ClockTime))


looks great. How is this intended to be used,
i.e. what should happen if there is an edit/save event in the IDE?
Then the IDE constructs a new StringBuffer from the buffer contents
and sends it to the GHC API? (what call?)


IIRC,you first set (or add) targets (with GHC.setTargets or  
GHC.addTargets) and then run GHC.load indicating LoadAllTargets. I  
*think* it will chose to use the StringBuffer only if the ClockTime  
is newer than the file's timestamp. Thus, if the user updates and  
saves the file between the creation of the StringBuffer and the  
actual call to GHC.load, ghc will load the target from disk.


But I'm mostly guessing here, so you should probably try it out and  
see if it works  :)


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


Re: [Haskell-cafe] Haskell's type system

2008-06-18 Thread Daniel Gorín

On Jun 17, 2008, at 11:08 PM, Don Stewart wrote:


Haskell's type system is based on System F, the polymorphic lambda
calculus. By the Curry-Howard isomorphism, this corresponds to
second-order logic.



just nitpicking a little this should read second-order  
propositional logic, right?


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


Re: [Haskell-cafe] hint / ghc api and reloading modules

2008-05-31 Thread Daniel Gorín
(Since this can be of interest to those using the ghc-api I'm cc-ing  
the ghc users' list.)


Hi, Evan

The odd behavior you spotted happens only with hint under ghc-6.8. It  
turns out the problem was in the session initialization.


Since ghc-6.8 the newSession function no longer receives a GhcMode.  
The thing is that, apparently, if one was passing the Interactive  
mode to newSession under ghc-6.6, now you ought to set the ghcLink  
dynflag to LinkInMemory instead.


I couldn't find this documented anywhere (except for this patch  
http://www.haskell.org/pipermail/cvs-ghc/2007-April/034974.html) but  
it is what ghci is doing and after patching hint to do this the  
reloading of modules works fine.


I'll be uploading a fixed version of hint to hackage in the next days.

Thanks,
Daniel

On May 31, 2008, at 2:46 PM, Evan Laforge wrote:


I'm using hint, but since it's basically a thin wrapper around the
GHC API, this is probably a GHC api question too.  Maybe this should
go to cvs-ghc?  Let me know and I'll go subscribe over there.

It's my impression from the documentation that I should be able to
load a module interpreted, make changes to it, and then reload it.
This is, after all what ghci does.  It's also my impression that the
other imported modules should be loaded as object files, if the .hi
and .o exist, since this is also what ghci does.

However, if I load a module and run code like so (using hint):

GHC.loadModules [Cmd.LanguageEnviron]
GHC.setTopLevelModules [Cmd.LanguageEnviron]
GHC.setImports [Prelude]
cmd_func - GHC.interpret (mangle_code text) (GHC.as :: LangType)

It works fine until I change LanguageEnviron.  If I make a change to a
function, I don't see my changes in the output, as if the session is
only getting partially reset.  If I insert a syntax error, then I do
see it, so it is recompiling the file in some way.  However, if I
*rename* the function and call it with the new name, I get a
GhcException:

During interactive linking, GHCi couldn't find the following symbol:
  ... etc.

So I examined the code in hint for loadModules and the code in
ghci/InteractiveUI.hs:/loadModule, and they do look like they're doing
basically the same things, except a call to rts_revertCAFs, which I
called too just for good measure but it didn't help (I can't find its
source anywhere, but the ghci docs imply it's optional, so I suspect
it's a red herring).

Here's a condensed summary of what hint is doing:
-- reset
GHC.setContext session [] []
GHC.setTargets session []
GHC.load session GHC.LoadAllTargets
-- rts_revertCAFs

-- load
targets - mapM (\f - GHC.guessTarget f Nothing) fs
GHC.setTargets session targets
GHC.load session GHC.LoadAllTargets

-- interpret
let expr_typesig = ($expr) :: xyz
expr_val - GHC.compileExpr session expr_typesig
return (GHC.Exts.unsafeCorce# expr_val :: a)

-- GHC.compileExpr
maybe_stuff - hscStmt hsc_env (let __cmCompileExpr = ++expr)
([n],[hv]) - (unsafeCoerce# hval) :: IO [HValue]
return (Just hv)


and then ghci does:
-- load
GHC.setTargets session []
GHC.load session LoadAllTargets

targets - io (mapM (uncurry GHC.guessTarget) files')
GHC.setTargets session targets
GHC.load session LoadAllTargets

rts_revertCAFs
putStrLn Ok, modules loaded: $modules

-- interpret
GHC.runStmt session stmt step

-- GHC.runStmt
Just (ids, hval) - hscStmt hsc_env' expr
coerce hval to (IO [HValue]) and run it carefully


So it *looks* like I'm doing basically the same thing as ghci...
except obviously I'm not because ghci reloads modules without any
trouble.  Before I go start trying to make hint even more identical to
ghci, is there anything obviously wrong here that I'm doing?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] hint / ghc api and reloading modules

2008-05-31 Thread Daniel Gorín
(Since this can be of interest to those using the ghc-api I'm cc-ing  
the ghc users' list.)


Hi, Evan

The odd behavior you spotted happens only with hint under ghc-6.8. It  
turns out the problem was in the session initialization.


Since ghc-6.8 the newSession function no longer receives a GhcMode.  
The thing is that, apparently, if one was passing the Interactive  
mode to newSession under ghc-6.6, now you ought to set the ghcLink  
dynflag to LinkInMemory instead.


I couldn't find this documented anywhere (except for this patch  
http://www.haskell.org/pipermail/cvs-ghc/2007-April/034974.html) but  
it is what ghci is doing and after patching hint to do this the  
reloading of modules works fine.


I'll be uploading a fixed version of hint to hackage in the next days.

Thanks,
Daniel

On May 31, 2008, at 2:46 PM, Evan Laforge wrote:


I'm using hint, but since it's basically a thin wrapper around the
GHC API, this is probably a GHC api question too.  Maybe this should
go to cvs-ghc?  Let me know and I'll go subscribe over there.

It's my impression from the documentation that I should be able to
load a module interpreted, make changes to it, and then reload it.
This is, after all what ghci does.  It's also my impression that the
other imported modules should be loaded as object files, if the .hi
and .o exist, since this is also what ghci does.

However, if I load a module and run code like so (using hint):

GHC.loadModules [Cmd.LanguageEnviron]
GHC.setTopLevelModules [Cmd.LanguageEnviron]
GHC.setImports [Prelude]
cmd_func - GHC.interpret (mangle_code text) (GHC.as :: LangType)

It works fine until I change LanguageEnviron.  If I make a change to a
function, I don't see my changes in the output, as if the session is
only getting partially reset.  If I insert a syntax error, then I do
see it, so it is recompiling the file in some way.  However, if I
*rename* the function and call it with the new name, I get a
GhcException:

During interactive linking, GHCi couldn't find the following symbol:
  ... etc.

So I examined the code in hint for loadModules and the code in
ghci/InteractiveUI.hs:/loadModule, and they do look like they're doing
basically the same things, except a call to rts_revertCAFs, which I
called too just for good measure but it didn't help (I can't find its
source anywhere, but the ghci docs imply it's optional, so I suspect
it's a red herring).

Here's a condensed summary of what hint is doing:
-- reset
GHC.setContext session [] []
GHC.setTargets session []
GHC.load session GHC.LoadAllTargets
-- rts_revertCAFs

-- load
targets - mapM (\f - GHC.guessTarget f Nothing) fs
GHC.setTargets session targets
GHC.load session GHC.LoadAllTargets

-- interpret
let expr_typesig = ($expr) :: xyz
expr_val - GHC.compileExpr session expr_typesig
return (GHC.Exts.unsafeCorce# expr_val :: a)

-- GHC.compileExpr
maybe_stuff - hscStmt hsc_env (let __cmCompileExpr = ++expr)
([n],[hv]) - (unsafeCoerce# hval) :: IO [HValue]
return (Just hv)


and then ghci does:
-- load
GHC.setTargets session []
GHC.load session LoadAllTargets

targets - io (mapM (uncurry GHC.guessTarget) files')
GHC.setTargets session targets
GHC.load session LoadAllTargets

rts_revertCAFs
putStrLn Ok, modules loaded: $modules

-- interpret
GHC.runStmt session stmt step

-- GHC.runStmt
Just (ids, hval) - hscStmt hsc_env' expr
coerce hval to (IO [HValue]) and run it carefully


So it *looks* like I'm doing basically the same thing as ghci...
except obviously I'm not because ghci reloads modules without any
trouble.  Before I go start trying to make hint even more identical to
ghci, is there anything obviously wrong here that I'm doing?
___
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] Problem with Python AST

2008-02-20 Thread Daniel Gorín

Hi

Something like this would do?

if_ = Compound $ If [(IntLit 6, Suite [] [Break])] Nothing
while_ = Compound $ While (IntLit 6) (Suite [] [if_]) Nothing

f = Program [while_]

-- this one fails
-- f2 = Program [if_]


newtype Ident = Id String

data BinOp = Add
   | Sub

data Exp = IntLit Integer
 | BinOpExp BinOp Exp Exp

data NormalCtx
data LoopCtx

data Statement ctx where
  Compound :: Compound ctx - Statement ctx
  Pass :: Statement ctx
  Break:: Statement LoopCtx

newtype Global = Global [Ident]

data Suite ctx = Suite [Global] [Statement ctx]

type Else ctx = Suite ctx

data Compound ctx where
If:: [(Exp, Suite ctx)] - Maybe (Else ctx) - Compound ctx
While :: Exp - (Suite LoopCtx) -  Maybe (Else LoopCtx) -  
Compound ctx


newtype Program = Program [Statement NormalCtx]

Daniel

On Feb 20, 2008, at 5:12 PM, Roel van Dijk wrote:


Hello everyone,

I am trying to create an AST for Python. My approach is to create a
data type for each syntactic construct. But I am stuck trying to
statically enforce some constraints over my statements. A very short
example to illustrate my problem:


newtype Ident = Id String

data BinOp = Add
   | Sub

data Exp = IntLit Integer
 | BinOpExp BinOp Exp Exp

data NormalCtx
data LoopCtx

data Statement ctx where
  Compound :: Compound - Statement ctx
  Pass :: Statement ctx
  Break:: Statement LoopCtx

newtype Global = Global [Ident]

data Suite ctx = Suite [Global] [Statement ctx]

type Else = Suite NormalCtx

data Compound = If [(Exp, Suite NormalCtx)] (Maybe Else)
  | While Exp (Suite LoopCtx) (Maybe Else)

newtype Program = Program [Statement NormalCtx]


The global statement makes an identifier visible in the local scope.
It holds for the entire current code block. So it also works
backwards, which is why I didn't make it a statement but part of a
suite (= block of statements).

Some statements may occur in any context, such as the pass
statement. But others are only allowed in certain situations, such as
the break statement. This is why I defined the Statement as a GADT.
I just supply the context in which the statement may be used and the
typechecker magically does the rest.

Feeling very content with this solution I tried a slightly more
complex program and discovered that my AST can not represent this
Python program:

for i in range(10):
  if i == 6:
break

The compound if statement is perfectly valid nested in the loop
because the Compound constructor of Statement allows any context. But
the suites inside the clauses of the if statement only allow normal
contexts. Since Break has a LoopCtx the typechecker complains.

Is there some other way to statically enforce that break statements
can only occur _nested_ inside a loop? There is a similar problem with
return statements that may only occur in functions. These nested
statements should somehow 'inherit' a context, if that makes any sense
:-)

I know I can simply create separate data types statements that can
occur inside loops and function bodies. But that would make the AST a
lot more complex, something I try to avoid. Python's syntax is already
complex enough!

Most of these constraints are not in the EBNF grammar which can be
found in the language reference, but they are specified in the
accompanying text. The cpython interpreter will generate SyntaxError's
when you violate these constraints.

See also Python's language reference:
http://docs.python.org/ref/ref.html (see sections 6 and 7)
___
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


Problem with functional dependencies

2007-11-16 Thread Daniel Gorín

Hi

I have some code that uses MPTC + FDs + flexible and undecidable  
instances that was working fine until I did a trivial modification on  
another part of the project. Now, GHC is complaining with a very  
confusing (for me, at least) error message. I've been finally able to  
reproduce the problem using these three small modules:


 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 module M1

 where

 data M n = M
 data F n = F

 class C m f n | m - n, f - n where
 c :: m - f - Bool

 instance C (M n) (F n) n where
 c _ _ = True

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE FlexibleInstances #-}
 module M2

 where

 import M1

 newtype F'= F' (F N)

 data N = N

 instance C m (F N) N = C m F' N where
  c m (F' f) = c m f

 module M3

 where

 import M1
 import M2()

 data N' = N'

 go :: M N' - F N' - Bool
 go m f = c m f

Now, when trying to compile M3 (both in 6.6.1 and 6.8.1) I get:

M3.hs:11:0:
Couldn't match expected type `N'' against inferred type `M2.N'
When using functional dependencies to combine
  C m M2.F' M2.N, arising from the instance declaration at M2.hs: 
13:0

  C (M N') (F N') N', arising from use of `c' at M3.hs:11:9-13
When generalising the type(s) for `go'

It is worth observing that:

- M2 compiles fine
- No type defined in M2 is visible in M3
- if the import M2() is commented out from M3, it compiles fine
- if, in M3, N' is placed by N (needs to be imported), everything  
compiles again


Normally, it takes me some time to digest GHC's type-classes-related  
error messages, but after some reflection, I  finally agree with  
them. This time, however, I'm totally lost. I can't see any reason  
why N' and M2.N would have to be unified, nor why this code should be  
rejected.


Any help would be much appreciated!

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


Re: Problem with functional dependencies

2007-11-16 Thread Daniel Gorín

Hi, Chris

Thanks for your answer. I guess that my intuitions of what functional  
dependencies and context meant were not very  accurate (see below)



class C m f n | m - n, f - n where
c :: m - f - Bool


The m-n functional dependency means that I tell you
C x _ z is an instance then you whenever you match x that you
must have the corresponding z.


That's what I thought..



instance C (M n) (F n) n where
c _ _ = True


This promises that C x _ z with x==M n has z==n


I agree


instance C m (F N) N = C m F' N where
 c m (F' f) = c m f


By the m-n functional dependency, the above implies that _any_  
m must map

to the type M2.N:  m - M2.N

This kills you in M3...


Here I was expecting the context C m (F N) N to work as a logical  
guard, something like:


'for all m such that C m (F N) N holds, C m F' N must hold too'

and since 'C m (F N) N holds' would already imply 'm - N', then C  
m F' N would not produce any contradiction.


I guess this view doesn't hold when FlexibleInstances is on  
Anyway, it makes (kind of) sense now...



By the way, if you make the class C fundep declaration into:


class C m f n | m f - n where


then it compiles.  This means ((M n) and (F n) imply N) and (any  
m and F'

imply N') which no longer conflict.


Thanks again for the tip, I will try it out!

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


Re: module containing GADTs no longer compiles in ghc 6.8.0

2007-09-27 Thread Daniel Gorín
Hi Simon,

Thanks for your prompt response. Actually, the problem was with lambda 
patterns containing GADT constructors in let bindings and I guess GHC doesn't 
like that anymore. 

After replacing them with case statements everything compiles fine as long 
as I don't turn on -O2 optimizations :(

This boiled-down example illustrates my problem:

 {-# OPTIONS_GHC -fglasgow-exts #-}
 module T where
 
 data T a where T :: T a - T [a]
 
 class C a where
   f :: a - ()
 
 instance C (T [a]) where
   f (T x@(T _)) = f x

$ ghc --make -c -Wall -O2 T
[1 of 1] Compiling T( T.hs, t/T.o )
ghc-6.8.0.20070917: panic! (the 'impossible' happened)
  (GHC version 6.8.0.20070917 for i386-unknown-linux):
Template variable unbound in rewrite rule
co_X6j{tv} [tv]
[a{tv a5u} [sk], co_a5X{tv} [tv], a{tv a5Y} [sk], co_a60{tv} [tv],
 ds_d67{v} [lid]]
[a{tv X5P} [sk], co_X6j{tv} [tv], a{tv X6l} [sk], co_X6o{tv} [tv],
 ds_X6w{v} [lid]]
[TYPE a{tv a5Y} [sk],
 (main:T.T{v r5Q} [gid]
@ a{tv a5u} [sk]
@ a{tv a5Y} [sk]
@ co_a60{tv} [tv]
ds_d67{v} [lid])
 `cast` (base:GHC.Prim.trans{(w) tc 34y}
   (main:T.T{tc r1} (base:GHC.Prim.right{(w) tc 34E} co_a5X{tv} 
[tv]))
   (base:GHC.Prim.trans{(w) tc 34y}
  (main:T.T{tc r1}
 (base:GHC.Prim.right{(w) tc 34E}
(base:GHC.Prim.sym{(w) tc 34v} co_a5X{tv} [tv])))
  (main:T.T{tc r1} co_a60{tv} [tv]))
 :: predmain:T.T{tc r1} a{tv a5u} [sk]
~
  main:T.T{tc r1} [a{tv a5Y} [sk]])]
[TYPE a{tv a5Y} [sk],
 wild_Xc{v} [lid]
 `cast` (base:GHC.Prim.trans{(w) tc 34y}
   (main:T.T{tc r1} (base:GHC.Prim.right{(w) tc 34E} co_a5X{tv} 
[tv]))
   (base:GHC.Prim.trans{(w) tc 34y}
  (main:T.T{tc r1}
 (base:GHC.Prim.right{(w) tc 34E}
(base:GHC.Prim.sym{(w) tc 34v} co_a5X{tv} [tv])))
  (main:T.T{tc r1} co_a60{tv} [tv]))
 :: predmain:T.T{tc r1} a{tv a5u} [sk]
~
  main:T.T{tc r1} [a{tv a5Y} [sk]])]

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

Thanks
Daniel

On Wednesday 26 September 2007 13:55:10 Simon Peyton-Jones wrote:
 | PS: On a side note, I found this error message to be kind of funny. It
 | seems to indicate no real error but some sort of error-message-driven
 | poll!

 That's exactly what it is, and you are the pollee.

 Nevertheless it's probably needlessly obscure.  The point is this: you are
 doing case x of { ... }
 where the ... has GADT patterns.  But GHC doesn't know what type 'x' is. 
 Usually type inference will suffice, but not for GADTs.

 Solution: use a type signature to tell GHC just what type x has.  Example:

 f x = case x of ...

 give f a type signature

 f :: forall a. T a - Int

 There ought to be a contributed documentation wiki page about GADTs here
 http://haskell.org/haskellwiki/GHC
 but there isn't yet. Would someone like to start one?

 sorry brevity, rushing to get to icfp

 Simon

 | -Original Message-
 | From: [EMAIL PROTECTED]
 | [mailto:[EMAIL PROTECTED] On Behalf Of Daniel
 | Gorín
 | Sent: 26 September 2007 17:34
 | To: glasgow-haskell-users@haskell.org
 | Subject: module containing GADTs no longer compiles in ghc 6.8.0
 |
 | Hi
 |
 | I just tried to compile a project of mine that builds fine using ghc
 | 6.6.1 and got many errors like this:
 |
 | src/HyLo/Formula/NNF.hs:247:48:
 | GADT pattern match in non-rigid context for `Opaque'
 |   Tell GHC HQ if you'd like this to unify the context
 | In the pattern: Opaque f'
 | In the expression: \ (Opaque f') - Opaque (Box r f')
 | In the definition of `box':
 | box = \ (Opaque f') - Opaque (Box r f')
 |
 | I don't know what a non-rigid context is, nor if I like this to unify
 | the context or not, but I would certainly be happy if I could get this
 | module to compile again! :)
 |
 | For the record, I was using ghc-6.8.0.20070917. Please let me know if you
 | need further information
 |
 | Thanks
 | Daniel
 |
 | ___
 | Glasgow-haskell-users mailing list
 | Glasgow-haskell-users@haskell.org
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


module containing GADTs no longer compiles in ghc 6.8.0

2007-09-26 Thread Daniel Gorín
Hi

I just tried to compile a project of mine that builds fine using ghc 6.6.1 and 
got many errors like this:

src/HyLo/Formula/NNF.hs:247:48:
GADT pattern match in non-rigid context for `Opaque'
  Tell GHC HQ if you'd like this to unify the context
In the pattern: Opaque f'
In the expression: \ (Opaque f') - Opaque (Box r f')
In the definition of `box':
box = \ (Opaque f') - Opaque (Box r f')

I don't know what a non-rigid context is, nor if I like this to unify the 
context or not, but I would certainly be happy if I could get this module to 
compile again! :)

For the record, I was using ghc-6.8.0.20070917. Please let me know if you need 
further information

Thanks
Daniel

PS: On a side note, I found this error message to be kind of funny. It seems 
to indicate no real error but some sort of error-message-driven poll!
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users