freezeSTArray not found

1997-12-01 Thread Byron Cook

hi,

as far as I can tell "freezeSTArray" doesn't appear in the modules
LazyST/ST.

it appears in the documentation
(http://www.dcs.gla.ac.uk/fp/software/ghc/2.09/users_guide/user_102.html#SEC102)
and also in Hug's LazyST/ST modules


cheers,  :-)
byron




Re: runST and LazyST don't mix -- ghc-2.09

1997-12-01 Thread Simon Marlow

Byron Cook [EMAIL PROTECTED] writes:

 in ghc-2.09 (solaris) i cannot use runST with LazyST
 observe:

 $ cat lazy.hs
 import LazyST
 main = print $ f True
 
 f x = runST(
   do n - newSTRef x
  readSTRef n
   )

Yes: GHC's LazyST doesn't define runST at the moment (I should have
documented this deficiency, sorry about that).  For now, you can do it
like this:

import LazyST
import ST (runST)
main = print $ f True

f x = runST (lazyToStrictST (
  do n - newSTRef x
 readSTRef n
  ))

I make no claims about the LazyST stuff: it hasn't been thoroughly
tested by any means.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: freezeSTArray not found

1997-12-01 Thread Simon Marlow

Byron Cook [EMAIL PROTECTED] writes:

 as far as I can tell "freezeSTArray" doesn't appear in the modules
 LazyST/ST.
 
 it appears in the documentation
 (http://www.dcs.gla.ac.uk/fp/software/ghc/2.09/users_guide/user_102.html#SEC102)
 and also in Hug's LazyST/ST modules

Patch follows

*** ST.lhs  1997/11/24 15:43:22 1.9
--- ST.lhs  1997/12/01 17:17:21
***
*** 22,28 
newSTRef, readSTRef, writeSTRef,
  
STArray,
!   newSTArray, readSTArray, writeSTArray, Ix
  
  ) where
  
--- 22,30 
newSTRef, readSTRef, writeSTRef,
  
STArray,
!   newSTArray, readSTArray, writeSTArray, boundsSTArray, 
!   thawSTArray, freezeSTArray, unsafeFreezeSTArray, 
!   Ix
  
  ) where

*** LazyST.lhs  1997/11/24 17:45:57 1.2
--- LazyST.lhs  1997/12/01 17:19:04
***
*** 20,27 
ST.STRef,
newSTRef, readSTRef, writeSTRef,
  
!   ST.STArray,
!   newSTArray, readSTArray, writeSTArray, Ix,
  
strictToLazyST, lazyToStrictST
  ) where
--- 20,29 
ST.STRef,
newSTRef, readSTRef, writeSTRef,
  
!   STArray,
!   newSTArray, readSTArray, writeSTArray, boundsSTArray, 
!   thawSTArray, freezeSTArray, unsafeFreezeSTArray, 
!   Ix,
  
strictToLazyST, lazyToStrictST
  ) where

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: runST and LazyST don't mix -- ghc-2.09

1997-12-01 Thread Simon Marlow

Byron Cook [EMAIL PROTECTED] writes:

 that didn't quite work --- it gave a type error.  

Bizarre... it worked for me.  Did you get the indentation right when
you cut 'n' pasted it? :-)

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: runST and LazyST don't mix -- ghc-2.09

1997-12-01 Thread Simon Marlow

Byron Cook [EMAIL PROTECTED] writes:

 i tried your solution on the function "f" used in earlier mesgs and got
 the same problem:
 paratha% ghc lazy.hs
  
 lazy.hs:6: Couldn't match the type `ST' against `ST'
 Expected: `ST taMI taML'
 Inferred: `ST taN9 taMu'

This really means: 

lazy.hs:6: Couldn't match the type `LazyST.ST' against `ST.ST'
Expected: `LazyST.ST taMI taML'
Inferred: `ST.ST taN9 taMu'

