Re: Inlining errors...

2000-04-27 Thread Josef Sveningsson

On Wed, 19 Apr 2000, Jan-Willem Maessen wrote:

 I agree so wholeheartedly that I just write a (very!) short paper on
 the subject for ICFP (having discovered to my surprise that no such
 write-up existed).  It describes how to identify such expressions and
 hoist them out so they don't end up getting inlined.  It's still being
 refereed is thus likely to be revised, but if you're interested in a
 pre-print take a look (there are no pointers to it from elsewhere at
 the moment):
 
It's interesting reading. However, it seems to me that it would interact
badly with minimal typing derivations (mtd). Mtd is an algorithm for type
checking which computes the least general type instead of the most
general. This is used by some compilers to guide other optimisations. Some
optimisations, like certain representation analysises, do a better job on
less polymorphic code and therefore it is desirable to have less general
types.

Does ghc use mtd or some other heuristics to remove redundant
polymorphism?

/Josef

PS. Sorry for not having any pointers to mtd.





Minimal typing derivations and free theorems...

2000-04-27 Thread Jan-Willem Maessen

Josef Sveningsson [EMAIL PROTECTED] writes:
 It's interesting reading. However, it seems to me that it would interact
 badly with minimal typing derivations (mtd). Mtd is an algorithm for type
 checking which computes the least general type instead of the most
 general. This is used by some compilers to guide other optimisations.

My instinct is that any analysis which makes use of free theorems is
going to require a most general type.  This is because the free
theorems are based upon the most general type---and of course the more
polymorphism there is, the stronger the free theorems that can be
derived in general.  

That being said, I don't see any difficulty with using both kinds of
type information---the information we obtain with the two analyses is
different, and both types constrain program behavior in different
ways.  Mtd is unlikely to be useful for extracting bottoms, but there
is no reason bottom extraction should stop us from assigning a more
specific minimal type to an error-handling expression.

Actually, though, I wonder if mtd are useful at all for expressions
known to be bottom---this knowledge is an assertion that we need not
represent the value at all, and consequently seems strictly more
flexible than any representation we might choose by eliminating
polymorphism. 

The most important observation, really, is that we can still assign a
minimal type (like "Int") to a bottom expression, and thus that we
will not contaminate representation analysis or other mtd-based
optimizations.  And, in fact, its bottom-ness means we can assign such
a minimal type to each occurrence, so that the sharing of the bottom
expression need not introduce spurious polymorphism.

-Jan-Willem Maessen





ghc-4.06 installation -- libgmp.so.2?

2000-04-27 Thread Arthur H. Gold

I've been trying to install the last couple of ghc releases (from
various linux binaries). Installation itself goes OK, but ghc dies on
the lack of libgmp.so.2.

Unfortunately, the only libgmp releases I've seen build only a static
library.

Am I (no doubt) missing something?

Thanks,
--ag
-- 
Artie Gold, Austin, TX  (finger the cs.utexas.edu account for more info)
mailto:[EMAIL PROTECTED] or mailto:[EMAIL PROTECTED]
--
A: Look for a lawyer who speaks Aramaic...about trademark infringement.




Bcc: Re: ghc-4.06 installation -- libgmp.so.2?

2000-04-27 Thread Manuel M. T. Chakravarty


"Arthur H. Gold" [EMAIL PROTECTED] wrote,

 I've been trying to install the last couple of ghc releases (from
 various linux binaries). Installation itself goes OK, but ghc dies on
 the lack of libgmp.so.2.
 
 Unfortunately, the only libgmp releases I've seen build only a static
 library.
 
 Am I (no doubt) missing something?

Which distribution are you running?  If you use Red Hat,
just install the gmp-devel package that is on the binaries
CD.  Otherwise, a symbolic link from libgmp.so.2.x.y to
libgmp.so should also do the job.

Manuel





Re: State Monad operators accross different monads

2000-04-27 Thread Marcin 'Qrczak' Kowalczyk

Wed, 26 Apr 2000 23:49:43 -0700, Mike Jones [EMAIL PROTECTED] pisze:

 (||*):: Vi Bool - Vi Bool - Vi Bool
 b1 ||* b2 = do
   p - b1
   if p then return True else b2

The definition does not use anything specific to this particular monad.
The most general type that can be derived for this function is
(||*):: Monad m = m Bool - m Bool - m Bool

 Should I make a new class from Monad, say InstrumentMonad, define
 my state monads with it, then write:
 
 (||*):: (InstrumentMonad a) = a Bool - a Bool - a Bool

This would be needed if there was some operation used there that
applies to all InstrumentMonads, but only to them.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





Derived class problem

2000-04-27 Thread Mike Jones

All,

I am having a problem with a derived class. I define:

class (Monad m) = InstrumentMonad m where
yuck :: a - m a

Then I define:

instance InstrumentMonad Vi where  (Line 30)
return a = Vi (\s - (s, a))
Vi sf0 = f =
Vi $ \s0 - 
let
(s1, a1) = sf0 s0
Vi sf1 = f a1
(s2, a2) = sf1 s1
in (s2, a2)

And when I compile, I get the error:

Vi.hs:30:
No instance for `Monad Vi'
arising from an instance declaration at Vi.hs:30

Vi.hs:31: Class `InstrumentMonad' does not have a method `return'

Vi.hs:32: Class `InstrumentMonad' does not have a method `='

I am not sure what is going on here.

Mike





Derived class problem

2000-04-27 Thread Frank Atanassow

Mike Jones writes:
  I am having a problem with a derived class. I define:
  
  class (Monad m) = InstrumentMonad m where
   yuck :: a - m a
  
  Then I define:
  
  instance InstrumentMonad Vi where  (Line 30)
   return a = Vi (\s - (s, a))
   Vi sf0 = f =
   Vi $ \s0 - 
   let
   (s1, a1) = sf0 s0
   Vi sf1 = f a1
   (s2, a2) = sf1 s1
   in (s2, a2)
  
  And when I compile, I get the error:
  
  Vi.hs:30:
  No instance for `Monad Vi'
  arising from an instance declaration at Vi.hs:30
  
  Vi.hs:31: Class `InstrumentMonad' does not have a method `return'
  
  Vi.hs:32: Class `InstrumentMonad' does not have a method `='

You need to define the methods for class Monad (return, =) in an instance
for class Monad, and the methods for class InstrumentMonad (yuck) in an
instance for class InstrumentMonad.

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: Derived class problem

2000-04-27 Thread Marcin 'Qrczak' Kowalczyk

Thu, 27 Apr 2000 00:27:05 -0700, Mike Jones [EMAIL PROTECTED] pisze:

 class (Monad m) = InstrumentMonad m where
   yuck :: a - m a

This means that any type constructor that is an instance of Monad can
be made an instance of InstrumentMonad by providing the implementation
of yuck for this type constructor.

This implies that any InstrumentMonad is also a Monad, i.e. a context
(InstrumentMonad m, Monad m) will be simplified to (Monad m), and
that yuck :: InstrumentMonad m = a - m a, and that you specify
implementations of yuck for various type constuctors in InstrumentMonad
instances.

 instance InstrumentMonad Vi where  (Line 30)
   return a = Vi (\s - (s, a))
   Vi sf0 = f =

return and (=) are methods of Monad, not of InstrumentMonad.
They should be defined for Vi in instance Monad Vi.

In instance InstrumentMonad Vi a function yuck should be defined,
with type a - Vi a.

BTW. ghc-4.06 includes the module MonadState (requires -fglasgow-exts)
with a parametrized type constructor of state monads. It's enough to use
type Vi = State ViState
and you already have the Monad instance, with a couple of functions
to manage the state.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





doubly linked list

2000-04-27 Thread Jan Brosius



Hi,

I wonder if it is possible to simulate a doubly linked list in 
Haskell.

Friendly

Jan Brosius


Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

 I wonder if it is possible to simulate a doubly linked list in Haskell.

No need to simulate it... it's perfectly possible.  See my Wiki article.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: doubly linked list

2000-04-27 Thread Chris Okasaki

 I wonder if it is possible to simulate a doubly linked list in
 Haskell.

Depends on what you mean.  

  - Using mutable state in a monad you can implement a doubly 
linked list directly.
  - If you store all the nodes of the doubly linked list in
an array and simulate the pointers with indices into the
array, then you can easily implement this in Haskell using
some kind of extensible persistent array (probably some flavor 
of binary tree).  [Here you get a logarithmic slowdown
compared to ordinary doubly linked lists.]
  - If you want to be able to add/remove things from the front/back
