Re: [Haskell-cafe] how to write an haskell binding

2006-06-28 Thread Fritz Ruehr

On Jun 27, 2006, at 10:35 AM, Brian Hulley wrote:


I suppose they are the exception that proves the rule... :-)


Seems like there's a real opportunity here for someone who works in the 
area of inference systems for error handling ... .


(Hmmm, pun-potential may not be the best way to pick a research topic, 
though.)


  --  Fritz

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


Re: [Haskell-cafe] Deducing Show for GADTs

2006-06-28 Thread Brandon Moore

Joel Björnson wrote:
Hi. I came a cross the following phenomena which, at least to me, occurs 
kind

of awkward. The code below :

data MyData a  where
  DC1 :: (Show a ) => a -> MyData a
 
instance Show (MyData a) where

  show (DC1 a ) = show a

yields the ghci error :  
'Could not deduce (Show a) from the context (Show (MyData a))'



...


I would also like to point out that adding a 'wrapper type' as in

data Wrap a = Wrap a

data MyData a  where
  DC1 :: (Show a ) => a -> MyData (Wrap a)

instance Show (MyData a ) where
  show (DC1 a ) = show a  


works fine. Even though 'Wrap' does not derive Show.

So, if anyone can give me some hints about the reason for this,  I will 
appreciate it :)


I think your example is tranlated to something like this, making an
new existential type for the "a" in Wrap a, and adding an equality 
constraint saying that the result type has to match a.

data MyData a
  forall b . (Show b, a = Wrap b) => DC1 a

That will work because b is an existential type, and
pattern matching on existentially typed constructors
lets you use the constraints (dictionaries) they carry around.

I'm not sure how GHC works now, but the paper "System F with 
TypeEquality Conversions" says GHC is eventually going to

change to an intermediate representation like this.

You can even put a constraint on the entire argument to the type
constructor, just as long as your constructor constraints that argument.

data Ex a where
  Ex :: Show (a,b) => (a,b) -> Ex (a,b)

It's more confusing when some parameters are constrained and some are 
not - it seems that a class constraint has to mention at least one

constrained type to work.

To finish your program, you could directly write
the encoding that uses type equality. This GADT
is evidence of type equality:

data Equal a b where Refl :: Equal a a

With it you can define

data MyData a where
  DC1 :: (Show b) => Equal a b -> b -> MyData a

and use values like this

instance Show (MyData a) where
  show (DC1 Refl x) = show x

It works:

*Main> show (DC1 Refl [1,2])
"[1,2]"

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


Re: [Haskell-cafe] Packages and modules

2006-06-28 Thread Brian Hulley

Marc Weber wrote:

I'm not sure on which mail of this thread I should append MHO.

What happens if two programmers "happen" to choose the same package
name? (Prepend the location on the filesystem? ;-)

If something like a package name is introduced I would prefer not
separating package and module name with a "." because you might then
even use the package name to point to a web address from where to load
code (source/ binary/ byte code??) from.. Then creating something like
Java applets would be more easy. We can't ignore this completely as
the world (or important parts eg Windows) will try to bring more
richness to internet applications/ the user.. They strive to
integrate web applications so that you as user can't see if you're
running a native or a
downloaded application... If you use eg "," as separator you can use
dots in the package name without hassle.


I think the package alias syntax would help here eg (non-existent url):

 package http://www.metamilk.com/packages/duma-1.0 as Duma

 import Duma/Text.Line  -- etc

I don't think the package name should ever be written directly into the 
import statement, because the package name needs to be able to use normal 
filename syntax but a component of a module identifier needs to conform to 
Haskell syntax because it could be used anywhere (*) eg


  let
x = Duma/Text.Line.take 5 y

Also, to clarify my reasons for wanting to make the package part of the 
module id syntactically distinct (by using eg / instead of .), the entire 
namespace of hierarchical modules is supposed to be internal to each 
package, and therefore any id of the form A.B.C belongs to this internal 
namespace and therefore must refer to an internal module. All modules in 
external packages have ids of the form PackageAlias/ModulePath so when you 
read the source you (and the compiler) can tell at a glance whether you're 
referring to an internal or external module.
An extra advantage of making the package alias part syntactically visible is 
that we could make package directives optional in the common case where we 
want to just use the latest version of a package that has a globally agreed 
name eg


import Fps/Data.ByteString  -- uses latest fps package

whereas if we just used import Fps.Data.ByteString the compiler would have 
no way to tell whether we're referring to an external package Fps or another 
module in our own package, and, imho, this would just simply be messy and 
inconsistent.


Also, although this requires changes to existing code, it should be possible 
to completely automate the change by using a simple conversion utility which 
knows about current packages, their prefixes, and what modules they contain 
(and therefore should be much less troublesome than the change from flat 
module namespace to hierarchical namespace).