(i.e. one example of why it's not always a good idea to print
unqualified Id's  in the type error :-)

Anyway, the type of LazyST differs from ST, so you can't mix them
without using lazyToStrictST and strictToLazyST.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: runST and LazyST don't mix -- ghc-2.09

1997-12-01 Thread Byron Cook

sorry, i should clarify.  i'm not using the little "f x" function
refered to in earlier mesgs.

i got this error mesg:
SignalArray.hs:78: Couldn't match the type `ST' against `ST'
Expected: `ST ta1tm [[ArrResp ta1m9 ta1ma]]'
Inferred: `ST ta1yp [[ArrResp ta1m9 ta1ma]]'
In the first argument of `runST', namely
`(do
arr - newSTArray bounds initVal
initArray arr
performRequests arr)'
In the second argument of `$', namely
`runST (do
  arr - newSTArray bounds initVal
  initArray arr
  performRequests arr)'
In an equation for function `stateArray':
`stateArray ((bounds@(loBound, hiBound)), initWrites) (Sig reqss)
= Sig
  $ (runST (do...


when compiling this rather long and ugly attached below.

however, lazyToStrictST, did the trick.  
--
module SignalArray
  (
 stateArray
,updateArray
,ArrayDesc
,ArrReq(..)
,ArrResp(..)
  ) where

import Array
import Signal
import LazyST 
import ST(runST)
import BasicTypes

-- Begin Signature 
stateArray  :: (Enum a, Ix a) = ArrayDesc a b - Signal [ArrReq a b] - 
Signal [ArrResp a b]

updateArray :: Ix a =
  Signal (Array a b) -
  [(Signal Bool,(Signal a,Signal b))] -
  Signal (Array a b)

-- End Signature 



-- Updates an array Signal, given a static list of updaters. Each
--  updater consists of a Boolean enable signal, and a signal pair
--  of the update address and update value.
updateArray arr updaters
  = foldr (\(updateEnable,updater) prevArray -
if' updateEnable 
   then' (lift2 (//) prevArray (singleton (bundle updater)))
   else' prevArray)
  arr
  updaters
where singleton = lift1 $ \x - [x]


 Array implemented with lazy state -

-- Info needed to initialize a stateful array.
--  the list of tuples denotes what the various array subranges
--  should be initialized to.
--type ArrayDesc index val = ((index,index),[(index,index,val)])

-- Array request
data ArrReq i a  = ReadArr i |
   WriteArr i i a |
   WriteFn i (a - a) | -- modify contents at location i
   FreezeArr
   deriving Show

-- Array response
data ArrResp i a = ReadVal a |
   Written |
   WrittenFn a |
   ArrayVal (Array i a)
   deriving Show

{-
stateArray :: (Ix i, Enum i) =
ArrayDesc i a   -- array initialization info
-
Signal [ArrReq i a] -- array requests to read
--  and write values from/to
--  the array.
-
Signal [ArrResp i a]-- array responses corresponding
--  to ReadArr and FreezeArr
--  requests.
-}
stateArray (bounds@(loBound,hiBound),initWrites) (Sig reqss)
  = Sig $ runST (
do arr - newSTArray bounds initVal
   initArray arr
   performRequests arr)
where
  -- Determine what the array should be initialized to; remove
  --  some of the writes that would initialize the array to the
  --  same value to speed up the initialization process.
  contigWrites = contigWriteRanges 
  (loBound,hiBound,
   error "uninitialized value read from stateArray") 
  initWrites
  maxRange@(_,_,initVal) = maxWriteRange contigWrites
  reducedInitWrites = removeWriteRange maxRange contigWrites


  -- Initialize the array according to 'initWrites'
  initArray arr
= strictSequence [ writeSTArray arr index val |
(lowIdx,hiIdx,val) - reducedInitWrites,
index - range (lowIdx,hiIdx) ]

  --accumulate   :: Monad m = [m a] - m [a]
  accumulate [] = return []
  accumulate (c:cs) = do x - c
 xs - (accumulate cs) 
 return (x:xs)

  -- Perform the requested writes, reads, and freezes for each clock cycle
  performRequests arr
= accumulate $ map performReqs reqss
  where
performReqs reqs
  = mapM performReq reqs

performReq (ReadArr i)
  = do val - readSTArray arr i
   return (ReadVal val)

performReq (WriteArr loAddr hiAddr val)
  = do sequence [ writeSTArray arr loc val |
 

2.09: cygwin32 binary distrib available

1997-12-01 Thread Sigbjorn Finne


A 2.09 binary bundle for cygwin32 (x86) is now available via
the ghc download page,

  http://www.dcs.gla.ac.uk/fp/software/ghc/download.html

NOTE: Its huge (~12M), as it contains sequential, profiled, concurrent
and prof-conc libs.

--Sigbjorn



Re: Problem with assembler on Digital UNIX

1997-12-01 Thread Alex Ferguson


Hi, Alex.  Your problem sounds not entirely dissimiliar to one I
encountered with ghc-2.08 on Digital UNIX V4.0B, though I'm not sure
it's exactly the same -- see ghc-bugs, _passim_. ;-)

 Anyway, we are now trying to compile the GHC with -fvia-C.

That's what worked for me.  In fact, I only had to compile one module
by this route (the one producing the as error...), the rest went fine.

Good luck,
Alex.



Re: GHC-2.09 documentation buglet

1997-12-01 Thread Alessandro Vernet

Sven Panne wrote:
 
 The compilation of 2.09 went quite smoothly, there were only two minor
 obstacles:
 
* During the compilation of the libraries, ghc made some segmentation
  faults. But this happened only a few times and only on Linux. As I
  can't seem to reproduce this, I think it's safe to forget it...

I also think so. I compiled on a Linux system GHC 2.09 using GHC 2.09
yersterday without any problem. Congratulations to the GHC development
team!

Alex

-- 
+---+--+
| Alessandro VERNET | email: [EMAIL PROTECTED] or [EMAIL PROTECTED]|
| Longeraie 3   | ProOnline Central Mail System. Non profit org.   |
| CH-1006 Lausanne  | WWW pages: http://www.scdi.org/~avernet/ |
+---+--+



Re: Problem with assembler on Digital UNIX

1997-12-01 Thread Sigbjorn Finne


Alessandro Vernet writes:
 We are trying to compile GHC 2.09 on our Digital UNIX 4.0b systems. We
 had no problem with GHC itself, but rather with the Digital assembler.
 When compiling "huge" files, our assembler crashes with a segmentation
 fault. We could solve this problem by spliting one "huge" Haskell file
 into two files, however this process is somewhat painfull. Had someone
 here already this problem (and possibly solved it)?
 

Hi,

haven't got Digital UNIX 4.0 here, so no first hand experiences to
pass on, I'm afraid. A couple of suggestions that might be of some
help:

- It looks like you're running up against a limit of some sort. If
  it's swap/tmp space (unlikely, since ghc operates ok), setting
  TMPDIR to something other than the default might help.
- If the .s file was produced with ghc's native code generator (the
  default), try going the via C route, i.e., compile with -fvia-C
- GNU as?

--Sigbjorn



Re: bug report

1997-12-01 Thread Alex Ferguson


 Did you do 'make install' in ghc, instead of using the binary
 distribution?

I did make install from a build from source, yes, not least as there was
no binary distrib. available  at that point. ;-)

 Hard links are a pain for several reasons - if you install a new ghc
 over the existing one, you have to be sure to remove the old one
 first, or you might stomp on the ghc-2.09 link too...

Having created such links by hand, I can report that the install
script doesn't appear to thusly stomp.  I guess it'd do so if it
changed the file contents, rather than the handle, but don't quote
me on the details of this, as I haven't investigated the details of
what the script does...

Either hard or symbolic is fine by me, mind you.

Cheers,
Alex.



runST and LazyST don't mix -- ghc-2.09

1997-12-01 Thread Byron Cook

hi, 

in ghc-2.09 (solaris) i cannot use runST with LazyST
observe:

-
STRICT
$ ghc strict.hs
ghc: module version changed to 1; reason: no old .hi file
paratha$ cat strict.hs
import ST
main = print $ f True

f x = runST(
  do n - newSTRef x
 readSTRef n
  )
-
LAZY
$ ghc lazy.hs
 
lazy.hs:7: Value not in scope: `runST'

Compilation had errors


$ cat lazy.hs
import LazyST
main = print $ f True

f x = runST(
  do n - newSTRef x
 readSTRef n
  )



byron




Re: bug report

1997-12-01 Thread Simon Marlow

Alex Ferguson [EMAIL PROTECTED] writes:

  Did you do 'make install' in ghc, instead of using the binary
  distribution?
 
 I did make install from a build from source, yes, not least as there was
 no binary distrib. available  at that point. ;-)

