Re: Strange lexical syntax

1999-06-28 Thread Christian Sievers

Simon Marlow wrote:

> Quick quiz:  how many Haskell lexemes are represented by the following
> sequences of characters?
> 
>   1)  M.x
>   2)  M.let
>   3)M.as
>   4)  M..
>   5)  M...
>   6)  M.!
> 
> answers:
>   
>   1)  1.  This is a qualified identifier.

We all know what M.x means, but recently I wondered about how the
report makes this sure. I'm afraid it doesn't.

Of course, there is section "5.5.1 Qualified names" saying:

A qualified name is written as modid.name. Since qualifier names are
part of the lexical syntax, no spaces are allowed between the
qualifier and the name. Sample parses are shown below.

[I guess "qualifier names" should be "qualified names".]
 
But this seems to be an explanation, not an additional information.
The second sentence seems to say M.x is a lexeme, as they are the
fundamental items of lexical analysis.
(Section "2.2 Lexical Program Structure": At each point, the longest
 possible lexeme satisfying the lexeme production is read, using a
 context-independent deterministic lexical analysis ...)

And if it weren't a lexeme, we're really in trouble, because:
Any kind of whitespace is also a proper delimiter for lexemes.

Still it isn't. It surely is a qvarid, but lexeme is defined like
this: 

lexeme  -> varid | conid | varsym | consym
 | literal | special | reservedop | reservedid 

A varid is unqualified, and it is also none of the others.

So maybe this should be:
lexeme  -> qvarid | qconid | qvarsym | qconsym
 | literal | special | reservedop | reservedid 

And then I guess we should have   qtyc{on,ls} -> qconid .

Am I terribly missing something?

>   2)  3. 'let' is a keyword, which excludes this string
>  from being a qualified identifier.

That's really ugly. I never thought about such things.
Good you finally uncovered it.

>   3)  1. 'as' is a "specialid", not a "reservedid".
> 
>   4)  1. This is a qualified symbol.
> 
>   5)  2. '..' is a reserved operator, so a qualified symbol
>  is out.  The sequence '...' is a valid operator and
>  according to the maximal munch rule this must be
>  the second lexeme.
> 
>   6)1. '!' is a "specialop", not a "reservedop".
> 
> 
> I especially like case 5 :-)

Yes, it's amazing! Why didn't you go on? M is a qualified symbol?

> This is pretty bogus.  I suggest as a fix for Haskell 2 that all of the
> above be treated as 1 lexeme, i.e. qualified identifiers/symbols.

But what would M.let mean? Module M can't define let, neither this way
  M.let = ...  -- qualiefied name not allowed
nor that:
  let = ...-- let is reserved 

However, 'let' does mean something in module M, so a strange option is
to let 'M.let' mean 'let'.

Should we just disallow it?


There is still another problem in the report.
Section "2.3 Comments" says:
A nested comment begins with the lexeme "{-" ...

There is no such lexeme.
We'd need  lexeme -> ... | opencom


What does M.-- mean?


All the best,
Christian Sievers
-- 
Freeing Software is a good beginning. Now how about people?





Re: Second attempt for an STL like library for Haskell

1999-06-28 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--D60EAED940B337DE04784023
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Kevin Atkinson wrote:
 
> The file Main.hs contains a small test script demonstrating how
> PrimArrays can be faster than arrays with bound checking.  Although it
> is difficult to tell, as the garbage collector gets in the way of my
> benchmarks, accumPrimArray is about 50% to 33% faster than the normal
> accumArray and my implementation of accumArray also seams to be a little
> faster than GHC implantation.  I tried profiling the various accums
> however I can't seam to get meaningful results form  the CVS version of
> ghc.  (Is the profiler still not working correctly or is it me?).

After modifying Main.hs to test each of the accums one at a time it
seams that my accum takes about as much time as ghc accum and the
accumPrimArray is twice as fast as the other two.

As I suspected the fancy indexes and bound checking come at a high
price.

I attached the modified Main.hs so that you can try it out for yourself.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--D60EAED940B337DE04784023
Content-Type: text/plain; charset=us-ascii;
 name="Main.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Main.hs"


module Main (main, prim, norm, orig, expr) where

import Prelude hiding (null, lookup)

import Mutable
import Assoc
import Container

import MutPrimArray
import MutAltArray 
import STExtras

import Random
import System

import qualified Array
import Ix


