unsafePerformIO to give warnings

2001-12-20 Thread Ian Lynagh


Hi all

If I want to give warnings when doing something and I don't care too
much about the order they appear in, can I use this?

foo x = if success x then Just x
 else warn "Working out x went wrong" Nothing

warn :: String -> a -> a
warn s x = unsafePerformIO (hPutStrLn stderr s) `seq` x

The hslibs docs say

If the I/O computation wrapped in unsafePerformIO performs side
effects, then the relative order in which those side effects take
place (relative to the main I/O trunk, or other calls to
unsafePerformIO) is indeterminate.

but it's not entirely clear on whether or not I could end up with 2
warnings interspersed?

And is it guaranteed that the warnings will be printed at some point?
hugs and ghci only seem to print the first warning, but ISTR similar
problems happen with threads and got the impression that they were in
the wrong.


Thanks
Ian


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



installation problems with graphics-2.0.4

2001-12-20 Thread Bernhard Reus

The graphics lib of the new December release does not
compile with the shipped makefile.
The makefile does not do anything at all???
Maybe there is a problem with wildcard extensions?

To be honest, I have no clue. I am using a Sparc5/Solaris
machine.
Any help appreciated.

Thanks in advance,

  Bernhard

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



Working Conference on Generic Programming, 2nd call for papers

2001-12-20 Thread Johan Jeuring

  WCGP '02

IFIP WG2.1 Working Conference on

GENERIC PROGRAMMING
  
   http://www.generic-programming.nl/wcgp/cfp.html

 Organised in conjunction with MPC'02

July  8 - July 13, 2002

 Dagstuhl, Germany


  CALL FOR PAPERS

Generic programming is about making programs more 
adaptable by making them more general. Generic 
programs often embody non-traditional kinds of 
polymorphism; ordinary programs are obtained from 
them by suitably instantiating their parameters. 
In contrast with normal programs, the parameters 
of a generic programs are often quite rich in 
structure. For example they may be other programs, 
types or type constructors, class hierarchies, or 
even programming paradigms. 

Generic programming techniques have always been of 
interest, both to practitioners and to theoreticians, 
but only recently have generic programming 
techniques become a specific focus of research in 
the functional and object-oriented programming 
language communities. This working conference will 
bring together leading researchers in generic 
programming from around the world, and feature 
papers capturing the state of the art in this 
important emerging area. 

We welcome contributions on all aspects, theoretical 
as well as practical, of generic programming, 
aspect-oriented programming, polytypic programming, 
adaptive object-oriented programming, generic 
components, and so on. 


SUBMISSION

Full papers should be submitted in Postscript or pdf 
format by e-mail to reach [EMAIL PROTECTED] 
by February 16, 2002. The details of the submission 
procedure can be found at


http://www.generic-programming.nl/wcgp/submit.html

Although there is no page limit, submissions should 
strive for brevity and clarity. 


  IMPORTANT DATES

Submission   February 16, 2002
Notification April 12,2002
Final version dueMay 24,  2002


PROGRAMME COMMITTEE

Matt Austern 
Eerke Boiten
Ulrich Eisenecker 
Jeremy Gibbons (co-chair)
Ralf Hinze 
Johan Jeuring (co-chair)
Gary Leavens 
Karl Lieberherr 
Lambert Meertens 
Eugenio Moggi 
Bernhard Moeller
Oege de Moor 
David Musser 
Martin Odersky 
Ross Paterson
Simon Peyton Jones
Colin Runciman
Doaitse Swierstra
Stephanie Weirich


  LOCAL ORGANISATION

Jeremy Gibbons
Johan Jeuring
Bernhard Moeller

   CORRESPONDENCE
  
Jeremy Gibbons ([EMAIL PROTECTED])
Johan Jeuring  ([EMAIL PROTECTED])



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



Re: global counters

2001-12-20 Thread Jan de Wit


> basically, i want a function getVar :: () -> String which returns a new
> string every time.  i tried this:
>
> > curVarId = newSTRef (0 :: Integer)
> >
> > {-# NO-INLINE newVar -}
> >
> > newVar = \_ -> ('\0' : show x)
> > where y = unsafePerformIO (stToIO curVarId)
> >   x = unsafePerformIO $ stToIO $
> >   do x <- readSTRef y
> >  writeSTRef y (x + 1)
> >  return x
>
> and in ghci it works wonderfully, but when i actually compile, all i get
> is "\NUL0".
>
> what's the proper way to write this?

I think (haven't tested this one) you should write (modulo layout):
| curVarIdRef :: IORef Integer
| curVarIdRef = unsafePerformIO $ newIORef (0 :: Integer)
|
| {-# NO-INLINE newVar -}
|
| newVar :: () -> String
| newVar = \_ -> ('\0' : show x) where
|   x = unsafePerformIO $
| do x <- readIORef curVarIdRef
|   writeIORef curVarIdRef (x + 1)
|   return x

Because in your original version, curVarId allocates a new reference to 0
every time newVar is called.

Hope this works, Jan de Wit





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



x^y. Reply

2001-12-20 Thread S.D.Mechveliani

Toralf Wittner <[EMAIL PROTECTED]>

writes

> [..]
> data PowerNum = INT Integer | DBL Double deriving (Eq, Show, Read)
> [..]
> Now it basically works. However wouldn't it have been easier to write  
> something like this:
> 
> powPos :: Integer -> Integer -> Integer
> [..]
> powNeg :: Integer -> Integer -> Double
> [..]
>   | y <  0= 1 / fromInteger x * powNeg x (y + 1)
>
> Initially I wanted something as terse as the Python version, now I either 
> have to write two functions or I need to define a type. Is there not an 
> easier way to come as close as possible to the Python version?
>
> Thanks anyway - learnt a lot!


For this particular task, the most natural solution is, probably,   

  pow :: Fractional a => a -> Integer -> a
  pow a n = 
   if n > 0 then a^n  else (1/a)^(- n)

(^) is of standard, only  pow  adds the facility of negative n.

Then, you need each time to convert the argument to appropriate
type of Fractional: 

   pow (fromInteger 2 :: Ratio.Rational) 2 --> 4 % 1
   pow (fromInteger 2 :: Ratio.Rational) (-2)  --> 1 % 4
   pow (2 :: Double) (-2)  --> 0.25
   pow (2 :: Integer) (-2) -->
   ... No instance for (Fractional Integer)

If you replace standard (and not lucky)  Fractional  with some 
class  Foo  (with multiplication  mul  and  division  div), 
make  Integer  an instance of  Foo  
(where  div  may fail for some data),
and program 
  pow :: Foo a => a -> Integer -> a
via  mul, div,
then it would work like this:

  pow (2 :: Integer)  2--> 4
  pow (2 :: Integer)  (-2) --> "Error: cannot invert 2 :: Integer"
  pow (2 :: Rational) (-2) --> 1%4

Another way is to try to straggle with overlapping instances by
defining something like this:

  class Pow a b where pow :: a -> Integer -> b

  instance Num a => Pow a a   where  pow = (^)
   Fractional ? 
  instance Num a => Pow Integer a where  pow = ?

If this succeeds, there will be also no need in new type 
constructors.

-
Serge Mechveliani
[EMAIL PROTECTED]





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