Questions concerning hierarchical module system

2002-04-17 Thread Wolfgang Jeltsch

Hi,
I have some questions regarding the hierarchical module system now 
implemented in Hugs as well as in GHC.
Currently it is possible to have a module A1.A2. ... .Am and a module A1.A2. 
... .Am. ... .An (n > m) at the same time. The first one's source code would 
be in file /A1/A2/ ... /Am.hs and the second one's in file 
/A1/A2/ ... /Am/ ... /An.hs. So there would be both a Am.hs file and a 
Am directory in the same directory. A1.A2. ... .Am would have two meanings: a 
module and a "module container". Hugs and GHC doesn't seem to have problems 
with this. But I want to know if I can rely on this behaviour still beeing 
present in future implementations and if this kind of module organisation is 
maybe considered bad practice.

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



Haskell Web Publisher --- help wanted

2002-04-17 Thread Wolfgang Jeltsch

Hello Haskell freaks,
I'm developing some software which I call the "Haskell Web Publisher". This 
software shall allow the implementation of websites in Haskell and will 
consist mainly of Haskell modules providing the necessary types and 
variables. By using HWP, website implementors shall be able to write clear 
and problem-oriented website implementations. In addition, many errors (e.g. 
"broken links") shall be prevented by compiler checks. This shall be achieved 
by using Haskell's type system appropriately.
I have written some kind of paper about the basic ideas which can, at the 
moment, be downloaded by using the following URI:
http://www.wolfgang.jeltsch.net/
convenient-website-implementation-with-haskell.pdf
I decided to exclude all the code from HWP which may also be useful for other 
software This code will form a separate library called Seaweed.
During the last 2 1/2 years I worked on the described kind of software. Last 
year I decided to revise some of the code and to rewrite the rest of it. In 
conjunction with this I made the split into Seaweed and HWP and began hosting 
these projects on Sourceforge (now Sourceforge.net). The respective URI are 
these:
http://sourceforge.net/projects/seaweed/
http://sourceforge.net/projects/hwp/
Because I didn't have the time, I didn't rewrite the existing HWP stuff and 
didn't write what is missing of HWP until now. I only worked on the Seaweed 
part. Some of the resulting code is already in the CVS repository, and some 
code is on my harddisk and will, hopefully, be checked in during April/May. 
If somebody should be interested, I can also send him/her the code from 
before the revision/rewrite phase which covers some of the more interesting 
stuff of HWP, namely code for realising the compiler checks mentioned above.
Now let me come to the aim of this e-mail. I'm looking for people who are 
interested in helping me realising HWP and Seaweed. Because I develop these 
things only in my free time, finishing them is far away if it's only me who 
is working on them. So if someone of you is interested in taking part in the 
development process, please, please write me! Thank you in advance!
Okay, I will finish now and I hope for reply.

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



Re: data structure question

2002-04-17 Thread John Meacham

perhaps you can modify 'gperf' (the gnu perfect hash function generator) to
output haskell rather than c. i actually looked into this before, it
should not be too tough as gperf always generates a generic polynomial
and just the coefficients are different for diffirente input, it would
be pretty easy to awk those out and reimplement the generic function in
haskell. alternativly you could roll your own.. some useful information
is here http://burtleburtle.net/bob/hash/perfect.html and around.
John

On Wed, Apr 17, 2002 at 11:11:50AM -0700, Hal Daume III wrote:
> i need an associative data structure (like finitemap) which will map data
> elements to Doubles.  i don't need to be able to remove elements and don't
> even need to insert elements once i've built the structure; all i really
> care about is fast lookup.  i have reasonable instances of Eq and Ord and
> probably any other reasonable comparitive metric you could think
> of.  moreover, when i'm creating the data structure, i *know* the
> (approximate) relative frequency of each element.  that is, i know that
> on average i will need to get the Double corresponding to element 'a' ten
> times more frequently than the Double corresponding to element 'b'.
> 
> does anyone have any suggestions for data structures to solve such a
> problem.  i'm currently using FiniteMap, but would like something faster
> (btw, there are a LOT of these elements -- around 1million or so).
> 
>  - 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
> 

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Flocasa: 2nd Call for Paper

