RE: efficiency of UArray

2002-05-16 Thread Simon Peyton-Jones

GHC doesn't remove intermediate lists down both
branches of a zip, so yes, you'll get intermediate lists.

Why not use array indexing, as per your second version
(only in Haskell)?

Simon

| -Original Message-
| From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
| Sent: 16 May 2002 00:55
| To: GHC Users Mailing List
| Subject: efficiency of UArray
| 
| 
| can we expect a function like:
| 
|   sum [x*y | (x,y) - zip (elems v) (elems u)]
| 
| to be as efficient as, say:
| 
| sum = 0
| for i=1, n
|   sum = sum + v[i] * u[i]
| 
| ?
| 
| Basically, will any intermediate lists be created here?
| 
| --
| Hal Daume III
| 
|  Computer science is no more about computers| [EMAIL PROTECTED]
|   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
| 
| ___
| Glasgow-haskell-users mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Exceptions and IO

2002-05-16 Thread Ashley Yakeley

My confusion surrounding exceptions in the IO monad comes from the fact 
that IO failures and bottom are not cleanly separated. I had always 
assumed the IO monad looked something like this:

 newtype IO a = IO (RealWorldState - Either IOFailure 
(RealWorldState,a))

 return a = IO (\r - Right (r,a))
 fail s = IO (\r - Left (userFailure s))

This would make sense, I think, because it's so easy this way for 
Prelude.catch to catch all IOFailures but leave pure bottom exceptions 
alone, just as the report says. But in fact IO looks more like this:

 newtype IO a = IO (RealWorldState - (RealWorldState,a))

 return a = IO (\r - (r,a))
 fail s = IO (\r - throw (userError s))

...which means Prelude.catch has to separate out exceptions caused by 
fail from those caused by error, etc. and there's confusion between 
bottom and exceptions that happen entirely in IO.

-- 
Ashley Yakeley, Seattle WA