(*) As an aside, it is a question to me whether identifiers in the body of a 
module should be allowed to be qualified with anything other than a module 
*alias*. Haskell98 just had flat modules, so the qualification was of the 
form A.val, whereas with the hierarchical extension you can use A.B.C.val 
etc. However does anyone actually ever use this rather than specifying an 
alias for A.B.C and using the alias to qualify val instead? This becomes a 
more urgent question if the lexical syntax for a module id needs to use 
another symbol such as /.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


[Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-28 Thread Simon Marlow

Ketil Malde wrote:


GHC puts the C library (-lafi) *before* Haskell library
(-lHSfmi-0.0) that refers to it.  Redoing the collect2 command but
moving -lafi last does, in fact, work.  Also, specifying
extra-libraries in the cabal package works, as long as they are
specified in the correct order.

>

The remaining question is whether inserting command line specified
libraries this early is a good choice.  Perhaps one option that
appears harmless is to specify it multiple times?


The idea is that a package should be self-contained; that is, it should 
include any external libraries that it depends on in its extra-libraries 
field.  If you follow this rule, then everything should work.


Specifying a library multiple times might work, but it would slow down 
linking, so I'd like to avoid it if possible.


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


Re: [Haskell-cafe] Packages and modules

2006-06-28 Thread Marc Weber

I'm not sure on which mail of this thread I should append MHO.

What happens if two programmers "happen" to choose the same package
name? (Prepend the location on the filesystem? ;-)

If something like a package name is introduced I would prefer not
separating package and module name with a "." because you might then
even use the package name to point to a web address from where to load
code (source/ binary/ byte code??) from.. Then creating something like
Java applets would be more easy. We can't ignore this completely as the
world (or important parts eg Windows) will try to bring more richness to
internet applications/ the user.. They strive to integrate web applications 
so that you as user can't see if you're running a native or a
downloaded application... If you use eg "," as separator you can use dots
in the package name without hassle.

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


Re: [Haskell-cafe] Are FunPtr's stable? (was: how to write an haskellbinding)

2006-06-28 Thread Brian Hulley

Simon Peyton-Jones wrote:

Can I urge any of you who learn stuff that "I wish I'd know at the
beginning" to add that information to GHC's FFI Wiki page?
http://haskell.org/haskellwiki/GHC/Using_the_FFI
Anyone can add to this material, and it's extremely helpful to jot
down what you've learned while it's fresh in your mind.

The current page is largely about C++ bindings, but that's only
because that's what the last contributor was interested in.  Feel
free to re-structure it, add  new sections etc.


I've added a section on unsafe/safe and a "Random Questions" section which 
will hopefully make it easier to quickly add useful things that spring to 
mind for anyone who doesn't want to do re-structuring - at the moment it 
just has the answer to "Are FunPtr's stable?"


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Deducing Show for GADTs

2006-06-28 Thread Niklas Broberg

On 6/28/06, David Roundy <[EMAIL PROTECTED]> wrote:

On Wed, Jun 28, 2006 at 11:52:51AM +0200, Joel Bjrnson wrote:
> Hi. I came a cross the following phenomena which, at least to me,
> occurs kind of awkward. The code below:
>
> data MyData a  where
>  DC1 :: (Show a ) => a -> MyData a

GADTs don't yet work right with classes.  :( The above, however,
doesn't need to be expressed as a GADT, I believe you can write
something like:

data MyData a = (forall a. Show a) => DC1 a

which (this is untested) should do what you want.


Only if "what he wants" is something that type checks, but doesn't do
the same thing. ;-)
In Joel's definition of MyData, values constructed with DC1 applied to
a value of type b will have type MyData b. In your definition they
will have type MyData a, for any a. In other words, your definition
would be identical to the GADT

data MyData a where
DC1 :: forall a b . (Show b) => b -> MyData a


As to Joel's question, this seems really really weird. In particular
since adding the completely useless wrapper type solves the problem.
In fact, giving DC1 any return type other than MyData a solves the
problem. This has to be a bug of some sort.

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


Re: [Haskell-cafe] Deducing Show for GADTs

2006-06-28 Thread David Roundy
On Wed, Jun 28, 2006 at 11:52:51AM +0200, Joel Bjrnson wrote:
> Hi. I came a cross the following phenomena which, at least to me,
> occurs kind of awkward. The code below:
> 
> data MyData a  where
>  DC1 :: (Show a ) => a -> MyData a

GADTs don't yet work right with classes.  :( The above, however,
doesn't need to be expressed as a GADT, I believe you can write
something like:

data MyData a = (forall a. Show a) => DC1 a

which (this is untested) should do what you want.
-- 
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Deducing Show for GADTs

2006-06-28 Thread Joel Björnson
Hi. I came a cross the following phenomena which, at least to me, occurs kind
of awkward. The code below :

