Re: [Haskell-cafe] Simple matrix

2006-06-26 Thread Bjorn Lisper
Udo Stenzel:
Bjorn Lisper wrote:
 - your definition of fromInteger will behave strangely with the elementwise
   extended operations, like (+). 1 + [[1,2],[3,4]] will become
   [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this
   kind of overloading invariably have the second form of semantics.

Don't call an array a matrix.  If is named matrix, it should have
matrix multiplication, addition, and they should obey the expected laws.  

But you still have the problem with the overloading of constants in your
proposal. If you write 17 + a, where a is a matrix, what do people in
general expect it to be?

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


[Haskell-cafe] closures with side effects

2006-06-26 Thread dkarapet
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.

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


Re: [Haskell-cafe] Scoped data declarations

2006-06-26 Thread Sebastian Sylvan

On 6/23/06, Christophe Poucet [EMAIL PROTECTED] wrote:

Dear,

Yesterday, while discussing with Cale and SamB on I suddenly came up with
the crazy idea of scoped data declarations.  After some brief discussion to
check the validity, I finally came to the conclusion that they should be
feasible. In addition, I don't think that they would require a high amount
of changes in current compilers.

Basically if you have something like:

module Main where
foo = let data Foo = Foo deriving Show in Foo\
main :: IO ()
main = print foo

One can see this as having an extra hidden module that defines Foo but that
does not export it.  The only change that is then required is that while
compiling Foo, the hidden-ness of Foo must be removed.

For instance, if one were to load this into, say, ghci (this is fictive of
course):
# ghci Main.hs
 :t foo
foo :: Codeloc2.Foo

There were initially some objections to this, because it is no longer
feasible to actually write the type of the function foo.  But if one looks
at current GHC, this objection is already there:

module A(foo) where
data Foo = Foo deriving Show
foo = Foo

module Main where
import A
main = print foo

As Excedrin then pointed out, importing this Main into ghci, gives
foo :: Foo.Foo

And this notation can not be written in Main either, because Foo is hidden
in A.

Therefore, I would like to note that scoped data declarations are just like
hidden data-declarations with two extra requirements:
1) Generate source-location-based submodule names
2) Add an extra import rule for those hidden modules in the subexpressions
of where the data-declaration is being originally defined.

Comments are welcome, of course :)



I'm not sure I understand why this is something we need. Do you have
any examples where this would be useful?


/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Packages and modules

2006-06-26 Thread Simon Peyton-Jones
Simon and I have been thinking about fixing this, and we think we might
actually do so for GHC 6.6.  Your message provoked us to write up the
design.  It's here
http://hackage.haskell.org/trac/ghc/wiki/GhcPackages
Feedback welcome

It's worth reading the old threads; for example

http://www.haskell.org//pipermail/libraries/2005-August/004281.html
But there are many others!

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brian
| Hulley
| Sent: 25 June 2006 10:16
| To: Haskell-cafe
| Subject: [Haskell-cafe] Packages and modules
| 
| Hi -
| At the moment there is a problem in that two packages P and Q could
contain
| the same hierarchical module eg Data.Foo, and the only way for user
code to
| ensure the right Data.Foo is used is to ensure that packages P and Q
are
| searched in the right order.
| However suppose P and Q also contain another module with the same
name, eg
| Data.Bar.
| And suppose a user module wants to use Data.Foo from P but Data.Bar
from
| Q!!!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Functional progr., infinity, and the Universe

2006-06-26 Thread Nils Anders Danielsson
On Sat, 24 Jun 2006, Paul Hudak [EMAIL PROTECTED] wrote:

 Hmmm... never tried to write all this down in one place before, but I
 think this covers all cases:

 A partial list is one that ends in _|_.
 A total list is one that ends in [].
 A finite list is either partial or total.
 Any other list is infinite.

To confuse the picture more I'd like to point out that some use
different terminology:

* A strictly (spine-) partial list is one that ends in _|_.
* A (spine-) total list is one that ends in [] or doesn't end at all.
* A finite list is one that ends (with [] or _|_).
* An infinite list is one that doesn't end.

The two concepts (finite/infinite and total/strictly partial) are
orthogonal, and both partition the set of all lists.

And of course this generalises to other data types:

