Re: not naming modules Main

2001-11-16 Thread Max A . K .

Strange, I'm not annoyed by this at all though I supposed to
be. First I make module alone, and have 'module Main' and
'main' function there, then I use it in project, and change
the name to whichever I want and rename or delete the 'main'
function.

Anyway there can be a workaround (I didn't try it):

= Module.hs
#ifdef Module_MAIN
module Main where
#else
module Module where
#endif

<..>

#ifdef Module_MAIN
main = test_main
#endif

<..>
= end

= Makefile
<..>
GHC_MAIN_MODULES=Module1 Module2
<..>
GHC_OPTS+=-cpp $(GHC_MAIN_MODULES:%=-D%_MAIN)
<..>
= end

(that's GNU make, I don't know if this works in other. If
don't, just add the options -D_MAIN directly)

Then the only thing you have to change is the first
mentioned line in the Makefile.

Max.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: How do I write the type of 'inverse'?

2001-11-16 Thread G Michael Sawka

<[EMAIL PROTECTED]> writes:
> I have a class whose instances can extract a field of type a.
> Is there a way of referring to that type 'a' in the signatures
> of functions that use the class?   Sigh!  That wasn't very clear. 
>  
> I'll try explaining via example:
> I am trying to define a `Pairable' class, which is an abstraction
> of all kinds of pairs:  (a,b),   Pair a b,  etc.
> 
> > class Ord p => Pairable p where
> > is_pair  :: p -> Bool
> > pair_fst :: Ord a => p -> a-- Precondition: is_pair
> > pair_snd :: Ord b => p -> b-- Precondition: is_pair
> > make_pair:: (Ord a, Ord b) => a -> b -> p
> 
> > instance (Ord a, Ord b) => Pairable (a,b) where
> > is_pair  (a,b) = True
> > pair_fst (a,b) = a
> > pair_snd (a,b) = b
> > make_pair a b  = (a,b)

Haskell's class system is extremely confusing -- 
  although beautiful + very powerful :)

I think what you want, is a class and an instance declaration that
looks like this:

class Pairable p where
  is_pair :: p a b -> Bool
  pair_fst :: p a b -> a
  pair_snd :: p a b -> b
  make_pair :: a -> b -> p a b

instance Pairable (,) where
  is_pair (_,_) = True
  pair_fst (a,_) = a
  pair_snd (_,b) = b
  make_pair a b = (a,b)

Now, what makes this confusing, at least to me, is the fact that in
the class decl you can say "p a b -> a".  "p" in this case is a
function over type-variables, not just a normal run-of-the-mill type
variable (the Monad class uses this same principle).  In more
technical terms, "p" has a "kind" of * -> * -> *, whereas all "normal"
values have kind "*".  This means that we can create an instance only
out of a constructor that has "kind" * -> * -> *, of which (,) (the
pair constructor) is one of.  The idea is that "p a b" is "p" with "a"
and "b" applied to it!  So in the instance the types become:

  is_pair :: (,) a b -> Bool
  pair_fst :: (,) a b -> a
  ... etc.

Everything works out.  This compiles, and you can do neat tricks like:

  main = putStrLn (pair_snd (1,"hello world"))

Just be careful with the function "make_pair".  If you try to use it
in a pain, vanilla context you will get a type ambiguity:

  main = putStrLn (pair_snd (make_pair 1, "foo"))

  Ambiguous type variable(s) `p' in the constraint `Pairable p'
arising from use of `make_pair' at tf.hs:21
In the first argument of `pair_snd', namely
`((make_pair 1 "foo"))'
In the first argument of `putStrLn', namely
`(pair_snd ((make_pair 1 "foo")))'

The problem is that the compiler does not know which instance of pair
to use for make_pair!  If I also declared:

data Foo a b = Foo a b
instance Pairable Foo where
  is_pair Foo a b = True
  pair_fst Foo a _ = a
  pair_snd Foo _ b = b
  make_pair a b = Foo a b

it would be impossible to know which instance to use in the example.
should it construct a "Foo" and then take pair_snd, or should it
construct a Pair and then take pair_snd?  (The same problems exist
with the "return" of the Monad class).  The solution is just to show
the compiler which one you want:

main = putStrLn (pair_snd ((make_pair 1 "hello!") :: (Int,[Char])))

I hope this helps some :)
If you're still confused about values with kinds other than "*", take
a look at the Monad class or the language reference.  Very cool stuff.

 -mike.







_
Do You Yahoo!?
Get your free @yahoo.com address at http://mail.yahoo.com


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: not naming modules Main

2001-11-16 Thread Mark Carroll

On Fri, 16 Nov 2001, Iavor S. Diatchki wrote:
(snip)
> having said all that, there seems to be a bug in ghc (or perhaps
> an implementation restriction), which requires that "main" is defined
> in the module "Main".  the only other haskell implementation i have
(snip)

Actually, what would be nice in ghci is to be able to :load modules that
don't have "main" defined. Followups should probably go to one of the GHC
lists though, I guess.

-- Mark


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: not naming modules Main

2001-11-16 Thread Iavor S. Diatchki

hi,

the haskell report says that a program should contain
a module called "Main", which should export a function called "main"
of type IO(). 

there is no requiremnt however that the function "main" is defined
in the module "Main", it could for example be imported from somewhere.

so in your situation you could have a module "Main", which just imports
the module where the "main" function is defined (don't forget
to also export "main") and than you won't need to rename your module
all the time.

having said all that, there seems to be a bug in ghc (or perhaps
an implementation restriction), which requires that "main" is defined
in the module "Main".  the only other haskell implementation i have
access to is hugs, and in this respect it behaves correctly, but alas
it has other issues with the module system.  

bye
iavor


On Fri, Nov 16, 2001 at 06:34:14PM +, Hal Daume wrote:
> I'm really frustrated that modules that you want to compile to
> executables have to be named Main.  I often have a module with a main
> method that I use for testing or whatever (perhaps I want the gained
> speed of an executable) but is, for the most part, a module I import
> into others.  I end up having to constantly change the module name
> whenever I want to compile it and I find this terribly frustrating.
> 
> Is there any reason you can't just compile things that simply export a
> main method with the proper type?  Is this a ghc specific thing or
> does nhc also have this restriction?  Any chance ghc will change its
> policy on this?
> 
>  - Hal
> 
> -- 
> Hal Daume III
> 
>  "Computer science is no more about computers| [EMAIL PROTECTED]
>   than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell

-- 
==
| Iavor S. Diatchki, Ph.D. student   | 
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



not naming modules Main

2001-11-16 Thread Hal Daume

I'm really frustrated that modules that you want to compile to
executables have to be named Main.  I often have a module with a main
method that I use for testing or whatever (perhaps I want the gained
speed of an executable) but is, for the most part, a module I import
into others.  I end up having to constantly change the module name
whenever I want to compile it and I find this terribly frustrating.

Is there any reason you can't just compile things that simply export a
main method with the proper type?  Is this a ghc specific thing or
does nhc also have this restriction?  Any chance ghc will change its
policy on this?

 - Hal

-- 
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: How do I write the type of 'inverse'?

2001-11-16 Thread John Hughes


I'll try explaining via example:
I am trying to define a `Pairable' class, which is an abstraction
of all kinds of pairs:  (a,b),   Pair a b,  etc.

> class Ord p => Pairable p where
> is_pair  :: p -> Bool
> pair_fst :: Ord a => p -> a-- Precondition: is_pair
> pair_snd :: Ord b => p -> b-- Precondition: is_pair
> make_pair:: (Ord a, Ord b) => a -> b -> p

> instance (Ord a, Ord b) => Pairable (a,b) where
> is_pair  (a,b) = True
> pair_fst (a,b) = a
> pair_snd (a,b) = b
> make_pair a b  = (a,b)

Funny: I get an error from just this instance declaration! The problem is that
the class definition means that pair_fst is *polymorphic* in a, that is, it
should be able to return *any* type in class Ord. Of course, your instance
can't: it can only return the type of the first component. Thus the instance
is not general enough.

The solution (using hugs -98 or ghc -fglasgow-exts, because this is an
extension to Haskell 98) is to use a multi-parameter class:

> class (Ord p, Ord a, Ord b) => Pairable p a b where
> is_pair  :: p -> Bool
> pair_fst :: p -> a-- Precondition: is_pair
> pair_snd :: p -> b-- Precondition: is_pair
> make_pair:: a -> b -> p

> instance Pairable (a,b) a b where
> is_pair  (a,b) = True
> pair_fst (a,b) = a
> pair_snd (a,b) = b
> make_pair a b  = (a,b)

This is what you were after here:

It seems like I want to pass the component types into the
class definition somehow:   class Pairable (p a b)

Now the instances of pair_fst and pair_snd are for a *particular* component
type, and all is fine.

This works, but tends to lead to many ambiguities, since the type-checker
cannot know that there isn't an instance

   instance Pairable (a,b) b a where
 ...
 pair_fst (a,b) = b
 ...

also. That means it cannot infer, when it sees pair_fst (a,b), that the result
is of the same type as a.

You can avoid the ambiguities too, by adding a *functional dependency* to the
class definition. In this case, the type of the "pair" presumably determines
the type of each component, so you could write

> class (Ord p, Ord a, Ord b) => Pairable p a b | p->a, p->b where
> is_pair  :: p -> Bool
> pair_fst :: p -> a-- Precondition: is_pair
> pair_snd :: p -> b-- Precondition: is_pair
> make_pair:: a -> b -> p

to declare that for each type p, there can only be one type a and one type
b. This permits the type-checker to infer the result type of pair_fst and
pair_snd from the argument type.

Of course, if you actually *want* to declare pairs with reversed components as
"pair-like" also, then you can't do this: you have to put up with the
ambiguities (and add types by hand to resolve them) because the ambiguities
are really there.

John


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



How do I write the type of 'inverse'?

2001-11-16 Thread marku

I have a class whose instances can extract a field of type a.
Is there a way of referring to that type 'a' in the signatures
of functions that use the class?   Sigh!  That wasn't very clear. 
 
I'll try explaining via example:
I am trying to define a `Pairable' class, which is an abstraction
of all kinds of pairs:  (a,b),   Pair a b,  etc.

> class Ord p => Pairable p where
> is_pair  :: p -> Bool
> pair_fst :: Ord a => p -> a-- Precondition: is_pair
> pair_snd :: Ord b => p -> b-- Precondition: is_pair
> make_pair:: (Ord a, Ord b) => a -> b -> p

> instance (Ord a, Ord b) => Pairable (a,b) where
> is_pair  (a,b) = True
> pair_fst (a,b) = a
> pair_snd (a,b) = b
> make_pair a b  = (a,b)

I then want to define a `Relation' to be a set of Pairable values.
 
> newtype Pairable p => Reln p = Reln [p] 

This works okay for many of my relation operations.
But I run into an interesting problem with `inverse'
(which swaps the components of each pair).

inverse   :: (Pairable p, Pairable p2) => Reln p -> Reln p2
inverse rs = Reln[make_pair (pair_snd p) (pair_fst p) | p <- reln2list rs]

Hugs gives the error:

ERROR /home/utting/jaza/tmp.hs:19 - Cannot justify constraints in explicitly
typed binding
*** Expression: inverse
*** Type  : (Pairable a, Pairable b) => Reln a -> Reln b
*** Given context : (Pairable a, Pairable b)
*** Constraints   : (Ord c, Ord d)

which I can understand.

BUT, I cannot see any way of naming the `component types', c and d,
in the signature of inverse!

It seems like I want to pass the component types into the
class definition somehow:   class Pairable (p a b)

How does one normally get around this kind of problem?

Thanks.
Mark Utting
Professeur Invité
Laboratoire d'Informatique de l'Université de Franch-Comté
16, route de Gray - 25000 Besançon, cedex, FRANCE
Tel:  (33) 3 81 66 20 69
Fax:  (33) 3 81 66 64 50
Email:  [EMAIL PROTECTED]



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: GHC installation

2001-11-16 Thread Simon Peyton-Jones

You don't say which version of GHC...

GHC 5.02.1 (which I advise you to use) installs in 
c:/ghc/ghc-5.02.1

The installer doesn't give you a way to change this.  (It should,
but we havn't found out how yet.)  But once you have put it there
you can move it if you want.

(Best to mail glasgow-haskell-users rather than the entire Haskell
mailing list with GHC-related questions.)

Simon

| -Original Message-
| From: Jerzy Karczmarczuk [mailto:[EMAIL PROTECTED]] 
| Sent: 16 November 2001 11:56
| Cc: [EMAIL PROTECTED]
| Subject: GHC installation
| 
| 
| I might be dead wrong, in that case I apologize...
| 
| I just took the Windows installer and tried to put GHC etc. 
| on my laptop. I suspect that the installer absolutely wants 
| to put the stuff in Program Files and doesn't give the user 
| the opportunity to install it on another disk. Anyway, I have 
| plenty of space on another partition, but the installer 
| complains that it lacks space.
| 
| Any suggestions, please?
| 
| 
| Jerzy Karczmarczuk
| Caen, France
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: how strict is Array.array?

2001-11-16 Thread Simon Peyton-Jones

Well, it's clearly a design choice.  But in general laziness does not
come for
free.  The choice made by the Haskell designers was that the 'array'
function
can consume and explore all its input before producing any result.   It
just
give more scope to the implementor.   Nothing too deep.

Simon

| -Original Message-
| From: Johannes Waldmann [mailto:[EMAIL PROTECTED]] 
| Sent: 12 November 2001 20:29
| To: [EMAIL PROTECTED]
| Subject: how strict is Array.array?
| 
| 
| I was surprised to note that
| 
| bounds $ array (0,1) undefined
| 
| is undefined ( rather than (0,1) ) - why is this?
| 
| just curious,
| -- 
| -- Johannes Waldmann  
| http://www.informatik.uni-leipzig.de/~joe/ --
| -- 
| [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/252 --
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Julian Seward (Intl Vendor)


I suspect you're both right.  I seem to remember that it used
to be the way Keith says, but was relatively recently changed to
be the way Robert says.

J

| > > But, to answer your emmediate question:
| > > 
| > > ZMZM = []  - The list Nil constructor
| > > Z1T = ( )  - The 1-tuple constructor
| > 
| > IIRC, the "1" is the number of commas, so Z1T is the *pair* 
| > constructor.
| 
| The comments in OccName.lhs say: 
| 
|   [copying direct from the file]
| 
|   Before  After
|   --
|   TrakTrak
|   foo_wib foozuwib
|   >   zg
|   >1  zg1
|   foo#foozh
|   foo##   foozhzh
|   foo##1  foozhzh1
|   fooZfooZZ   
|   :+  ZCzp
|   ()  Z0T 0-tuple
|   ()  Z5T 5-tuple  
|   (# #)   Z1H unboxed 1-tuple (note the space)
|   (##)Z5H unboxed 5-tuple
|   (NB: There is no Z1T nor Z0H.)
| 
| Which, interestingly, says that there is no Z1T, despite 
| sengan having 
| supposedly found one.
| 
| However it also suggests that, if Z1T did exist, then it 
| would be a 1-tuple.
| 
| 
| The code itself backs this up and suggests that the number is 
| the number of 
| commas + 1:
| 
| maybe_tuple "()" = Just("Z0T")
| maybe_tuple ('(' : cs)   = case count_commas (0::Int) cs of
|(n, ')' : cs) -> Just ('Z' : 
| shows (n+1) "T")
|other -> Nothing
| maybe_tuple other  = Nothing
| 
| 
| Just in case anyone wasn't confused yet :-)
| 
| 
| 
| -Rob
| 
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Robert Ennals

> > But, to answer your emmediate question:
> > 
> > ZMZM = []  - The list Nil constructor
> > Z1T = ( )  - The 1-tuple constructor
> 
> IIRC, the "1" is the number of commas, so Z1T is the *pair* constructor.

The comments in OccName.lhs say: 

[copying direct from the file]

Before  After
--
TrakTrak
foo_wib foozuwib
>   zg
>1  zg1
foo#foozh
foo##   foozhzh
foo##1  foozhzh1
fooZfooZZ   
:+  ZCzp
()  Z0T 0-tuple
()  Z5T 5-tuple  
(# #)   Z1H unboxed 1-tuple (note the space)
(##)Z5H unboxed 5-tuple
(NB: There is no Z1T nor Z0H.)

Which, interestingly, says that there is no Z1T, despite sengan having 
supposedly found one.

However it also suggests that, if Z1T did exist, then it would be a 1-tuple.


The code itself backs this up and suggests that the number is the number of 
commas + 1:

maybe_tuple "()" = Just("Z0T")
maybe_tuple ('(' : cs)   = case count_commas (0::Int) cs of
 (n, ')' : cs) -> Just ('Z' : shows (n+1) "T")
 other -> Nothing
maybe_tuple other= Nothing


Just in case anyone wasn't confused yet :-)



-Rob


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



GHC installation

2001-11-16 Thread Jerzy Karczmarczuk

I might be dead wrong, in that case I apologize...

I just took the Windows installer and tried to put GHC etc. on my laptop.
I suspect that the installer absolutely wants to put the stuff in Program Files
and doesn't give the user the opportunity to install it on another disk.
Anyway, I have plenty of space on another partition, but the installer complains
that it lacks space.

Any suggestions, please?


Jerzy Karczmarczuk
Caen, France

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Keith Wansbrough

> But, to answer your emmediate question:
> 
> ZMZM = []  - The list Nil constructor
> Z1T = ( )  - The 1-tuple constructor

IIRC, the "1" is the number of commas, so Z1T is the *pair* constructor.

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



CFP: EuroPar 20002

2001-11-16 Thread Kevin Hammond

[Apologies for any duplication.   Please can you distribute to those who
might be interested...

I am global chair of topic 10,  Parallel Programming: Models, Methods and
Programming
Languages, and would welcome submissions from the Haskell community.

Kevin]

 * Euro-Par 2002 - http://europar.upb.de **


  Paderborn, Germany
  August 27-30, 2002


  First Call for Papers

Euro-Par is well established as the premier European conference on
all aspects of parallel computing.  Previous events were held in
Stockholm (1995), Lyon (1996), Passau (1997), Southampton (1998),
Toulouse (1999), Munich (2000), and Manchester (2001). The conference
normally attracts more than 300 participants coming from universities,
research centres, and industry.

The major themes of the conference can be divided into the broad
categories of hardware, software, algorithms and applications.
In common with previous years, Euro-Par 2002 will be organised as
a number of parallel sessions on the following topics for which
papers are solicited:

   1. Support Tools and Environments
   2. Performance Evaluation, Analysis and Optimization
   3. Scheduling and Load Balancing
   4. Compilers for High Performance
  (compilation and parallelization techniques)
   5. Parallel and Distributed Databases, Data-Mining and
  Knowledge Discovery
   6. Complexity Theory and Algorithms
   7. Applications of High-Performance Computers
   8. Parallel Computer Architecture and Instruction Level
  Parallelism
   9. Distributed Systems and Algorithms
  10. Parallel Programming: Models, Methods and Programming
  Languages
  11. Numerical Algorithms
  12. Routing and Communication in Interconnection Networks
  13. Architectures and Algorithms for Multimedia Applications
  14. Meta- and Grid-Computing
  15. Discrete Optimization
  16. Mobile Computing, Mobile Networks

Further details for each topic can be found at:

  http://europar.upb.de/

Authors are requested to use the electronic form on the web site
to submit their paper to the topic they judge most appropriate.

All accepted papers will be available at the conference in the
proceedings published by Springer-Verlag in the LNCS series.

The conference will also feature invited talks and tutorials.
Further information will appear on the website as it becomes
available.

--

Key Dates: February 8th, 2002  Final date for submissions
   April 30th, 2002Acceptance notified
   May 31st, 2002  Deadline for final papers
   June 30th, 2002 Author registration deadline
   June 30th, 2002 Early registration deadline

   August 27th-30th, 2002  Euro-Par 2002 in Paderborn


Apologies for multiple copies of this call for papers!
If you would like to be removed from this mailing list or have
received multiple copies and you would like some address(es) to
be removed please email [EMAIL PROTECTED]



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Robert Ennals

> I searched on google, but had no luck.
> My program is an implementation of 
> http://www-aig.jpl.nasa.gov/public/home/gat/lisp-study.html
> in haskell, and the dictionary read in is rather large
> (900Kb) so I assume most of the space should be [[Char]]

Zxxx is the way GHC encodes operator names into something friendly to C.

For a description of the translation, it is probably easiest to look at the relevent 
GHC source code, available online as:

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/basicTypes/OccName.lhs?rev=1.44&content-type=text/x-cvsweb-markup

This URL will probably get broken up by my mailer. The file is basicTypes/OccName.lhs


But, to answer your emmediate question:

ZMZM = []  - The list Nil constructor
Z1T = ( )  - The 1-tuple constructor


-Rob


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell