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  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 :
>> 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
>>  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-28 Thread Daniel Gorín
It is not only a matter of teaching, I think. After first learning the very 
basics of a language, browsing the libraries that come included is a more or 
less standard way of getting more acquainted with it. By including only the 
abstract versions we are making it much harder to learn the common idioms.

For instance, at the moment, how likely is that someone will start using (&&&), 
(***), (+++) or any of the useful combinators in Control.Arrow from reading its 
haddock? These are very handy functions, easy to understand when specialized to 
(->), but are usually reserved for advanced users since they are presented only 
in their most general way. With an extension like this one available, one could 
propose including specialized versions of them in Data.Function and/or 
Data.Tuple/Data.Either; today it would be a very bad idea due to the clash with 
Control.Arrow!

Daniel

On May 28, 2013, at 3:27 AM, Edward A Kmett wrote:

> This is basically what you get by default already with the raw proposal we've 
> been talking about -- the Preludes in the haskell98 and haskell2010 remain 
> unmodified by this proposal and are available for teaching use.
> 
> Sent from my iPhone
> 
> On May 27, 2013, at 8:53 PM, Andrew Farmer  wrote:
> 
>> I generally agree with Iavor's points, but if this is such an issue, why not 
>> make Prelude more general by default and have a special 'Prelude.Basic' with 
>> the more specific type signatures for beginners? The general Prelude would 
>> be implicitly imported as now, unless the module imported Prelude.Basic 
>> unqualified. Then make Hackage warn/reject packages that use Prelude.Basic.
>> 
>> Tutorials/Books would have to tell readers to add a magic "import 
>> Prelude.Basic" at the beginning of their source files, but tutorials for 
>> other languages do this (public static void main(..)?) to relatively little 
>> complaint.
>> 
>> Sorry, I'm sure this has been proposed before... but the proposed extension 
>> seems complicated to avoid some qualified imports/hidings. If we really want 
>> people to use Foldable's foldr by default, then make it the default and let 
>> beginners add a magic line once per file to get simpler types.
>> 
>> Andrew
>> 
>> 
>> On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:
>> 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  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 d

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  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

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 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
> ___
> 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


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 
> 
> 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] 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: 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: 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: 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


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: 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: 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


Re: gadt changes in ghc 6.10

2008-10-14 Thread Daniel Gorín


On Oct 14, 2008, at 10:19 PM, Jason Dagit wrote:


On Tue, Oct 14, 2008 at 7:27 AM, Daniel Gorín <[EMAIL PROTECTED]>  
wrote:

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:
[...]

I don't have 6.10 handy to try out your program, but in 6.8 and  
older the type error message you're getting means that the compiler  
needs more "outside in" help with type checking this.


Usually this means adding type more type signatures on the outside.   
For example, maybe you need to give the type signatures inside the  
case to make the types inside the pattern matches of the case more  
rigid.  That probably didn't make a lot of sense :(  So here is an  
example,


case wit :: {- Try adding a signature here -} of ...

Given that your code has such deep pattern nesting I would argue  
that it is in your best interest to add local functions (in a where  
clause) along with their explicit type signatures.  Start with the  
inner most case expressions and convert those to local functions and  
work your way out.


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? :)


I think adding local functions is easier than randomly sprinkling in  
the type signatures.  It has a nice side-effect that your new code  
is often easier to read as well.


Good luck!
Jason


Thanks for the advice!

By using some auxiliary functions I can now compile an alternative  
version of the program. And although the resulting program is more  
clear, I'd still like to know if this can be achieved be adding only  
annotations to the original program. The reason for this is that, for  
performance reasons,  I depend on the case-of-case transformation  
removing every possible case construct. I already verified this is  
happening for the original program and I rather keep the code as is  
than browse through the generated core again :)


I must say that I also found this thread to be very helpful:

http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153

I'll make sure the wiki points to it.

For the record the resulting code is this:

{-# LANGUAGE GADTs, EmptyDataDecls #-}
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)

unWrap1 :: Impl S a -> Maybe a
unWrap1 (I1 m) = m

unWrap2 :: Impl M a -> [a]
unWrap2 (I2 m) = m

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


Bye
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


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: 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: 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: [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: 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


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: 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]))
 :: main: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]))
 :: main: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