using perl version 5 now?

1998-12-02 Thread Byron Cook

when i installed the binary version of ghc-4.00 i recieved the following 
error mesg. when trying to run the compiler:

lassi$ ghc-4.00
syntax error in file ./ghc-4.00 at line 2540, next token "["
syntax error in file ./ghc-4.00 at line 2658, next 2 tokens "exists
$Supported_syslibs"
syntax error in file ./ghc-4.00 at line 2662, next 2 tokens "}"
..


changed the line  #!/usr/local/bin/perl to #!/usr/local/bin/perl5
seems to have fixed the problem.  has GHC now begun assuming Perl version
5?

I know very little about perl, but is "perl5" a common executable name for
perl version 5.  if so, perhaps GHC should be more specific about the
version of perl it needs.  

- Byron




No instance for `Eq (c r w)' when deriving classes for `Trans'

1998-11-21 Thread Byron Cook

Here is some code that works well in the Hugs 98 BETA, but not in
GHC-4.00:

data Trans c i r w = Trans [c r w] i [c r w] [c r w]
   deriving (Eq,Show)


GHC complains:
Trans.hs:1:
No instance for `Eq (c r w)'
When deriving classes for `Trans'


Hugs merrily works on the same code:
Trans Trans [Reg R (Val (5::Word32))] () [] [] == Trans [Reg R (Val (5::Word32))] () 
[] []
True
Trans 



- Byron




Hugs bug --- perhaps

1998-11-21 Thread Byron Cook

I've mailed to hugs-bugs, but their mailing list appears to be acting up.

Really this is a Hugs/GHC difference with the Word library.

In GHC Word64 is an instance of Num, in Hugs (as of Hugs-98) it is
not.

- Byron




binary release of 3.x?

1998-04-30 Thread Byron Cook

Does anyone have a projected date for a GHC 3.x binary release?

:-)


byron




GHC-3.0 link error on HP

1998-02-18 Thread Byron Cook

Hi, 

im getting the following link error on an HP (uname -a = HP-UX dtthp237
B.10.01 A 9000/770 2009624264 two-user license)

/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in Env.o and AbsHLSpec.o. This
may not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in ExceptionM.o and Env.o. This
may not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in NameM.o and Env.o. This may
not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in ParseL.o and Env.o. This may
not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in Parser.o and Env.o. This may
not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "PerformGC_wrapper" of incompatible
types (such as CODE and DATA) were found in PrettyL.o and Env.o. This may
not be supported in future releases.
/usr/ucb/ld: (Warning) Symbols named "Ind_info" of incompatible types
(such as CODE and DATA) were found in
/idl/strategic/fv2/hlspec/ghc-3.0/lib/ghc-3.00/libHS.a(PrelBase__3.o) and
AbsSpec.o. This may not be supported in future releases.
/usr/ucb/ld: Unsatisfied symbols:
   PerformGC_wrapper (data)
   Ind_info (data)
collect2: ld returned 1 exit status

when i try to link ghc .o files with the command:
ghc -o prog *.o

any suggestions?




still no happy

1998-01-28 Thread Byron Cook