-- ghc -package lang TestException.hs -o TestException  ./TestException
module Main where
{
import IORef;
import qualified Exception;

getPureException :: a - IO (Maybe Exception.Exception);
getPureException a = (Exception.catch (seq a (return Nothing)) (return . 
Just));

showIOS :: String - IO String - IO ();
showIOS s ios = do
{
putStr (s ++ : );
mpe - getPureException ios;
case mpe of
{
Just pe - putStrLn (pure exception (++ (show pe) ++));
Nothing - Exception.catch (Prelude.catch (do
{
result - ios;
mrpe - getPureException result;
case mrpe of
{
Just pe - putStrLn (returned pure exception 
(++ (show pe) ++));
Nothing - putStrLn (value (++ (show result) 
++));
};
}) (\e - putStrLn (IO failure ( ++ (show e) ++))) 
)
(\e - putStrLn (IO other exception ( ++ (show e) 
++)));
};
};

evaluate' :: a - IO a;
evaluate' a = a `seq` return a;

evaluate'' :: a - IO a;
evaluate'' a = (Exception.catch (seq a (return a)) (\e - fail (show e)));

main :: IO ();
main = do
{
putStrLn * value;
showIOS return text   
(return text);
showIOS return undefined  return text   (return undefined  
return text);
putStrLn ;

putStrLn * returned pure exception;
showIOS return undefined  
(return undefined);
showIOS return (seq undefined text)   (return (seq undefined 
text));
showIOS return ()  return undefined (return ()  return 
undefined);
showIOS return undefined = return   (return undefined = 
return);
putStrLn ;

putStrLn * IO failure;
showIOS fail text
 (fail text);
showIOS ioError (userError text)  (ioError 
(userError text));
putStrLn ;

putStrLn * IO other exception;
showIOS undefined  return text  (undefined  
return text);
showIOS return ()  undefined(return ()  
undefined);
showIOS ioError (ErrorCall text)  (ioError 
(Exception.ErrorCall text));
showIOS ioError (AssertionFailed text)(ioError 
(Exception.AssertionFailed text));
putStrLn ;

putStrLn * pure exception;
showIOS undefined
 undefined;
showIOS seq undefined (return text)   (seq undefined (return 
text));
showIOS seq undefined (return undefined)  (seq undefined (return 
undefined));
showIOS error text(error 
text);
showIOS throw (userError text)
(Exception.throw (userError text));
showIOS throw (ErrorCall text)
(Exception.throw (Exception.ErrorCall text));
showIOS throw (AssertionFailed text)  (Exception.throw 
(Exception.AssertionFailed text));
putStrLn ;

putStrLn * evaluate functions;
showIOS evaluate undefined
(Exception.evaluate undefined);
showIOS evaluate' undefined  

Re: Giving profiled object files a different extension (was: RE: Profiling suggestion)

2002-05-16 Thread Malcolm Wallace

Simon Marlow [EMAIL PROTECTED] writes:

  Re the current and recurring conflicts between profiling and
  non-profiling code; how hard would it be to name GHC's output files
  differently when compiling with -prof?
 
 The proposal, therefore, is to extend the meaning of '-prof' to mean
 '-prof -osuf p_o -hisuf p_hi' or similar.

It might be worth pointing out that nhc98 already does something like
this, and we find that it is definitely a big win.  We settled on .p.o
for heap profiling and .z.o for time profiling (also .T.o for tracing,
but that may disappear shortly with the advent of portable Hat).

 To summarise the advantages/disadvantages:
   - win: you could store profiled and normal objects in the same
 directory.

Very handy, because it means you can switch between normal and profiled
versions of a project without having to do a complete rebuild every time.

   - win: you'd be less likely to mix up profiled and normal objects.

Mixing up object files was an absolute pain in the backside, and
happened far too frequently, until we adopted separate suffixes.

   - lose: Makefile writing gets harder.  Extra suffix rules have to
 be added to deal with the new suffixes, and 'make depend' has
 to add dependency rules for the extra suffixes (ghc -M has some
 support for doing this).  If you're using ghc --make this doesn't
 affect you.

Worth noting also that `hmake' currently understands that -p (for
nhc98) means to look for the .p.o suffix etc.  It would be very
straightforward to extend the mechanism to do the same or similar
for ghc.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



syntax of RULES pragmas?

2002-05-16 Thread Janis Voigtlaender

Hi,

I was trying to play with GHC 5.02's RULES pragmas, but failed due to
syntax problems.

When trying:

  {-# RULES map/map forall f g xs. map f (map g xs) = map (f.g) xs #-}

  main = print (map id (map id Hello))

I get:

  ghc5 test.hs -O
  test.hs:1: Variable not in scope: `forall'

  test.hs:1: Variable not in scope: `f'

  test.hs:1: Variable not in scope: `g'

  test.hs:1: Variable not in scope: `xs'

  test.hs:1: Variable not in scope: `f'

  test.hs:1: Variable not in scope: `g'

  test.hs:1: Variable not in scope: `xs'

  test.hs:1: Variable not in scope: `f'

  test.hs:1: Variable not in scope: `g'

  test.hs:1: Variable not in scope: `xs'
  Exit 1


With:

  {-# RULES map/map forall f g xs. 
  map f (map g xs) = map (f.g) xs #-}

  main = print (map id (map id Hello))

I get:

  test.hs:2: parse error (possibly incorrect indentation)
  Exit 1


In the user's doc on http://www.haskell.org/ghc/ I also saw the syntax:

  {-# RULES map/map forall f,g,xs. map f (map g xs) = map (f.g) xs #-}

  main = print (map id (map id Hello))

which fails with:

  test.hs:1: parse error on input `,'
  Exit 1


So how exactly do I have to specify a rewrite rule? Any hints
appreciated.

Thanks, Janis.


--
Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: syntax of RULES pragmas?

2002-05-16 Thread Simon Peyton-Jones

You need -fglasgow-exts.  (Should ignore a pragma without
-fglasgow-exts,
and does so now, but 5.03 gave the bad message you found.)

The manual is wrong; spaces between the variables is right.

Simon

| -Original Message-
| From: Janis Voigtlaender [mailto:[EMAIL PROTECTED]] 
| Sent: 16 May 2002 14:49
| To: [EMAIL PROTECTED]
| Subject: syntax of RULES pragmas?
| 
| 
| Hi,
| 
| I was trying to play with GHC 5.02's RULES pragmas, but 
| failed due to syntax problems.
| 
| When trying:
| 
|   {-# RULES map/map forall f g xs. map f (map g xs) = map 
| (f.g) xs #-}
| 
|   main = print (map id (map id Hello))
| 
| I get:
| 
|   ghc5 test.hs -O
|   test.hs:1: Variable not in scope: `forall'
| 
|   test.hs:1: Variable not in scope: `f'
| 
|   test.hs:1: Variable not in scope: `g'
| 
|   test.hs:1: Variable not in scope: `xs'
| 
|   test.hs:1: Variable not in scope: `f'
| 
|   test.hs:1: Variable not in scope: `g'
| 
|   test.hs:1: Variable not in scope: `xs'
| 
|   test.hs:1: Variable not in scope: `f'
| 
|   test.hs:1: Variable not in scope: `g'
| 
|   test.hs:1: Variable not in scope: `xs'
|   Exit 1
| 
| 
| With:
| 
|   {-# RULES map/map forall f g xs. 
|   map f (map g xs) = map (f.g) xs #-}
| 
|   main = print (map id (map id Hello))
| 
| I get:
| 
|   test.hs:2: parse error (possibly incorrect indentation)
|   Exit 1
| 
| 
| In the user's doc on http://www.haskell.org/ghc/ I also saw 
| the syntax:
| 
|   {-# RULES map/map forall f,g,xs. map f (map g xs) = map 
| (f.g) xs #-}
| 
|   main = print (map id (map id Hello))
| 
| which fails with:
| 
|   test.hs:1: parse error on input `,'
|   Exit 1
| 
| 
| So how exactly do I have to specify a rewrite rule? Any hints 
| appreciated.
| 
| Thanks, Janis.
| 
| 
| --
| Janis Voigtlaender
| http://wwwtcs.inf.tu-dresden.de/~voigt/
| mailto:[EMAIL PROTECTED]
| ___
| Glasgow-haskell-users mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: infix type constructors

2002-05-16 Thread Simon Peyton-Jones

Chris

I'm slowly getting around to this.   Design questions:

(A) I think it would be a good compromise to declare that operators
like + are type *constructors* not type *variables*.  So 
S+T
would be a type.  That's slightly inconsistent with value variables,
but it's jolly useful.  So only alphabetic things would be type
variables.
It's very clunky having to write
S :+: T

(B) One wants to declare fixities for type constructors, and that
gets them mixed up with their value counterparts.  My suggestion:
disamiguate with a compulsory 'type' keyword
infix 6 type +
infixl 9 type *

Or should it be 'data'?  Or should it depend how + and * are declared?

(C) The other place they can get mixed up is in import and export
lists.  I can think of several solutions

(i) module Foo( + ) where ...
means export the type constructor (+); currently illegal in H98
module Foo( (+) ) where ...
   means export the variable (+).

This seems a bit of a hack.

(ii) Use the 'type' keyword, rather like 'module':
module Foo( type + ) where 
data a+b = A a | B b
or
module Foo( type +(A,B) ) where
data a+b = A a | B b

[I think 'type' is better than 'data' because we want to hide the 
distinction in an export list or do you think we should use the 
same keyword as the one in the defn?]

Similarly on import lists.


(D) I suppose one might want infix notation for type variables too:

data T a = T (Int `a` Int)

but maybe that's going too far?

Simon

| -Original Message-
| From: Okasaki, C. DR EECS [mailto:[EMAIL PROTECTED]] 
| Sent: 03 May 2002 14:09
| To: '[EMAIL PROTECTED]'
| Subject: infix type constructors
| 
| 
| I'm not sure how long this has been implemented in GHC,
| but I just noticed that infix type constructors are allowed,
| as in
| 
|   data a :- b = ...
| 
| The syntactic asymmetry between type constructors and
| data contructors has bothered me for a while, so this
| is a welcome change!  However, this syntax seems to
| be supported for data and newtype declarations,
| but not for type declarations.  For example,
| 
|   type a :- b = ...
| 
| does not seem to be allowed.  Is there a reason for this?
| Or was it just an oversight?
| 
| -- Chris
| ___
| Glasgow-haskell-users mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



?? Redirecting standar error output ...

2002-05-16 Thread heron_carvalho


Hello,

  How can I redirect standard error output to a file in
GHC 5.02 ??

  Something like -odump flag in GHC 4.08 ...

Best Regards,
Heron de Carvalho





__
Quer ter seu próprio endereço na Internet?
Garanta já o seu e ainda ganhe cinco e-mails personalizados.
DomíniosBOL - http://dominios.bol.com.br


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



?? Redirecting standar error output ...

2002-05-16 Thread Heron




Hello,

 How can I redirect standard error output to 
a file in GHC 5.02 ?? 

 Something like -odump flag in GHC 4.08 
...

Best Regards,
Heron de Carvalho

 
__Heron 
CarvalhoMSc.ICQ#:117117637

  
  
Current ICQ status:
 
  + More ways to contact me i See more about 
me: 
__


online?icq=117117637=21
Description: Binary data


RE: efficiency of UArray

2002-05-16 Thread Hal Daume III

 GHC doesn't remove intermediate lists down both
 branches of a zip, so yes, you'll get intermediate lists.

Okay.

 Why not use array indexing, as per your second version
 (only in Haskell)?

something along the lines of:

f arr = f' low 0
where (low,high) = bounds arr
  f' pos acc | pos  high = acc
 | otherwise  = f' (pos+1) (acc + arr!pos)

?

would:

  sum [v!i + u!i | i - range (bounds v)]

also generate an intermediate list?

And finally, what about something like:

  f u v = listArray (bounds u) [v!i * u!i | i - range (bounds u)]

versus

  f u v = u // [(i, v!i*u!i) | i - range (bounds u)]

?

It's very unclear to me exactly what is going on behind the scenes with
arrays.  I would like to see functions like:

  afoldl, afoldr, azipWith, etc...

to be defined in the libraries, since there are so many possible
implementations and, it seems, the best implementation could be very
compiler dependent.  but barring this happening, what's the best approach
to take for things like this.  is // fast, or is it better to create new
arrays?

 - Hal

 | -Original Message-
 | From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
 | Sent: 16 May 2002 00:55
 | To: GHC Users Mailing List
 | Subject: efficiency of UArray
 | 
 | 
 | can we expect a function like:
 | 
 |   sum [x*y | (x,y) - zip (elems v) (elems u)]
 | 
 | to be as efficient as, say:
 | 
 | sum = 0
 | for i=1, n
 |   sum = sum + v[i] * u[i]
 | 
 | ?
 | 
 | Basically, will any intermediate lists be created here?
 | 
 | --
 | Hal Daume III
 | 
 |  Computer science is no more about computers| [EMAIL PROTECTED]
 |   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 | 
 | ___
 | Glasgow-haskell-users mailing list 
 | [EMAIL PROTECTED] 
 | http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
 | 
 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users