plus be able to splice two lists together, see my implementation
of catenable deques (ICFP'97 or in my book).
  - If you also want to be able to have a "cursor" into the middle
of the list where you can make changes, you can implement this
as a pair of catenable deques, where the first deque represents
the part before the cursor and the second deque represents the
part after the cursor.
  - If you want to allow an arbitrary number of cursors, then
the simulation using an extensible persistent array is probably
your best bet.

Chris




Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

Herewith the comp.lang.functional version of my article.  I may have 
tidied it up a little for the Wiki; if so, those changes are lost.  Let 
it hereby enter the Haskell List archive!




The following message is a courtesy copy of an article
that has been posted as well.

Matti Nykanen [EMAIL PROTECTED] writes:

 I  recently came  across an  algorithm that  constructs a  binary tree
 using single _but  not immediate_ assignments. By this  I mean that it
 attaches a newly  created node into the existing  tree, but leaves the
 children of  the totally unspecified.  Later the  algorithm returns to
 fill in the missing pieces.
 
 I tried to  write it in Haskell,  but couldn't. If I create  a node, I
 have to give its children some  values to start with, and those cannot
 be changed later.  I don't think uniqueness types  (from, e.g., Clean)
 help here,  because the partially  constructed node is referred  to by
 two  places: its  parent in  the tree,  and the  "to do"  list  of the
 algorithm for the unfinished nodes.

The solution to this is a little trick called `tying the knot'.
Remember that Haskell is a lazy language.  A consequence of this is
that while you are building the node, you can set the children to the
final values straight away, even though you don't know them yet!  It
twists your brain a bit the first few times you do it, but it works
fine.

Here's an example (possibly topical!).  Say you want to build a
circular, doubly-linked list, given a standard Haskell list as input.
The back pointers are easy, but what about the forward ones?

data DList a = DLNode (DList a) a (DList a)

mkDList :: [a] - DList a

mkDList [] = error "must have at least one element"
mkDList xs = let (first,last) = go last xs first
 in  first

  where go :: DList a - [a] - DList a - (DList a, DList a)
go prev [] next = (next,prev)
go prev (x:xs) next = let this= DLNode prev x rest
  (rest,last) = go this xs next
  in  (this,last)

takeF :: Integer - DList a - [a]
takeF 0 _ = []
takeF (n+1) (DLNode _ x next) = x : (takeF n next)

takeR :: Show a = Integer - DList a - [a]
takeR 0 _ = []
takeR (n+1) (DLNode prev x _) = x : (takeR n prev)


(takeF and takeR are simply to let you look at the results of mkDList:
they take a specified number of elements, either forward or backward).

The trickery takes place in `go'.  `go' builds a segment of the list,
given a pointer to the node off to the left of the segment and off to
the right.  Look at the second case of `go'.  We build the first node
of the segment, using the given prev pointer for the left link, and
the node pointer we are *about* to compute in the next step for the
right link.

This goes on right the way through the segment.  But how do we manage
to create a *circular* list this way?  How can we know right at the
beginning what the pointer to the end of the list will be?

Take a look at mkDList.  Here, we simply take the (first,last)
pointers we get from `go', and *pass them back in* as the next and
prev pointers respectively, thus tying the knot.  This all works
because of lazy evaluation.

Hope this helps.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:



-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::





updating file

2000-04-27 Thread Jan Skibinski


Since we are in a mood for puzzles today ..

How to update file "xxx" without
making backup "yyy" first, as in:

readFile  "xxx" =
writeFile "yyy" =
readFile  "yyy" =
process =
writeFile "xxx"
?

Jan Skibinski






Re: updating file

2000-04-27 Thread Ralf Krueger

On Thu, 27 Apr 2000 Jan Skibinski wrote:
 Since we are in a mood for puzzles today ..
 
   How to update file "xxx" without
   making backup "yyy" first, as in:
 
   readFile  "xxx" =
   writeFile "yyy" =
   readFile  "yyy" =
   process =
   writeFile "xxx"
   ?

I think, the problem can be solved by using the IO library and some strictness:

 import IO

 main = do text - readFile "xxx"
   text' - process $! text
   file - openFile "xxx" WriteMode
   hPutStr file text'
   hClose file

seems to work. The file will be read completly befor it is re-opened for
writing.

Ralf Krueger


-- 
0-0 In nur vier Zeilen was zu sagen
|[EMAIL PROTECTED]| erscheint zwar leicht, doch es ist schwer.
|[EMAIL PROTECTED]| Man braucht ja nur mal nachzuschlagen:
0-0 Die meisten Dichter brauchen mehr. (H. E.)




Re: updating file

2000-04-27 Thread Sven Panne

Ralf Krueger wrote:
 I think, the problem can be solved by using the IO library and some
 strictness:
 
  import IO
 
  main = do text - readFile "xxx"
text' - process $! text
file - openFile "xxx" WriteMode
hPutStr file text'
hClose file
 
 seems to work. The file will be read completly befor it is
 re-opened for writing.

Without trying it for myself, I have some doubts about the above code.
IIRC ($!) evaluates its second argument only to WHNF, i.e. only until
the toplevel constructor ((:) or [] in the case of lists) is known.
Perhaps you had luck because the files were short enough to fit into
the buffer of the underlying IO system. A more promising way is
probably:

   main = readFile "xxx" = hyper = process = writeFile "xxx"

   -- hack for hyperstrictness
   hyper txt | length txt = 0 = return txt
 | otherwise   = error "never happens"

And using hGetBuf{,BA}Full from GHC's upcoming IOExts module would be
a completely different way.

-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne




Re: updating file

2000-04-27 Thread Jan Skibinski


Ralf and Sven:

Thank you both for your answers. I knew that strictness
was needed here, but I was seeking some elegant solution.
I prefer your answer, Sven, a bit more. Could you elaborate
on your `hack' a bit more? It seems to be a good topic for
"how to be strict".

Your dressed up, reusable version is attached below.
Jan


updateFile :: FilePath - (String - IO String) - IO ()
updateFile file process
--
-- `process' content of `file'
-- and update it in place
--  
= readFile file  =
  hyperHack  =
  process=
  writeFile file
  where
  hyperHack txt
  | length txt = 0 = return txt
  | otherwise   = error "never happens" 

---






Re: updating file

2000-04-27 Thread Marcin 'Qrczak' Kowalczyk

Thu, 27 Apr 2000 19:20:57 +0200, Ralf Krueger [EMAIL PROTECTED] 
pisze:

  main = do text - readFile "xxx"
text' - process $! text

$! will usually not suffice, because it forces only the beginning of
the list.

"foldr seq (return ()) text" should suffice.

Or use a GHC extension: IO.slurpFile.

IMHO lazy readFile, or possibly hGetContents only, should really be
improved to behave sanely when e.g. the file gets hClosed. Laziness
should not change any result except to turn some bottoms into other
values. This is about the only place in standard Haskell when laziness
can bite in some other way than causing poor performance.

Unless we are talking about unsafe extensions, which OTOH are very
useful too. Sometimes eliminating unsafePerformIO would require
huge rewrite of the whole program, making it less readable and less
efficient. But they should be clearly marked as unsafe. The safe
sublanguage should behave safely.

It is not obvious how to fix hGetContents. I might want to do one of
two things before closing the file:
- read the remaining part of the file now,
- discard the remaining part of the file,
and it could be bad to rely on the garbage collection to distinguish
between them (i.e. to determine whether the file contents will
be still needed).

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





Re: updating file

2000-04-27 Thread Jan Skibinski



On 27 Apr 2000, Marcin 'Qrczak' Kowalczyk wrote:

 Unless we are talking about unsafe extensions, which OTOH are very
 useful too. Sometimes eliminating unsafePerformIO would require
 huge rewrite of the whole program, making it less readable and less
 efficient. But they should be clearly marked as unsafe. The safe
 sublanguage should behave safely.

Changing a course a little bit to describe some dangers
related to usage of `unsafePerformIO'

I am not very proud of what I did, but I will tell this
story anyway, hoping that someone can learn from my mistake.
"Unsafe perform" is just what it says :-)

When writing DateTime module few days ago I stupidly
entered this line of code, without even thinking about
its signature:

currentSecond = second $ unsafePerformIO localDateTime

where `localDateTime' has been defined via primitive
call to C:

localDateTime :: IO DateTime

To my distress the clock stopped after the first call to
`currentSecond'. I took me much more than just few seconds
to realize that the problem was not related to any
bug in the C code, but in the signature of
`currentSecond':

currentSecond :: Int

This is all fine and dandy if `currentSecond' is within `where'
clause, because it will be always evaluated afresh.
But being a top level function, as it was, it was always 
reporting a cached value. This all relates to the yesterday's
subject "openFile :: String - String" but it is even more
spectacular in its side effect. Try to beat this!

Jan

  






Re: doubly linked list

2000-04-27 Thread Jan Brosius


- Original Message - 
From: Chris Okasaki [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Sent: Thursday, April 27, 2000 4:13 PM
Subject: Re: doubly linked list


  I wonder if it is possible to simulate a doubly linked list in
  Haskell.
 
 Depends on what you mean.  
 
   - Using mutable state in a monad you can implement a doubly 
 linked list directly.

please show me how to implement using mutable state in
a monad

Friendly
Jan Brosius





Re: updating file

2000-04-27 Thread Fergus Henderson

On 27-Apr-2000, Jan Skibinski [EMAIL PROTECTED] wrote:
 
   currentSecond = second $ unsafePerformIO localDateTime
 
   where `localDateTime' has been defined via primitive
   call to C:
   
   localDateTime :: IO DateTime
 
   To my distress the clock stopped after the first call to
   `currentSecond'. I took me much more than just few seconds
   to realize that the problem was not related to any
   bug in the C code, but in the signature of
   `currentSecond':
 
   currentSecond :: Int
 
   This is all fine and dandy if `currentSecond' is within `where'
   clause, because it will be always evaluated afresh.

It might happen to work with current Haskell implementations,
but I don't think there's any guarantee of that.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.