data MyData a  where
  DC1 :: (Show a ) => a -> MyData a
  
instance Show (MyData a) where
  show (DC1 a ) = show a

yields the ghci error :  
'Could not deduce (Show a) from the context (Show (MyData a))'

Adding a Show restriction for the instantiation as in

instance Show a => Show (MyData a ) where
  show (DC1 a ) = show a

makes the type checker happy. However,  this means that all
parametrised values over MyData must have a Show type which isn't
necessarily what one wants.

I would also like to point out that adding a 'wrapper type' as in

data Wrap a = Wrap a

data MyData a  where
  DC1 :: (Show a ) => a -> MyData (Wrap a)

instance Show (MyData a ) where
  show (DC1 a ) = show a  

works fine. Even though 'Wrap' does not derive Show.

So, if anyone can give me some hints about the reason for this,  I will appreciate it :)

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


Re: [Haskell-cafe] Re: how to write an haskell binding

2006-06-28 Thread minh thu

old me>hopefully (well, i liked the discussions) this message will not spawn
old me>so much messages :)



Still everyone will be pleased to know that I won't post any more about this
subject now that the third true silent 'h' has been found :-)

Best regards, Brian.


my apologies ;)
thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] closures with side effects

2006-06-28 Thread tpledger
dkarapet wrote:
> I have been trying to understand closures
> in haskell and how they relate
> to side effects. I have been looking
> around but all I find are trivial
> examples with no side effects. Please let
> me know if you know of any examples.

The side effects occur in the context that causes the
closure to be entered.

Here's a nigh-trivial example.

myClosure :: IO ()
myClosure = putStrLn "Hello, world."
main  = myClosure >> myClosure

When myClosure is defined, the side effect doesn't occur
yet.  We just have a *definition* of an IO action that
hasn't yet been bound into the program's sequence of
actions.

When main binds myClosure into the program's sequence of
actions (twice), the side effect occurs (twice).  Depending
on the implementation of putStrLn, it may be faster the
second time because the same closure has been entered
before.

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


[Haskell-cafe] Re: Comments from Brent Fulgham on Haskell and the shootout

2006-06-28 Thread Simon Marlow

John Meacham wrote:

On Tue, Jun 27, 2006 at 02:58:05PM +0100, Simon Marlow wrote:


.. (and jhc already generates native C code, so it will have at least
one substantial advantage over GHC) ...


Compiling via C is a dead end.  We realised this about 5 years ago, and
yet we still haven't managed to shake off the C backend from GHC, but I
remain hopeful that one day we will.  /me heads for the cafe...


Out of curiosity, compiling via C as opposed to what? c--? Parrot? JVM?


C-- ultimately, but in the meantime GHC's built in native-code 
generator.  Our NCG is quite reasonable, and we plan to push it forward 
in various ways to improve the generated code.  There's a wiki page with 
some ideas:


  http://hackage.haskell.org/trac/ghc/wiki/BackEndNotes

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


RE: [Haskell-cafe] Are FunPtr's stable? (was: how to write an haskellbinding)

2006-06-28 Thread Simon Peyton-Jones
Can I urge any of you who learn stuff that "I wish I'd know at the
beginning" to add that information to GHC's FFI Wiki page?
http://haskell.org/haskellwiki/GHC/Using_the_FFI
Anyone can add to this material, and it's extremely helpful to jot down
what you've learned while it's fresh in your mind.

The current page is largely about C++ bindings, but that's only because
that's what the last contributor was interested in.  Feel free to
re-structure it, add  new sections etc.

Simon


| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brian
| Hulley
| Sent: 27 June 2006 22:56
| To: Jared Updike
| Cc: Haskell-cafe
| Subject: Re: [Haskell-cafe] Are FunPtr's stable? (was: how to write an
haskellbinding)
| 
| Jared Updike wrote:
| >> On a related note, as I was reading the FFI specification again, I
| >> can't find any mention of whether or not FunPtr's are stable with
| >> respect to garbage collection. I'm assuming they are but am I
| >> correct?
| >
| > Did you read Tackling the Awkward Squad? I think Section 6 (esp.
| > 6.4.2) addresses this:
| >   http://research.microsoft.com/~simonpj/papers/marktoberdorf/
| 
| Thanks - from 6.4.2:
| 
|"Incidentally, the alert reader may have noticed
| that foreign import "wrapper", described
| in Section 6.2, must use stable pointers."
| 
| Perhaps a future revision of the FFI document could also include a
direct
| confirmation like this?
| 
| Best regards, Brian.
| 
| --
| Logic empowers us and Love gives us purpose.
| Yet still phantoms restless for eras long past,
| congealed in the present in unthought forms,
| strive mightily unseen to destroy us.
| 
| http://www.metamilk.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