Right - it's a bug that the link isn't installed from the build tree
when doing 'make install'.  Will fix.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Problem with assembler on Digital UNIX

1997-12-01 Thread Alessandro Vernet

We are trying to compile GHC 2.09 on our Digital UNIX 4.0b systems. We
had no problem with GHC itself, but rather with the Digital assembler.
When compiling "huge" files, our assembler crashes with a segmentation
fault. We could solve this problem by spliting one "huge" Haskell file
into two files, however this process is somewhat painfull. Had someone
here already this problem (and possibly solved it)?

Alex

-- 
+---+--+
| Alessandro VERNET | email: [EMAIL PROTECTED] or [EMAIL PROTECTED]|
| Longeraie 3   | ProOnline Central Mail System. Non profit org.   |
| CH-1006 Lausanne  | WWW pages: http://www.scdi.org/~avernet/ |
+---+--+



compiling from src error: FastString interface file

1997-12-01 Thread Byron Cook

when compiling 2.09 from src on "SunOS lassi 5.5.1 Generic_103640-03 sun4u
sparc SUNW,Ultra-1" I encountered the following error mesg after executing
the command (./configure;gmake boot;gmake)

.
.
.
.
.
ghc-0.29 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen
-Iparser -iutils:b
asicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:st
ranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
-fhaskell
-1.3 -fomit-derived-read -fomit-reexported-instances   -fvia-C
'-#include"hspincl.h"'
 -c parser/U_binding.hs -o parser/U_binding.o -osuf o