in my on-going drama to build happy, i can successfully gmake boot and
gmake, but when ghc-0.29 tries to build the executable its missing a few
symbols:
ghc-0.29 -o happy.bin -cpp -fhaskell-1.3 -fglasgow-extsVersion.o
GenUtils.o Set.o ParseMonad.o Lexer.o AbsSyn.o Grammar.o Parser.o First.o
LALR.o Target.o ProduceCode.o Info.o GetOpt.o Main.o
/usr/ucb/ld: Unsatisfied symbols:
   PerformGC_wrapper (data)
   Ind_info (data


  any ideas?


ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Version.hs -o Version.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c GenUtils.lhs -o
GenUtils.o -osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Set.lhs -o Set.o -osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c ParseMonad.lhs -o
ParseMonad.o -osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Lexer.lhs -o Lexer.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c AbsSyn.lhs -o AbsSyn.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Grammar.lhs -o Grammar.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts   -Onot  -c Parser.hs -o
Parser.o -osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c First.lhs -o First.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c LALR.lhs -o LALR.o -osuf
o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Target.lhs -o Target.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c ProduceCode.lhs -o
ProduceCode.o -osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Info.lhs -o Info.o -osuf
o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c GetOpt.lhs -o GetOpt.o
-osuf o
ghc-0.29 -cpp -fhaskell-1.3 -fglasgow-exts -c Main.lhs -o Main.o -osuf
o
"Main.lhs", line 93: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 111: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 112: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 113: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 114: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 116: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 117: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 118: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 119: _scc_ (`set [profiling] cost centre') ignored
"Main.lhs", line 120: _scc_ (`set [profiling] cost centre') ignored
ghc-0.29 -o happy.bin -cpp -fhaskell-1.3 -fglasgow-extsVersion.o
GenUtils.o Set.o ParseMonad.o Lexer.o AbsSyn.o Grammar.o Parser.o First.o
LALR.o Target.o ProduceCode.o Info.o GetOpt.o Main.o 
/usr/ucb/ld: Unsatisfied symbols:
   PerformGC_wrapper (data)
   Ind_info (data)
collect2: ld returned 1 exit status
gmake[1]: *** [happy.bin] Error 1
gmake: *** [all] Error 2




ghc needs happy, happy needs happy. i dont have happy, im not happy

1998-01-26 Thread Byron Cook

I'm trying to install GHC-2.10 from sources on HP-UX
$ uname -a 
  HP-UX hp182 B.10.01 A 9000/770 

but it says it needs happy-1.4

so i grabbed happy-1.5 and tryed to install it, but it needs happy too.

which version of happy does happy-1.5 need to install?  and which version
will that version need?

help  :-)

your good friend,
- Byron





2.09 binary for Alpha/Digital UNIX

1997-12-05 Thread Byron Cook

Hi, 

does anyone have binary distribution of ghc-2.09 for the  Alpha/Digital
UNIX?

I'm trying to help someone else via email,  he's having a bad ghc
experience.


byron




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 Byron Cook
eSTArray arr loc val |
loc - range (loAddr,hiAddr) ]
   return Written

performReq (WriteFn loc f)
  = do readVal - readSTArray arr loc
   let writeVal = f readVal
   writeSTArray arr loc writeVal
   return (WrittenFn writeVal)

performReq FreezeArr
  = do arr - freezeSTArray arr
   return (ArrayVal arr)

-- Forces each action in its argument list by pattern-matching
--  on the action's output unit. This function is useful in preventing
--  large sequences of actions from being built.
strictSequence :: Monad m = [m ()] - m ()
strictSequence = foldr (\m n - do { () - m; n }) (return ())

{-
The following functions dealing with write-ranges are
needed because the hugs interpreter is very slow in evaluating
lazy monadic expressions involving lots of writes to a MutArr.
Even simple programs output by dlxgcc ask to have about 16K-words
of data to be initialized to zero, while other areas of memory
should be initialized to an error value. These routines
allow me to isolate what the majority of array locations should
be initialized to; I can pass this initialization value to
newArr (which is implemented as a primitive) to avoid most
of the initial writes.
-}

-- Given a write-range and a list of contiguous sorted write ranges,
--  this function outputs a contiguous sorted write range that would
--  result when the first write range is written to an array after the other
--  write ranges are written to an array. Note that the write-range to
--  be inserted must overlap or be contiguous to the write-range list.
insertWrite :: (Ix i,Enum i) = (i,i,a) - [(i,i,a)] - [(i,i,a)]
insertWrite writeRange []
  = [writeRange]
insertWrite writeRange@(lo,hi,v) (first@(firstLo,firstHi,firstVal):rest)
  -- empty writeRange
  | hi  lo = first : rest
  -- writeRange is completely less than first element
  | hi  firstLo= writeRange : first : rest
  -- writeRange is completely greater than first element
  | firstHi  lo= first : insertWrite writeRange rest
  -- writeRange completely overlaps the first element
  | lo = firstLo  hi = firstHi = insertWrite writeRange rest
  -- writeRange partially overlaps the first element; the leading
  --  edge of writeRange is less than or equal to the leading edge
  --  of the first element.
  | lo = firstLo   = writeRange : (succ hi,firstHi,firstVal) : rest
  -- writeRange partially overlaps the first element; the leading
  --  edge of writeRange is greater than the leading edge of the
  --  first element.
  | firstLo  lo= (firstLo,pred lo,firstVal) : insertWrite writeRange 
((lo,firstHi,firstVal):rest)
  | True= error "bug in insertWrite"


-- Given a write range 'writeRange' and a list of write-ranges 'ranges' whose
--  elements are subranges of 'writeRange', this function outputs a contiguous,
--  non-overlapping list of write-ranges that is equivalent to writing
--  'writeRange' to an array, followed by writing the elements of 'ranges'
--  in order to the same array.
contigWriteRanges :: (Ix i,Enum i) = (i,i,a) - [(i,i,a)] - [(i,i,a)]
contigWriteRanges writeRange ranges
  = foldr insertWrite [writeRange] (reverse ranges)