2002-04-17 Thread Jean-Marie JACQUET

[ Our apologies for multiple copies. ]


==

  1st International Workshop on
  Foundations of Coordination Languages and
  Software Architectures
  (Foclasa 2002)

   August 24, 2002, Brno, Czech Republic
   Workshop affiliated to CONCUR'2002, 20 - 23 August 2002.


  http://www.info.fundp.ac.be/~jmj/Workshops/Concur2002/Foclasa.html 

==

SCOPE AND TOPICS

Modern  information  systems  rely  more  and  more  on  combining
concurrent, distributed, mobile and heterogenous components.  This
move from  old systems, typically conceived  in isolation, induces
the  need  for  new   languages  and  software  architectures.  In
particular, coordination  languages have been  proposed to cleanly
separate  computational aspects  and communication.  On  the other
hand,  software  architects face  the  problem  of specifying  and
reasoning  on non-functional requirements.   All these  issues are
widely perceived as  fundamental to improve software productivity,
enhance maintainability, advocate modularity, promote reusability,
and  lead   to  systems  more  tractable  and   more  amenable  to
verification and global analysis. 

The aim of  the workshop is to bring  together researchers working
on the foundations of component-based computing, coordination, and
software architectures.  Topics of  interest include (but  are not
limited to):

o  Theoretical models  for  coordination (component  composition, 
   concurrency,   dynamic  aspects  of   coordination,  semantics, 
   expressiveness);
o  Specification,  refinement, and  analysis  of software  archi-
   tectures (patterns  and styles, verification  of functional and 
   non-functional properties);
o  Coordination, architectural, and interface definition languages
   (implementation, interoperability, heterogeneity);
o  Agent-oriented languages (formal models for interacting agents);
o  Dynamic  software architectures (mobile  agents, configuration, 
   reconfiguration);
o  Modeling  of  information  systems (groupware,  internet  and
   the web, workflow management, CSCW and multimedia applications)
o  Coordination patterns (mobile computing, internet computing);
o  Tools  and environments  for  the  development of  coordinated 
   applications