Finite: x is finite if it is contained in all ω-chains whose lubs are x.
Infinite: Not finite.
Total: No bottoms.
Strictly partial: Not total.
Partial: Total or strictly partial.

-- 
/NAD

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


Re: [Haskell-cafe] Scoped data declarations

2006-06-26 Thread Christophe Poucet
Hello,Well one specific example where this would be useful is for lambdabot and similar systems. Additionally this could be useful for experimenting in any interpreter such as hugs or ghci.Regards
On 6/26/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
On 6/23/06, Christophe Poucet [EMAIL PROTECTED] wrote: Dear, Yesterday, while discussing with Cale and SamB on I suddenly came up with
 the crazy idea of scoped data declarations.After some brief discussion to check the validity, I finally came to the conclusion that they should be feasible. In addition, I don't think that they would require a high amount
 of changes in current compilers. Basically if you have something like: module Main where foo = let data Foo = Foo deriving Show in Foo\ main :: IO () main = print foo
 One can see this as having an extra hidden module that defines Foo but that does not export it.The only change that is then required is that while compiling Foo, the hidden-ness of Foo must be removed.
 For instance, if one were to load this into, say, ghci (this is fictive of course): # ghci Main.hs  :t foo foo :: Codeloc2.Foo There were initially some objections to this, because it is no longer
 feasible to actually write the type of the function foo.But if one looks at current GHC, this objection is already there: module A(foo) where data Foo = Foo deriving Show foo = Foo
 module Main where import A main = print foo As Excedrin then pointed out, importing this Main into ghci, gives foo :: Foo.Foo And this notation can not be written in Main either, because Foo is hidden
 in A. Therefore, I would like to note that scoped data declarations are just like hidden data-declarations with two extra requirements: 1) Generate source-location-based submodule names
 2) Add an extra import rule for those hidden modules in the subexpressions of where the data-declaration is being originally defined. Comments are welcome, of course :)I'm not sure I understand why this is something we need. Do you have
any examples where this would be useful?/S--Sebastian Sylvan+46(0)736-818655UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple matrix

2006-06-26 Thread Atila Romero
Although there *could* be a fromInteger default behavior, there isn't a 
mathematical default behavior to c+A.
An even c*A it's hard to make work, because an identity matrix only 
works if it is a square matrix.

Example, if in c*A we make
A=
1 3
2 4
and
c=
c 0 0 0 ...
0 c 0 0 ...
0 0 c 0 ...
0 0 0 c ...
...
the result will have 2 lines and infinite columns. And if we make A*c 
the result will have 2 columns and infinite lines.
And since there's no way to tell to fromInteger which size we need for 
c, there's no way to make fromInteger works in a intuitive way.


So, I think it's better to just not use fromInteger at all, because it 
will work at some cases but will give wrong results at others.


Atila

Bjorn Lisper wrote:

Udo Stenzel:
  

Bjorn Lisper wrote:


- your definition of fromInteger will behave strangely with the elementwise
  extended operations, like (+). 1 + [[1,2],[3,4]] will become
  [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this
  kind of overloading invariably have the second form of semantics.
  

Don't call an array a matrix.  If is named matrix, it should have
matrix multiplication, addition, and they should obey the expected laws.  



But you still have the problem with the overloading of constants in your
proposal. If you write 17 + a, where a is a matrix, what do people in
general expect it to be?

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

  




___ 
Yahoo! Acesso Grátis - Internet rápida e grátis. Instale 
o discador agora! 
http://br.acesso.yahoo.com

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


Re: [Haskell-cafe] Scoped data declarations

2006-06-26 Thread lennart

Here's a different example:


foo = let data Foo = Foo in [Foo, Foo]


Since unfolding let bindings is always sematically equivalent
to the original expression this must be the same as


foo = [let data Foo = Foo, let data Foo = Foo]


How will you make that work?  A, you could outlaw unfolding
'data', but then you would have to outlaw unfolding any expression
with an embedded 'data'.  Very ugly.  Or B, you can go for
structural equality on types.  But that would be a radical departure
from Haskell.  (BTW, this kind of example is the very reason Cayenne
has structural equality on types by default.)

I don't think local (scoped) type definitions mesh at all well
with the Haskell design.  This work nicely now because type definitions
are only allowed at the top level, so they have a definition location.
Which means that name equality works.

 -- Lennart

Quoting Christophe Poucet [EMAIL PROTECTED]:


Dear,

Yesterday, while discussing with Cale and SamB on I suddenly came up with
the crazy idea of scoped data declarations.  After some brief discussion to
check the validity, I finally came to the conclusion that they should be
feasible. In addition, I don't think that they would require a high amount
of changes in current compilers.

Basically if you have something like:

module Main where
foo = let data Foo = Foo deriving Show in Foo\
main :: IO ()
main = print foo

One can see this as having an extra hidden module that defines Foo but that
does not export it.  The only change that is then required is that while
compiling Foo, the hidden-ness of Foo must be removed.

For instance, if one were to load this into, say, ghci (this is fictive of
course):
# ghci Main.hs

:t foo

foo :: Codeloc2.Foo

There were initially some objections to this, because it is no longer
feasible to actually write the type of the function foo.  But if one looks
at current GHC, this objection is already there:

module A(foo) where
data Foo = Foo deriving Show
foo = Foo

module Main where
import A
main = print foo

As Excedrin then pointed out, importing this Main into ghci, gives
foo :: Foo.Foo

And this notation can not be written in Main either, because Foo is hidden
in A.

Therefore, I would like to note that scoped data declarations are just like
hidden data-declarations with two extra requirements:
1) Generate source-location-based submodule names
2) Add an extra import rule for those hidden modules in the subexpressions
of where the data-declaration is being originally defined.

Comments are welcome, of course :)
Cheers!
Christophe (vincenz)




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


Re: [Haskell-cafe] closures with side effects

2006-06-26 Thread Jared Updike

 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.


Bulat what you mean by 'closure'?

Perhaps you are refering to something like the Accumlator generator in Lisp:

(defun mkacc (n)
  (lambda (i) (incf n i)))

or Scheme:

(define (mkacc n)
 (lambda (i)
   (set! n (+ n i))
 n))

(the term closure explained in footnote 6 in SICP here:
http://mitpress.mit.edu/sicp/full-text/book/book-Z-H-15.html#footnote_Temp_154:
A closure is an implementation technique for representing procedures
with free variables.)
?

In Haskell you can do this, but all side effects are made explicit and
can only be used within code marked with IO (in the IO monad):

import Data.IORef

mkAcc :: (Num a) = a - IO (a - IO a)
mkAcc n = do
 r - newIORef n
 return (\i - do
   modifyIORef r (+i)
   readIORef r)

(These examples are from http://www.paulgraham.com/accgen.html, by the way.)

On 6/26/06, dkarapet [EMAIL PROTECTED] 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.



in Haskell, expression may have a side
effect only if it has IO a return type. it is then whole point of
pure lazy language - evaluation of pure (not IO) expression can be
deferred until it's value really need and language guarantee that this
don't change anything (including lack of any side effects)
 Bulatmailto:[EMAIL PROTECTED]


The reason you need IO in the type that the compiler/type system
forces you to isolate side effects from pure code so all your pure
code stays pure. There is a good explanation here, under Pure
Functions:

http://en.wikipedia.org/wiki/Functional_Programming#Pure_functions

The reason purity is **enforced** is similar to the reason goto is
considered harmful: the belief is that the programmer receives great
benefits this tradeoff. In exchange for giving up side effects in
arbitrary places, the programmer gains freedom in knowing that all
pure functions are free from side-effects related bugs and her code is
easier to reason about mathematically.

My understanding is that Haskell's execution model is a lot more
involved than, say, Scheme, because pure code is more flexibly
refactored by the compiler and because the runtime evaluation strategy
for lazy evaluation is less obviously implemented. In this sense, if I
undertsand correctly, Haskell doesn't really use closures as an
implementation strategy (as defined above), if that is what your
question is refering to, and I'm not surprised that you don't find
interesting examples in Haskell, especially any involving side
effects.

 Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Packages and modules

2006-06-26 Thread Brian Hulley

Simon Peyton-Jones wrote:

Simon and I have been thinking about fixing this, and we think we
might actually do so for GHC 6.6.  Your message provoked us to write
up the design.  It's here
http://hackage.haskell.org/trac/ghc/wiki/GhcPackages
Feedback welcome

It's worth reading the old threads; for example

http://www.haskell.org//pipermail/libraries/2005-August/004281.html
But there are many others!


[from wiki]

 ghc -c -package P1 M1.hs
 ghc -c -package P2 M2.hs
 ...compile other modules...
 ghc -o app M1.o M2.o ... -package P1 -package P2


I don't think this solves the whole problem. Suppose M1 needs to use A.B.C 
from P1 *and* A.B.C from P2, then it would need to be compiled with P1 and 
P2, and there is no way (from the part of the proposal in this section 
alone) to distinguish between these packages from within M1 itself if we're 
still to be limited by the import A.B.C syntax. It only seems to address the 
problem of app needing to use M1 and M2 but not A.B.C directly where M1 only 
uses P1 and M2 only uses P2.


[from wiki]

import Packages.Gtk-1_3_4.Widget.Button


Allowing package aliases in the source could make this easier to type and 
avoid the necessity to capitalise and change underscores to dots:


  package gtk-1_3_4 as Gtk
or
  package gtk as Gtk -- use the current version of gtk
or
  if package directive is omitted an import Xyz/Mod is equivalent to:

package xyz as Xyz -- initial letter capitalised
import Xyz/Mod

and making the package part of the module id explicit prevents ambiguity 
problems (David House's idea) though at the expense of using more syntax ie


  import Widget.Button from Gtk
or
  import Gtk/Widget.Button -- instead of grafting

In all cases I think it would be an absolute disaster to allow modules to be 
imported without an explicit package id because this would defeat the whole 
purpose of having a simple per-package namespace for modules and wouldn't 
allow the reader of source to know which packages it's referring to.


Of course all code would need to be changed, but this could be accomplished 
by a conversion program which, given a list of packages and alias names, 
would just recursively traverse a source directory replacing imports and 
module exports by package directives and the fully qualified name of each 
module.


[from wiki]

Optional extra: grafting


ambiguity ( 
http://www.haskell.org//pipermail/haskell-cafe/2006-June/016317.html )
The use of / instead of . (or from) gives the advantage of grafting in terms 
of succinct qualified module names without this ambiguity.


Summary of my suggestions:
1) All module names would be of the form PackageAlias/ModId
2) package directives in the source bind aliases to actual packages
3) version number or package directive can be omitted when we are only
 interested in using the current version of that package
4) Package aliases have their own namespace

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] Simple matrix

2006-06-26 Thread Chris Kuklewicz

Mathematically the least surprising thing for matrices/arrays is

(fromInteger 0) * a{- n by m Matrix -} = 0{- n by m Matrix -}
(fromInteger 1) * a{- n by m Matrix -} = a{- n by m Matrix -}

Thus I would want (fromInteger 1) in this case to make an Identity {- n by n
Matrix -} matrix.  And then (fromInteger i) to be a diagonal n by n matrix of
all i's.

There is no reason to have infinite columns or rows from (fromInteger i), it
would only produce square diagonal matrices with i on the diagonal.

This has the very nice property that Num ops lift from integer to matrices:

For type Matrix: 2+3 == 5, 2*3 == 6,  2*(6-3) == (2*6)-(2*3) == (negate 6), etc.
and (negate (fromInteger 4)) == (fromInteger (negate 4))

Mathematically, I can't remember ever wanting to add x to every entry in a
matrix.   Remeber: (+) and (*) have type Matrix - Matrix - Matrix.  If you
want to add Int to Matrix then you should really define a new operator for that.

Note: For a purist Num should be commutative, which means only square Matrices
are allowed.

If you must use (*) and (+) in bizarre ways, then you could hide the Prelude and
 substitute your own Math type classes that know how to mix your types.

Atila Romero wrote:
Although there *could* be a fromInteger default behavior, there isn't a 
mathematical default behavior to c+A.
An even c*A it's hard to make work, because an identity matrix only 
works if it is a square matrix.

Example, if in c*A we make
A=
1 3
2 4
and
c=
c 0 0 0 ...
0 c 0 0 ...
0 0 c 0 ...
0 0 0 c ...
...
the result will have 2 lines and infinite columns. And if we make A*c 
the result will have 2 columns and infinite lines.
And since there's no way to tell to fromInteger which size we need for 
c, there's no way to make fromInteger works in a intuitive way.