"parser/U_binding.hs", line 6, column 22: can't find interface (.hi) file
for module "
FastString" on input: "FastString"
gmake[2]: *** [parser/U_binding.o] Error 1



byron




Re: compiling from src error: FastString interface file

1997-12-01 Thread Sigbjorn Finne


Byron Cook writes:
 when compiling 2.09 from src on "SunOS lassi 5.5.1 Generic_103640-03 sun4u
 sparc SUNW,Ultra-1" I encountered the following error mesg after executing
 the command (./configure;gmake boot;gmake)
 
 ghc-0.29 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen
 -Iparser -iutils:b
 
asicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:st
 ranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
 -fhaskell
 -1.3 -fomit-derived-read -fomit-reexported-instances   -fvia-C
 '-#include"hspincl.h"'
  -c parser/U_binding.hs -o parser/U_binding.o -osuf o
 "parser/U_binding.hs", line 6, column 22: can't find interface (.hi) file
 for module "
 FastString" on input: "FastString"
 gmake[2]: *** [parser/U_binding.o] Error 1
 

If parser/U_binding.hs is the first file you're compiling inside
ghc/compiler, then the above failure is likely to be due to 'make
boot' in ghc/compiler not completing successfully. Could you check this?

--Sigbjorn



Re: compiling from src error: FastString interface file

1997-12-01 Thread Byron Cook

oops, you;re quite right.  i fell for the same bug as in "Compiling from
source does not work" from the mailing list archive.  

this was in the gmake boot output
../../happy/src/happy +RTS -K2m -H10m -RTS -1.2-g rename/ParseIface.y
gmake[2]: execve: ../../happy/src/happy: No such file or directory
gmake[2]: *** [rename/ParseIface.hs] Error 127

cheers


byron

On Mon, 1 Dec 1997, Sigbjorn Finne wrote:

 
 Byron Cook writes:
  when compiling 2.09 from src on "SunOS lassi 5.5.1 Generic_103640-03 sun4u
  sparc SUNW,Ultra-1" I encountered the following error mesg after executing
  the command (./configure;gmake boot;gmake)
  
  ghc-0.29 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen
  -Iparser -iutils:b
  
asicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:st
  ranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
  -fhaskell
  -1.3 -fomit-derived-read -fomit-reexported-instances   -fvia-C
  '-#include"hspincl.h"'
   -c parser/U_binding.hs -o parser/U_binding.o -osuf o
  "parser/U_binding.hs", line 6, column 22: can't find interface (.hi) file
  for module "
  FastString" on input: "FastString"
  gmake[2]: *** [parser/U_binding.o] Error 1
  
 
 If parser/U_binding.hs is the first file you're compiling inside
 ghc/compiler, then the above failure is likely to be due to 'make
 boot' in ghc/compiler not completing successfully. Could you check this?
 
 --Sigbjorn