SUBMISSION GUIDELINES

   Papers describing  original work are solicited  as contributions to
   Foclasa.  Submitted  papers  should  be  limited to  6  000  words, 
   preferrably formatted  according  to  the  Fundamenta  Informaticae
   style (available at http://fi.mimuw.edu.pl/submissions.html).

   They  should be  emailed as  PostScript (PS)  or  Portable Document 
   Format (PDF) files to [EMAIL PROTECTED]


PROCEEDINGS

   The  proceedings will  be published  as a  technical report  of the
   Institute  of Informatics  at  the University  of  Namur, and  will 
   be available at the workshop. 


PUBLICATION

   Selected papers will be published  in a special issue of the Funda-
   menta Informaticae  journal, with February 2003  as expected publi-
   cation time.

   
   
IMPORTANT DATES:

  o May 25, 2002:Submission deadline.
  o June 30, 2002:   Notification of acceptance.
  o August 1, 2002:  Final version.
  o August 24, 2002: Meeting Date.


LOCATION

   The workshop will be held in Brno in August 2002. It is a satellite
   workshop of CONCUR 2002. For  venue and registration see the CONCUR
   web page at http://www.fi.muni.cz/concur2002/


WORKSHOP ORGANIZERS

  o Antonio Brogi (University of Pisa, Italy)
  o Jean-Marie Jacquet (University of Namur, Belgium)


PROGRAMME COMITTEE:

  o Antonio Brogi (University of Pisa, Italy) - Co-chair
  o Rocco De Nicola (University of Firenze, Italy)
  o Jos Luiz Fiadeiro (ATX Software and Univ. of Lisbon, Portugal) 
  o Roberto Gorrieri (Univerity of Bologna, Italy) 
  o Paola Inverardi (Univerity L'Aquila, Italy)
  o Jean-Marie Jacquet (University of Namur, Belgium) - Co-chair
  o Joost Kok (University of Leiden, The Netherlands) 
  o Antonio Porto (New University of Lisbon, Portugal) 




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



data structure question

2002-04-17 Thread Hal Daume III

i need an associative data structure (like finitemap) which will map data
elements to Doubles.  i don't need to be able to remove elements and don't
even need to insert elements once i've built the structure; all i really
care about is fast lookup.  i have reasonable instances of Eq and Ord and
probably any other reasonable comparitive metric you could think
of.  moreover, when i'm creating the data structure, i *know* the
(approximate) relative frequency of each element.  that is, i know that
on average i will need to get the Double corresponding to element 'a' ten
times more frequently than the Double corresponding to element 'b'.

does anyone have any suggestions for data structures to solve such a
problem.  i'm currently using FiniteMap, but would like something faster
(btw, there are a LOT of these elements -- around 1million or so).

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

2002-04-17 Thread Brian Huffman

On Tuesday 16 April 2002 07:15 pm, Jorge Adriano wrote:
> [1] Bug1?
>
> This declaration:
> > A = (,) Int Int
>
> is accepted by ghci. Is this behaveour correct,
> 1. It kind of shadows (,) is defined in PrelTup meaning that you can no
> longer use (,) prefix to refer to tuples - like (,) 1 2.
> 2. Seems to me like (,) is not correct syntax for a consym as defined in
> the H98 Report so we shouldn't be able to redefine it.
> ...

I found that ghci (I'm using version 5.02.2) will also allow you to reuse [] 
as a constructor, as in:

> data Foo a = [] a deriving Show

For some reason, though, this has the side effect of causing a segmentation 
fault whenever I type in a literal list like [1,2,3]. Here are some other 
weird things you can try:

> data [] a = [] Int deriving Show
 --ghci complains about duplicate instances

> data [] = [] Int deriving Show

Test> [] 6543
[] 6543
Test> :i []
-- PrelBase.[] is a data constructor
PrelBase.[] :: Int*** Exception: Prelude.head: empty list

>data (,) a b = (,) b a

Test> ('a',72::Int)
('a',72)
Test> (,) 'a' (72::Int)
(97,'H')

>data (,) a b = (,) b a
>typecast :: a -> b
>typecast x = fst ((,) x undefined)

Evidently, when you redefine the datatypes [] or (,), you can change the 
internal representation of those types, without affecting their class 
instances or other functions that may have depended on the original 
representation. Obviously this does not preserve type safety.

I see two possible remedies: (1) Simply disallow [] and (,) as user-defined 
types, or (2) Allow users to define their own versions of [] and (,), but use 
qualified names to distinguish them from the originals.

- Brian Huffman


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



Re: Bug?

2002-04-17 Thread Jorge Adriano

On Wednesday 17 April 2002 03:15, Jorge Adriano wrote:
> [1] Bug1?
> This declaration:
> > A = (,) Int Int


Opsss cut and paste problems :)
> data A = (,) Int Int
> is accepted by ghci. Is this behaveour correct,


This is what I meant.
Anyway in Bug 2 I used the 'correct' declaration

> [2] Bug2?
> - Step 1
> Load this in ghci,
> ---
> module Test where
> data C = C ((,) Int Int)
>
> data A = (,) !Int !Int --   <--- There it is


J.A.

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



Re: Coding Problems!! Please help

2002-04-17 Thread John Hughes

I am currently working on an assignment with requires us to write in
Haskell. I am having trouble with "pipeline". The required textbook
called, "The Craft of Functional Programming" 2nd Edition.  There is a
pipeline example, which I find it useful in my assignment, but for some
reason, there may be a typo in the pipeline syntax, which is ">.>". Coz it
doesn't compile.

Your problem is that that book defines and uses a non-standard composition
operator.

The standard Haskell function composition is written just ".", defined by

(f . g) x = f (g x)

Notice that in f . g, it is *g* which is applied first to the argument, and f
which is applied to the result of that. That is, composition is "backwards" in
some sense. Here's an example:

 sqrt . abs

takes the absolute value of its argument first, and then the square root of
that, not the absolute value of the square root (which would fail for negative
arguments).

Many people (including mathematicians) prefer to write the arguments of
compose in the other order, so that the first function to be applied is the
first one you write. To make that possible, Simon Thompson defines

(f >.> g) x = g (f x)

So now you would write the example above as

abs >.> sqrt

You take the absolute value first, so you write it first.

Regardless of which you prefer, the important thing to understand is that >.>
IS NOT PART OF THE HASKELL STANDARD. So if you want to use it, you have to
include the definition above in your own program.

John Hughes

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



Re: Coding Problems!! Please help

2002-04-17 Thread Martin Norbäck

ons 2002-04-17 klockan 09.25 skrev Jack Tsai:
> I am currently working on an assignment with requires us to write in
> Haskell. I am having trouble with "pipeline". The required textbook called,
> "The Craft of Functional Programming" 2nd Edition.   There is a pipeline
> example, which I find it useful in my assignment, but for some reason, there
> may be a typo in the pipeline syntax, which is ">.>". Coz it doesn't compile
> @_@

Well, normally I would tell you to ask your teacher for advice, but it
seems you have done a lot of work yourself here, and only got stuck on
the strange >.> operator.

One of the things about this book which I don't like is that Thompson
introduces a lot of non-standard functions.

You can try to make the following definition in your file:

(>.>) = flip (.)

Regards,

Martin

--
Martin Norbäck  [EMAIL PROTECTED]
Kapplandsgatan 40   +46 (0)708 26 33 60
S-414 78  GÖTEBORG  http://www.dtek.chalmers.se/~d95mback/
SWEDEN  OpenPGP ID: 3FA8580B



signature.asc
Description: PGP signature


Coding Problems!! Please help

2002-04-17 Thread Jack Tsai

Dear staff,
I am currently working on an assignment with requires us to write in 
Haskell. I am having trouble with "pipeline". The required textbook called, 
"The Craft of Functional Programming" 2nd Edition.   There is a pipeline 
example, which I find it useful in my assignment, but for some reason, there 
may be a typo in the pipeline syntax, which is ">.>". Coz it doesn't compile 
@_@

I have attached a file of the example, I found from the book. There is a 
website where I could download the entire book. It's got the same stuff as 
in my textbook. Please help me, coz i've tried even Unix's pipeline syntax  
which is obviously wrong... I'm not desperate, please reply, thank you very 
much.

Sincerely,
Jack

This is the output of the compilor...
/*/
Haskell 98 mode: Restart with command line option -98 to enable

Reading file "C:\PROGRAM FILES\HUGS98\lib\Prelude.hs":
Parsing
Dependency analysis
Type checking..
Compiling..
Reading file "E:\433\CHAPTE~1.LHS":
Parsing
Dependency analysis
ERROR "E:\433\CHAPTE~1.LHS" (line 22): Undefined variable ">.>"
Prelude>
/**/




_
Send and receive Hotmail on your mobile device: http://mobile.msn.com

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



Coding Problems!! Please help

2002-04-17 Thread Jack Tsai

Dear staff,
I am currently working on an assignment with requires us to write in 
Haskell. I am having trouble with "pipeline". The required textbook called, 
"The Craft of Functional Programming" 2nd Edition.   There is a pipeline 
example, which I find it useful in my assignment, but for some reason, there 
may be a typo in the pipeline syntax, which is ">.>". Coz it doesn't compile 
@_@

I have attached a file of the example, I found from the book. There is a 
website where I could download the entire book. It's got the same stuff as 
in my textbook. Please help me, coz i've tried even Unix's pipeline syntax  
which is obviously wrong... I'm not desperate, please reply, thank you very 
much.

Sincerely,
Jack

This is the output of the compilor...
/*/
Haskell 98 mode: Restart with command line option -98 to enable

Reading file "C:\PROGRAM FILES\HUGS98\lib\Prelude.hs":
Parsing
Dependency analysis
Type checking..
Compiling..
Reading file "E:\433\CHAPTE~1.LHS":
Parsing
Dependency analysis
ERROR "E:\433\CHAPTE~1.LHS" (line 22): Undefined variable ">.>"
Prelude>
/**/


_
Chat with friends online, try MSN Messenger: http://messenger.msn.com



Haskell: The Craft of Functional Programming
Simon Thompson
(c) Addison-Wesley, 1999.

Chapter 10

Example: creating an index
^^

The basic type symonyms

>   type Doc  = String
>   type Line = String
>   type Word = String

The type of the top-level function
The top-level definition

>   makeIndex :: Doc -> [ ([Int],Word) ]
>   makeIndex
> = lines   >.> --   Doc-> [Line]
>   numLines>.> --   [Line] -> [(Int,Line)] 
>   allNumWords >.> --   [(Int,Line)]   -> [(Int,Word)]
>   sortLs  >.> --   [(Int,Word)]   -> [(Int,Word)]
>   makeLists   >.> --   [(Int,Word)]   -> [([Int],Word)]
>   amalgamate  >.> --   [([Int],Word)] -> [([Int],Word)]
>   shorten --   [([Int],Word)] -> [([Int],Word)]

Implementing the component functions

 
Attach a number to each line.

>   numLines :: [Line] -> [ ( Int , Line ) ]
>   numLines linels
> = zip [1 .. length linels] linels

Associate each word with a line number

>   numWords :: ( Int , Line ) -> [ ( Int , Word ) ]

>   numWords (number , line)
> = [ (number , word) | word <- Chapter7.splitWords line ]

The definition uses splitWords from Chapter 7, modified to use a different
version of whitespace. For this to take effect, need to make the modification
in the Chapter7.lhs file.

>   whitespace :: String
>   whitespace = " \n\t;:.,\'\"!?()-"

Apply numWords to each integer,line pair.

>   allNumWords :: [ ( Int , Line ) ] -> [ ( Int , Word ) ]
>   allNumWords = concat . map numWords

The list must next be
sorted by word order, and lists of lines on which a word appears be built.
The ordering relation on pairs of numbers and 
words is given by

>   orderPair :: ( Int , Word ) -> ( Int , Word ) -> Bool
>   orderPair ( n1 , w1 ) ( n2 , w2 )
> = w1 < w2 || ( w1 == w2 && n1 < n2 )

Sorting the list using the orderPair ordering on pairs.

>   sortLs :: [ ( Int , Word ) ] -> [ ( Int , Word ) ]

>   sortLs [] = []
>   sortLs (p:ps)
> = sortLs smaller ++ [p] ++ sortLs larger
>   where
>   smaller = [ q | q<-ps , orderPair q p ]
>   larger  = [ q | q<-ps , orderPair p q ]

The entries for the same word need to be accumulated together.
First each entry is converted to having a list of line numbers associated with
it, thus

>   makeLists ::  [ (Int,Word) ] -> [ ([Int],Word) ]
>   makeLists 
> = map mklis 
>   where
>   mklis ( n , st ) = ( [n] , st )

After this, the lists associated with the same words are amalgamated.

>   amalgamate :: [ ([Int],Word) ] -> [ ([Int],Word) ]

>   amalgamate [] = []
>   amalgamate [p] = [p]
>   amalgamate ((l1,w1):(l2,w2):rest)
> | w1 /= w2= (l1,w1) : amalgamate ((l2,w2):rest)
> | otherwise   = amalgamate ((l1++l2,w1):rest)

Remove all the short words.

>   shorten :: [([Int],Word)] -> [([Int],Word)]

>   shorten 
> = filter sizer 
>   where
>   sizer (nl,wd) = length wd > 3


Verification and general functions
^^

All the functions used in this section have been defined earlier.