So, I think it's better to just not use fromInteger at all, because it 
will work at some cases but will give wrong results at others.


Atila

Bjorn Lisper wrote:

Udo Stenzel:
 

Bjorn Lisper wrote:
   
- your definition of fromInteger will behave strangely with the 
elementwise

  extended operations, like (+). 1 + [[1,2],[3,4]] will become
  [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages 
supporting this

  kind of overloading invariably have the second form of semantics.
  

Don't call an array a matrix.  If is named matrix, it should have
matrix multiplication, addition, and they should obey the expected 
laws.  


But you still have the problem with the overloading of constants in your
proposal. If you write 17 + a, where a is a matrix, what do people in
general expect it to be?

Björn Lispe





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


[Haskell-cafe] how to write an haskell binding

2006-06-26 Thread minh thu

hi,

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

i'd like to know if there exist some general guidelines/information
about writing an haskell (or is it *a* haskell ?) binding for a c or a
c++ library.

i worry about :
* implementation tools : use tools like c2hs or others, or do that bare hands
* haskell idioms/usage : make good use of monads, type classes and
other haskell related things
* for c++, is it better to first write a c api for the c++ code before
writing the binding
* maybe advice about the c api knowing there will be haskell binding
* any thing i forgot

thanks a lot,
thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-06-26 Thread Brian Hulley

minh thu wrote:

about writing an haskell (or is it *a* haskell ?) binding for a c or a


It is defnitely *a* haskell. There is actually no word in English with a 
silent 'h', though this statement is unfortunately controversial and news to 
whoever wrote the spell checker used in many printed publications. Of course 
some particular dialects use different pronunciation like me 'otel room 'ad 
an 'askell 'mpiler in t' closet as well as tub 'n sink tha knows



c++ library.

i worry about :
* implementation tools : use tools like c2hs or others, or do that
bare hands


I'd recommend just using bare hands :-)


* haskell idioms/usage : make good use of monads, type classes and
other haskell related things


You might like to look at some existing libraries to get ideas ( 
http://www.haskell.org/haskellwiki/Libraries_and_tools )



* for c++, is it better to first write a c api for the c++ code before
writing the binding


Personnally, I write everything in C++, then have just one unit of plain C 
functions which are exported as the api, so the entire api is contained in 
one .h, .cpp (with extern C around the bindings), and .def file. I find it 
helpful to have a consistent naming convention, so if I have a static C++ 
class such as:


   class TimerFactory {
   static void Construct();
   static void Destruct();
   };

then the C api functions are given names like:

xxx_TimerConstruct()

where xxx is the name of the api.


* maybe advice about the c api knowing there will be haskell binding
* any thing i forgot


Perhaps to consider using the Haskell types for everything in the C code eg 
HsInt, HsWord16 etc instead of plain int, unsigned short etc, so that your 
Haskell code isn't messed up by having to use CInt instead of plain Int etc.


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] Packages and modules

2006-06-26 Thread Ian Lynagh
On Mon, Jun 26, 2006 at 04:20:16PM +0100, Brian Hulley wrote:
 
 I don't think this solves the whole problem. Suppose M1 needs to use A.B.C 
 from P1 *and* A.B.C from P2

For a simple example of a case where this might arise, suppose M1 is the
migration module for data (stored in a database, received over a
network, or some other such case) in P version 1's format to P version
2's format.

 [from wiki]
 import Packages.Gtk-1_3_4.Widget.Button

I'm also not a fan of this magic Packages.* hierarchy, nor the package
name change hoops it makes us jump through.

   package gtk-1_3_4 as Gtk
 or
   package gtk as Gtk -- use the current version of gtk
 or
   if package directive is omitted an import Xyz/Mod is equivalent to:
 
 package xyz as Xyz -- initial letter capitalised
 import Xyz/Mod

The package gtk as Gtk bit makes sense to me, but I'd expect then to
use Gtk.Foo.Bar for module Foo.Bar in package Gtk.

import gtk-1.3.4/Foo.Bar also makes sense, although personally I'd
prefer the syntax

from gtk-1.3.4 import Foo.Bar

where either from packagename is an optional prefix to current
import declaration syntax, or from packagename starts a block so we
can say

from gtk1
import Foo.Bar  as Gtk1.Foo.Bar
import Baz.Quux as Gtk1.Baz.Quux
from gtk2
import Foo.Bar  as Gtk2.Foo.Bar
import Baz.Quux as Gtk2.Baz.Quux

If we have gtk-1.something and gtk-2.something (rather than
gtk1-version and gtk2-version as above) then we'd probably instead want
the wiki's

-package gtk-2.0.1=Gtk2

which could be generated due to a .cabal build-depends of

gtk (= 2) as Gtk2


Thanks
Ian

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


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

2006-06-26 Thread Brian Hulley

Brian Hulley wrote:

minh thu wrote

* for c++, is it better to first write a c api for the c++ code before
writing the binding

[snip]
   class TimerFactory {
   static void Construct();
   static void Destruct();
   };

then the C api functions are given names like:

xxx_TimerConstruct()

Ooops!
xxx_TimerFactory_Construct()

I think I also missed the point of your question. In the program I'm writing 
sometimes I find I need to write the binding first and other times the C 
first and other times the C++ first since it is not always clear how to 
achieve a goal. One other thing to bear in mind is that foreign calls are 
extremely slow, so for example it is much faster to use the 
Foreign.Marshal.Array and Foreign.C.String functions to allocate and 
populate a temporary array with the contents of a list, and send the pointer 
to this array to C with one foreign call, than to send each element of the 
list with multiple foreign calls (eg to paste only 19K of text from the 
Windows clipboard to my app took over 1 minute!!! with individual foreign 
calls but a fraction of a second when I switched to passing a pointer and 
using peekCAString (ditto pokeArray0 for copy))


Regards, Brian. 


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


RE: [Haskell-cafe] Packages and modules

2006-06-26 Thread S. Alexander Jacobson

Simon,

We covered this extensively in the Cabal vs Haskell thread starting 
here: http://www.haskell.org//pipermail/libraries/2005-April/003607.html


You concluded it by saying on April 22:

  And this observation points towards a simpler solution: rather than
  invisibly pre-pend the package name, just get the programmer to do so.
  So package P exposes a module called P.M and package Q exposes Q.M.  All
  P's internal modules are called P.something, and similarly for Q.  (We
  rely on some social mechanism for allocating new package names, as now.)
  Now of course you can import P.M and Q.M in a single module.

  That would be simple.  It might be pretty inconvenient to say 'import
  Base.Data.List' rather than just 'import Data.List'.  But nothing forces
  you to do this -- and indeed we don't do it for the current 'base'
  package.  The point is that it's an easy way for a package author to
  ensure their package won't conflict with others.  If they choose not to
  avail themselves of it, it's more likely that their package will be
  unusable because of accidental name conflicts.

  Bottom line: the current story is pretty defensible.  I'm not sure that
  keeping names unique by implicitly using package-ids is worth the
  bother.

  http://www.haskell.org//pipermail/libraries/2005-April/003672.html

It seems like you are changing your position with this proposal?  Any 
reason for doing so?


-Alex-

__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com









On Mon, 26 Jun 2006, Simon Peyton-Jones wrote:


Simon and I have been thinking about fixing this, and we think we might
actually do so for GHC 6.6.  Your message provoked us to write up the
design.  It's here
http://hackage.haskell.org/trac/ghc/wiki/GhcPackages
Feedback welcome

It's worth reading the old threads; for example

http://www.haskell.org//pipermail/libraries/2005-August/004281.html
But there are many others!

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brian
| Hulley
| Sent: 25 June 2006 10:16
| To: Haskell-cafe
| Subject: [Haskell-cafe] Packages and modules
|
| Hi -
| At the moment there is a problem in that two packages P and Q could
contain
| the same hierarchical module eg Data.Foo, and the only way for user
code to
| ensure the right Data.Foo is used is to ensure that packages P and Q
are
| searched in the right order.
| However suppose P and Q also contain another module with the same
name, eg
| Data.Bar.
| And suppose a user module wants to use Data.Foo from P but Data.Bar
from
| Q!!!
___
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