-- Finds the largest write-range in a list of write-ranges.
maxWriteRange :: (Ix i,Enum i) = [(i,i,a)] - (i,i,a)
maxWriteRange
  = foldr1 (\a@(loA,hiA,_) b@(loB,hiB,_) -
if rangeSize (loA,hiA) = rangeSize (loB,hiB)
  then a
  else b)

-- removes a given write-range from a list of write-ranges
removeWriteRange :: (Ix i,Enum i) = (i,i,a) - [(i,i,a)] - [(i,i,a)]
removeWriteRange (lo,hi,_) = filter (\(loA,hiA,_) - lo /= loA || hi /= hiA)
  



byron

On 1 Dec 1997, Simon Marlow wrote:

 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
 




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




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 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
 




/tmp files - ghc2.05

1997-08-20 Thread Byron Cook

ghc2.05 isnt deleting the tmp files it creates during compilation.

i assume that there is some flag that i need to set the ghc Perl  script


byron




Re: ghc 2.05 -- typo in makefile

1997-08-20 Thread Byron Cook

i dont know. i cant reproduce it either.

it must have just been me or something maybe i ran out of disk space


byron

On Tue, 19 Aug 1997, Sigbjorn Finne wrote:

 
 Byron Cook writes:
 
  I successfully built 2.05 
  
 
 Great, hope it turns out to be useful.
 
  
  one problem, the makefiles built prof. archives like libBlah_p.a
  but then were looking for archives like libBlah.p_a when installing
  
 
 I'm not able to reproduce this - do you have some more details as to
 what went wrong?
 
 --Sigbjorn
 




ghc 2.05 -- typo in makefile

1997-08-19 Thread Byron Cook

Hi,

I successfully built 2.05 


one problem, the makefiles built prof. archives like libBlah_p.a
but then were looking for archives like libBlah.p_a when installing



byron




Re: I just can't stand it any more

1997-07-31 Thread Byron Cook

that would be fine but the word "might" makes me nervous. Lazy State
is really really handy.  I can send you some examples if your curious

So if both ghc and hugs provided another monad LazyST in a module LazyST
then that would be quite cool.  


cheers


byron

On Thu, 31 Jul 1997, Alastair Reid wrote:

 The compatability problem with Hugs using lazy ST and GHC using strict ST
 will be resolved as follows:
 
   Hugs will provide a strict ST monad by default.
   The lazy ST monad might be available for import from another module
 for compatability reasons.
 
 
 Alastair Reid
 




Re: I just can't stand it any more

1997-07-30 Thread Byron Cook

Yes, I agree 70% of the time I dont need lazy state
-- and the performance cost _is_ big.

However, couldn't the same be said of general laziness ? 
Only a percentage of my code uses laziness. Perhaps, for
performance reasons, we should change the semantics of Haskell and make it
strict?  

There is also a compatability issue with Hugs.  I know of at least 5
people here at OGI who developed programs in Hugs and were then
confused when their programs kept asking for more stack space in GHC.  

:-)

byron

On Wed, 30 Jul 1997, Sigbjorn Finne wrote:

 
 Byron Cook writes:
  I've kept quiet up until now  but GHC burned me again today, and I
  need to share my frustration
  
  GHC's ST monad is strict in the state --- and that's just wrong.  
  This is Haskell after all.
  
 
 The ST monad used to have lazy binds, but with 0.29 (and later) a
 switch was made to strict binds. If you want to be lazy, use
 ST.returnLazySTt ST.thenLazyST. 
 
 The experience with lazy binds was that the laziness simply wasn't
 depended upon, and you take a performance hit with it. Your mileage
 may vary.
 
 --Sigbjorn
 




I just can't stand it any more

1997-07-28 Thread Byron Cook

I've kept quiet up until now  but GHC burned me again today, and I
need to share my frustration

GHC's ST monad is strict in the state --- and that's just wrong.  
This is Haskell after all.


The default should be lazy state with strict versions of binds and return

Perhaps there should be another monad "StrictST" with functions moving
between:
strictST :: ST a - StrictST a
lazyST   :: StrictST a - ST a

Hugs does something like this, where "IO" is the strict state monad, and
"ST" is lazy 


Long live laziness! 


byron