import PrelBase
import PrelST
import PrimArrayDefn hiding (freeze', unsafeFreeze', thaw')

#ifdef __GLASGOW_HASKELL__

import Eval -- this should really not be necessary, however the CVS
-- version of ghc (June 27, 1999) requires it. 
-- I think it is a bug.

import CPUTime

num :: Int
num = 10

#define scc(n) _scc_ n

#else

getCPUTime :: IO Integer
getCPUTime = return 0

num :: Int
num = 1000

#define scc(n)

#endif

l :: [Int]
l = take num$ rs (mkStdGen 13)

rs g = case randomR (0,98) g of (x,g') -> x : rs g'

main :: IO ()
main = do bench$ print$ scc("gen") seq (sum l) "Evaluating l"
  x <- getArgs
  case head x of 
   "orig" -> bench$ scc("orig") orig l
   "prim" -> bench$ scc("prim") prim l
   "norm" -> bench$ scc("norm") norm l

bench com = do s <- getCPUTime
   com
   f <- getCPUTime
   print$ (f-s) `div` (10^9)

prim l = do let a :: PrimArray Int Int
a = accumPrimArray (+) 0 100 $ zip l (repeat 1)
putStr "prim\n"
print$ elems a

norm l = do let a :: Array Int Int
a = accumArray (+) 0 (0,99) $ zip l (repeat 1)
putStr "norm\n"
print$ elems a

orig l = do let a :: Array.Array Int Int
a = Array.accumArray (+) 0 (0,99) $ zip l (repeat 1)
putStr "orig\n"
print$ Array.elems a

{-
expr l = do let els = do m <- mlistPrimArray 100 (take 100 $ repeat 0)
 maccum (+) m (1,
 melems m
putStr "expr\n"
print$ runST els
-}

expr l = do let a :: PrimArray Int Int
a = accumPrimArray (+) 0 100 [(1,a!2),(2,a!3),(3,a!4),(4,100)]
putStr "expr\n"
print$ elems a

maccum' f (M m _) l = ST$ \s -> (# z s l, () #)
where z s [] = s
  z s ((I# ix,el):t) = 
  case readArray# m ix s of
  (# s, x #) -> let r = case x `f` el of r -> seq r r 
in  case writeArray# m ix r s of
s -> z s t

mcount' (M m _) l = ST$ \s -> (# z s l, () #)
where z s [] = s
  z s ((I# ix):t) = 
  case readArray# m ix s of
  (# s, x #) -> case writeArray# m ix (x+1) s of
s -> z s t

--D60EAED940B337DE04784023--






RPM with Haskell documentation

1999-06-28 Thread Manuel M. T. Chakravarty

For all Linux users who like to have the HTML version of the
Haskell 98 report plus the library report, errata page, and
the differences to 1.4 handily stored in /usr/doc (and who
use rpm as their package manager), check out

  ftp://greyarea.is.tsukuba.ac.jp/pub/jibunmaki/noarch/haskell-doc-98-1.noarch.rpm

for easy installation and removal (includes an `index.html'
file, so that a single bookmark in your HTML browser
suffices).

Manuel





Re: Making system call from Haskell?

1999-06-28 Thread Manuel M. T. Chakravarty

> Do anyone know another way to make system call from Haskell (such as finding
> files in a directory, change file attribute...)  besides calling to another
> language to do the job?

In the end, you will have to call out to C anyway.  So what
do you really want to avoid?  The bother of coding it up
yourself?  Then, try GHC's Posix libraries.

Manuel





Re: Making system call from Haskell?

1999-06-28 Thread Hans Aberg

At 13:15 +0800 1999/06/26, Nguyen Phan Dung wrote:
>Do anyone know another way to make system call from Haskell (such as finding
>files in a directory, change file attribute...)  besides calling to another
>language to do the job?

Hugs has a System module, which calls the C system() function. It then
depends on what this system() is implemented to do -- doing nothing is
legal in ISO C, but on a UNIX computer it calls the Bourne shell, simple
but inefficent.

  Hans Aberg
  * Email: Hans Aberg 
  * Home Page: 
  * AMS member listing: 







Re: Making system call from Haskell?

1999-06-28 Thread Lennart Augustsson

Hans Aberg wrote:

> At 13:15 +0800 1999/06/26, Nguyen Phan Dung wrote:
> >Do anyone know another way to make system call from Haskell (such as finding
> >files in a directory, change file attribute...)  besides calling to another
> >language to do the job?

Both of these things are supported by the Directory module (check out the
library report).


> Hugs has a System module, which calls the C system() function.

Not just Hugs, it's part of the Haskell standard.

-- Lennart







Strange lexical syntax

1999-06-28 Thread Simon Marlow

I just uncovered a couple of strange cases in the Haskell lexical syntax.
If you're not especially bothered about such things, don't bother to read
on!

Quick quiz:  how many Haskell lexemes are represented by the following
sequences of characters?

1)  M.x
2)  M.let
3)M.as
4)  M..
5)  M...
6)  M.!

answers:

1)  1.  This is a qualified identifier.

2)  3. 'let' is a keyword, which excludes this string
   from being a qualified identifier.

3)  1. 'as' is a "specialid", not a "reservedid".

4)  1. This is a qualified symbol.

5)  2. '..' is a reserved operator, so a qualified symbol
   is out.  The sequence '...' is a valid operator and
   according to the maximal munch rule this must be
   the second lexeme.

6)1. '!' is a "specialop", not a "reservedop".


I especially like case 5 :-)

This is pretty bogus.  I suggest as a fix for Haskell 2 that all of the
above be treated as 1 lexeme, i.e. qualified identifiers/symbols.

Cheers,
Simon





Second attempt for an STL like library for Haskell

1999-06-28 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Here is begginings of my second attempt for an STL like library for
Haskell.  The only think this version has is Arrays however I plan to
add a lot more.  I am almost done with a mutable hash table and I plan
on adding incorporating in other containers such as Ordered Map, Sets,
and Bags, Queues, Dequeues and other similar stuff.  I also plan on
working on a general algorithm collection.  I will implement both purely
functional containers and truly mutable ones.

This version will compile under ghc 4.02 without optimization and the
June 27 CVS version of ghc with Optimizations.  It will also work
through hugs provided you run the files through hscpp.  Unlike Edition I
will strive to making sure that my library always makes it through the
latest version of Hugs.

The file Main.hs contains a small test script demonstrating how
PrimArrays can be faster than arrays with bound checking.  Although it
is difficult to tell, as the garbage collector gets in the way of my
benchmarks, accumPrimArray is about 50% to 33% faster than the normal
accumArray and my implementation of accumArray also seams to be a little
faster than GHC implantation.  I tried profiling the various accums
however I can't seam to get meaningful results form  the CVS version of
ghc.  (Is the profiler still not working correctly or is it me?).

I am very serious about hammering out a nice STL like library for
Haskell so I would be very interested in early feedback from some of you
Haskell experts out there.

I have attached some of the more interesting files from my library.  The
complete set can be found at http://metalab.unc.edu/kevina/abs.tar.

Once again feed back most welcome, especially from the Haskell experts
out on the list.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii;
 name="Container.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Container.hs"

module Container where

import Prelude hiding (null)

{- Basic container functions. -}

class Name c where
name :: c -> String

class Size c where
size :: c -> Int

class Empty c where
empty:: c

class Null c where
null :: c -> Bool
isEmpty  :: c -> Bool

null = isEmpty
isEmpty = null

class Values c v where
values :: c v -> [v]

class ValMap c v1 v2 where
valmap :: (v1 -> v2) -> c v1 -> c v2

instance (Functor c) => ValMap c v1 v2 where
valmap = fmap

--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii;
 name="Assoc.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Assoc.hs"


module Assoc where

{- 

Functions on Associated Containers (Assoc. C.).  A Simple Assoc. C.
is a container which is indexed based on the value of its
elements such as Sets and Bags.  A Pair Assoc. C. is a Finite Map.

-}

import Container (ValMap(..))
import Prelude hiding (lookup)
import Maybe

class Buckets c where
-- the number of buckets in a hash table
buckets :: c -> Int

class Bounds c i e where
-- the bounds of an array
bounds :: c i e -> (i,i)

class Assocs c i e where
-- convert a container to a list of ...
assocs  :: c i e -> [(i,e)]
indices :: c i e -> [i]
keys:: c i e -> [i]
elems   :: c i e -> [e]

-- minimal definition: assocs | indices & elems | keys & elems
-- keys and indices are assumed to do the same thing
   
assocs c = zip (indices c) (elems c)
indices = map fst . assocs
keys= indices
elems   = map snd . assocs

class Lookup c i e where
-- finds an elemant in a Pair. Assoc. C.  (!) will cause an error
-- if the element is not found
lookup  :: i -> c i e -> Maybe e
(!) :: c i e -> i -> e

-- monmal defination: lookup
  
c ! a = fromJust (lookup a c)

class Find c v where
find :: v -> c v -> Maybe v
findAll :: v -> c v -> [v]  
isMember :: v -> c v -> Bool
count :: v -> c v -> Int

-- minimal defination: find | findAll

find v c = listToMaybe$ findAll v c
findAll v c = maybeToList$ find v c
isMember v c = isJust$ find v c
count v c = length$ findAll v c

class Ixmap c i e j where
ixmap   :: (j,j) -> (i -> j) -> c i e -> c j e

class Keymap c i e j where
keymap   :: (i -> j) -> c i e -> c j e

class Elmap c i e f where
elmap   :: (e -> f) -> c i e -> c i f
map_:: ((i,e) -> f) -> c i e -> c i f

-- minimal defination: map_

elmap f = map_ (\(_,e) -> f e)

instance (Elmap c i e f) => ValMap (c i) e f where
valmap = elmap

class AssocsMap c i e j f where
assocsMap :: ((i,e) -> (j,f)) -> c i e -> c j f

class Insert c v where
-- insert a new element in a Simple Assoc. C.  
-- the behavinor of insertin