Re: slight difference in strictness between -O0 and -O

2007-03-13 Thread Kirsten Chevalier

On 3/13/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:


I noticed that compiling with -O -frules-off causes the test program
here to correctly print out "x". So, I was looking at the "take" rule
in GHC/List.lhs. Doesn't this rule change the strictness of take?

"take" [~1] forall n xs . take n xs = case n of I# n# -> build (\c
nil -> foldr (takeFB c nil) (takeConst nil) xs n#)



I may be talking to myself here, but what I mean is:


take 1 (1:undefined)

[1]

build (\ c nil -> foldr (takeFB c nil) (takeConst nil) (1:undefined) 1#)

[1*** Exception: Prelude.undefined

(where takeFB and takeConst are defined as they are in GHC/List.lhs)

So that rule doesn't seem to be quite right.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"80% of success is showing up."--Woody Allen
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: slight difference in strictness between -O0 and -O

2007-03-13 Thread Kirsten Chevalier

On 3/12/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:

On 3/12/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:
> On 3/12/07, Albert Y. C. Lai <[EMAIL PROTECTED]> wrote:
> > main = print (map (const 'x') (take 1 (undefined:undefined)))
> >
> > In ghci, or with ghc -O0, this produces "x".
> > With ghc -O, this produces Prelude.undefined.
> >
>
> What version of ghc?
>

I was curious, so I checked this against ghc 6.6. Indeed, it exhibits
the behavior Albert describes above. Same goes for the HEAD. In ghc
6.4.2, however, the program prints "x" whether compiled with -O or
-O0.

This does seem like a bug to me.



I noticed that compiling with -O -frules-off causes the test program
here to correctly print out "x". So, I was looking at the "take" rule
in GHC/List.lhs. Doesn't this rule change the strictness of take?

"take"   [~1] forall n xs . take n xs = case n of I# n# -> build (\c
nil -> foldr (takeFB c nil) (takeConst nil) xs n#)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"It's a woman's dream, this autonomy / Where the lines connect and the
points stay free" -- Ferron
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: slight difference in strictness between -O0 and -O

2007-03-12 Thread Kirsten Chevalier

On 3/12/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:

On 3/12/07, Albert Y. C. Lai <[EMAIL PROTECTED]> wrote:
> main = print (map (const 'x') (take 1 (undefined:undefined)))
>
> In ghci, or with ghc -O0, this produces "x".
> With ghc -O, this produces Prelude.undefined.
>

What version of ghc?



I was curious, so I checked this against ghc 6.6. Indeed, it exhibits
the behavior Albert describes above. Same goes for the HEAD. In ghc
6.4.2, however, the program prints "x" whether compiled with -O or
-O0.

This does seem like a bug to me.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Live fast, love hard, and wear corrective lenses if you need them."
--Webb Wilder
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: slight difference in strictness between -O0 and -O

2007-03-12 Thread Kirsten Chevalier

On 3/12/07, Albert Y. C. Lai <[EMAIL PROTECTED]> wrote:

main = print (map (const 'x') (take 1 (undefined:undefined)))

In ghci, or with ghc -O0, this produces "x".
With ghc -O, this produces Prelude.undefined.



What version of ghc?

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"make them believe, if not in magic, in money well spent" -- Annie Gallup
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parsing GHC Core

2007-03-08 Thread Kirsten Chevalier

On 3/8/07, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

Yes, it'll be great to have External Core working again.  Thanks to Kirsten and 
Peter for picking it up.

(Peter, Kirsten, if you get stuck, I'm happy to help.)


Correction -- that's Aaron, not Peter :-)

At the moment we're not stuck, it's just a matter of finding time to
work on it. We won't hesitate to ask if something comes up, though.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Who needs reasons when you've got the root password?"[EMAIL PROTECTED]
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parsing GHC Core

2007-03-08 Thread Kirsten Chevalier

On 3/8/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:

Hi,

I would like to parse GHC Core to an abstract syntax tree, as the old
GHC Core library used to allow the user to do. I do not want to depend
on the GHC API (too big), but don't mind depending on a small and
separately available .cabal'd package. I also don't mind copying a few
modules into my program. The types are of no interest to me, if that
makes it any easier

Does anyone have the code/library to do this sitting around?


Does it matter which version of GHC? As far as I know, there's no
External Core parser that will work with the code emitted by
-fext-core in 6.6. (Aaron Tomb and I (mostly Aaron) have been working
on getting that working again.) I have a parser that works with (IIRC)
GHC 6.0 somewhere, though it would take a little bit of finding. If
that would be useful for you, let me know.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"In a land of quince jelly, apple butter, apricot jam, blueberry preserves,
pear conserves, and lemon marmalade, you always get grape jelly."
--William Least Heat-Moon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Data.Hashtable operations in IO?

2007-02-20 Thread Kirsten Chevalier

[redirecting to a more appropriate mailing list]

On 2/20/07, ROBERT DOUGLAS HOELZ <[EMAIL PROTECTED]> wrote:

I was reading the docs for Data.Hashtable, and quickly noticed that operations 
on a hashtable are of the IO monad.  Why is this?  I should think that the 
operations would look like this:

insert :: Hashtable -> key -> val -> Hashtable
lookup :: Hashtable -> key -> a


If you read the source for Data.HashTable, you'll notice that the
HashTable type is defined in terms of mutable arrays, which must be in
the IO monad since side effects are involved. This is purely for
performance reasons. If you want an analogous type whose operations
are pure, look at Data.Map:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Nuclear war can ruin your whole compile." -- Karl Lehenbauer
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] cabal-upload build problem

2007-02-19 Thread Kirsten Chevalier

You might try asking this on GHC-users instead, rather than haskell, since
it's a GHC-specific question. I took the liberty of CCing this there.

Cheers,
Kirsten

On 2/19/07, Paul Johnson <[EMAIL PROTECTED]> wrote:


I want to upload a package to Hackage.  I tried installing cabal-upload,
but got the following error:

! Preprocessing executables for cabal-upload-0.2...
! Building cabal-upload-0.2...
!
! src/CabalUpload.hs:7:7:
!Could not find module `Distribution.Compat.FilePath':
!it is hidden (in package Cabal-1.1.6)


I tried "ghc-pkg expose Cabal-1.1.6" without success.

I have ghc-6.6 installed on Linux (Fedora Core 6), including Cabal-1.1.6.

(BTW I know I will also need a user id and password.  That was going to
be my next step).

Paul.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell





--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in
doubt
"Dare to be naive."--R. Buckminster Fuller
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Kirsten Chevalier

On 2/13/07, Jefferson Heard <[EMAIL PROTECTED]> wrote:

Thanks for the redirect.  I haven't tried profiling yet, as I was hoping it
was obvious to the more seasoned user.  In reference to your comment about
tail-recursion not working as you'd always expect, is there some document
somewhere that tells the wherefores of that?  I'm using fully qualified types
and fully uncurried functions, so I wouldn't think that I should really see
this kind of recursion, coming from languages like Scheme and OCaml.


Seasoned users know that nothing is obvious until you run the
profiler. With that said, the discussion on haskell-cafe is good when
it comes to the reasoning behind tail-recursion not working the way
users of strict languages might expect. Perhaps it should be written
up somewhere more permanent. But that's a point about Haskell in
general.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Everyone's too stupid." -- _Ghost World_
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Kirsten Chevalier

[redirecting to ghc-users since this is a GHC question]

On 2/13/07, Jefferson Heard <[EMAIL PROTECTED]> wrote:

Hi, I am running the following code against a 210 MB file in an attempt to
determine whether I should use alex or whether, since my needs are very
performance oriented, I should write a lexer of my own.  I thought that
everything I'd written here was tail-recursive, but after compiling this with
GHC 2.4.6, and running it, I eat up 2GB of RAM in less than a second.  So
far, I have tried token and character oriented Parsec parsers and alex and
alex is winning by a factor of 2.  I would like to be able to tokenize the
entirety of a 1TB collection in less than 36 hours on my current machine,
which is where alex has gotten me so far.  Thanks in advance!

 -- Jeff

---

module Main
where


import qualified FileReader
import qualified Data.Set as Set

punct = foldl (flip Set.insert) Set.empty "<,>.?/:;\"'{[}]|\\_-+=)
(*&[EMAIL PROTECTED]"

stripTagOrComment [] = []
stripTagOrComment ('>':rest) = rest
stripTagOrCOmment (c:rest) = stripTagOrComment rest

pass1 :: String -> String -> String
pass1 left [] = left
pass1 left ('<':right) = pass1 left (stripTagOrComment right)
pass1 left (' ':right) = pass1 left right
pass1 left (c:right)
| Set.member c punct = pass1 (' ':c:' ':left) right
| otherwise  = pass1 (c:left) right


pass2 :: [String] -> String -> Char -> String -> [String]
pass2 left word ' ' [] = word:left
pass2 left word c [] = (c:word):left
pass2 left word ' ' (' ':right) = pass2 left word ' ' right
pass2 left word ' ' (c:right) = pass2 (word:left) "" c right
pass2 left word l (c:right) = pass2 left (l:word) c right

tokenize = (pass2 [] "" ' ') . (pass1 [])

main = do
  file <- do FileReader.trecReadFile "trecfile"
  print (tokenize (head (tail file)))


--  print (length (map (runParser tokenizeDoc [] "") file))


Have you tried profiling? (see section 5 of the GHC manual.) What's
your GHC command line? Tail-recursion in Haskell doesn't always work
the way you'd expect, but without profiling it's pretty hard to tell
what the problem is.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Relax. I'm weird, not violent."--Brad Boesen, _Disturbed_
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Problem compiling happy 1.15

2007-02-13 Thread Kirsten Chevalier

[redirecting to ghc-users]

On 2/13/07, Rob Hoelz <[EMAIL PROTECTED]> wrote:

I downloaded the source for happy 1.15, and when I run make, this pops
up:

/usr/bin/ghc -H16m -O -cpp -fglasgow-exts -O-c LALR.lhs -o LALR.o
-ohi LALR.hi

LALR.lhs:626:34: Not in scope: `bounds'
make[3]: *** [LALR.o] Error 1
make[2]: *** [all] Error 2
make[1]: *** [all] Error 1
make[1]: Leaving directory `/home/rob/downloads/happy-1.15/happy'
make: *** [/home/rob/downloads/happy-1.15/happy/src/happy-inplace]
Error 2

After erasing hiding (bounds) in these lines:

import Data.Array hiding (bounds)
import Array hiding (bounds)

it does some more work, then this error pops up:

/usr/bin/ghc -H16m -O -cpp -fglasgow-exts -O-c ProduceCode.lhs -o
ProduceCode.o  -ohi ProduceCode.hi

ProduceCode.lhs:31:20: Not in scope: `Data.Array.MArray.indices'
make[3]: *** [ProduceCode.o] Error 1
make[2]: *** [all] Error 2
make[1]: *** [all] Error 1
make[1]: Leaving directory `/home/rob/downloads/happy-1.15/happy'
make: *** [/home/rob/downloads/happy-1.15/happy/src/happy-inplace]
Error 2

Is my configuration messed up or something?



What version of ghc are you using? (/usr/bin/ghc --version)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"I don't care too much for money/Money can't buy me TeX." -- Jason Reed
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] External Core

2007-02-06 Thread Kirsten Chevalier

On 2/6/07, Ricky Barefield <[EMAIL PROTECTED]> wrote:


I've tried running Happy on these files but get the error `Not enough type arguments for 
the type synonym "P"' when I try to run the resultant Parser.hs in Hugs and 
similar errors when run in GHC.



What I'm trying to achieve is to read the hcr files into a Haskell data type 
which I could work with, if anyone could give me any help with using the files 
for manipulating Core I would be very grateful.



External Core isn't currently working correctly in the HEAD. Aaron
Tomb was working on this, I know (as per mailing lists posts on
cvs-ghc from November and December), but I don't know if he still is.

glasgow-haskell-users is a better place to discuss this.

Your best bet if you want to be able to use External Core may be to
fix it yourself. I know that's what I had to do! But, people on
glasgow-haskell-users and cvs-ghc will probably be happy to discuss it
with you.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"I saw no reason then why hell should not have, so to speak, visible branch
establishments throughout the earth, and I have visited quite a few of them
since."--Robertson Davies
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc 6.6 for mac os x (intel)

2007-02-05 Thread Kirsten Chevalier

[redirecting to the list]
On 2/5/07, Ariel Apostoli <[EMAIL PROTECTED]> wrote:

Hello Kirsten,

Thanks so much for your time and help so far. However, I am still stuck
on the issue when I try to do this:

./configure --with-readline-includes=/usr/local \
  --with-readline-libraries=/usr/local

I get:
checking build system type... i686-apple-darwin8.8.1
checking host system type... i686-apple-darwin8.8.1
checking target system type... i686-apple-darwin8.8.1
Canonicalised to: i386-apple-darwin
checking for path to top of build tree... /Users/ariel/work/ghc/ghc-6.6
checking for ghc... no
checking for ghc-pkg matching ... no
checking for ghc-pkg... no
checking whether ghc has readline package... no
checking for nhc... no
checking for nhc98... no
checking for hbc... no
configure: error: GHC is required unless bootstrapping from .hc files.

Do you know what should I do to avoid this?



Do you already have a binary version of GHC installed? If you want to
build GHC from source, you need a binary of GHC installed already,
like the error message suggests. (Unless you want to bootstrap from
.hc files, but I've never done that, so I don't know.)
See:
http://haskell.org/ghc/download_ghc_66.html#macosxintel

You didn't say what version of Mac OS X you were using; if it's
anything older than 10.3, you're probably SOL.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"just thinking of a series of dreams" -- Bob Dylan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: time profiling (was: (no subject))

2007-02-05 Thread Kirsten Chevalier

On 2/5/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:

On 2/5/07, Tays Soares <[EMAIL PROTECTED]> wrote:
>
>
>
> Hello everyone,
>
> I did at my master thesis a compiler that generates Haskell code. Now I need 
to measure the execution time of my generated code and I've been searched and I 
don't know if I'm looking with the wrong keywords but I could not find anything. I 
just need to measure the time of simple functions, like Ackermann and Fibonacci. 
Does anyone know how to measure the execution time of a Haskell program or 
function?


Another post (where someone didn't change the subject line) mentioned
looking at existing research in order to get an idea of what
methodology people used for profiling, so while we're at it, I might
as well plug my own master's thesis, where, in chapter 4, I wrote
about how I measured the performance of a Haskell optimization I
implemented externally to GHC:
http://lafalafu.com/krc/Writing/chevalier_ms_2004_type_inference.pdf
Maybe it'll be helpful to you.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"What doesn't kill you makes you look really, really bad."--Carrie Fisher
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: time profiling (was: (no subject))

2007-02-05 Thread Kirsten Chevalier

On 2/5/07, Tays Soares <[EMAIL PROTECTED]> wrote:




Hello everyone,

I did at my master thesis a compiler that generates Haskell code. Now I need to 
measure the execution time of my generated code and I've been searched and I 
don't know if I'm looking with the wrong keywords but I could not find 
anything. I just need to measure the time of simple functions, like Ackermann 
and Fibonacci. Does anyone know how to measure the execution time of a Haskell 
program or function?


If you just want wallclock time, then use the standard Unix "time" command.

If you want more specific data, look at the Profiling section of the GHC manual:
http://www.haskell.org/ghc/docs/latest/html/users_guide/profiling.html
and also at the Profiling section of the Commentary, though it's very
incomplete:
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Profiling

And feel free to ask again on this list after looking at those pages,
if you still have more questions.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"the faith that is so easy to forget / in moment after moment of distraction"
-- Ilene Weiss
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc 6.6 for mac os x (intel)

2007-02-04 Thread Kirsten Chevalier

On 2/4/07, Ariel Apostoli <[EMAIL PROTECTED]> wrote:

Hello,

I tried to install ghc 6.6 but apparently I have done something wrong
since whenever I type ghc I obtain:

$ /usr/local/bin/ghc
dyld: Library not loaded: /opt/local/lib/libreadline.5.1.dylib
 Referenced from: /usr/local/lib/ghc-6.6/ghc-6.6
 Reason: image not found
Trace/BPT trap



Hi, Ariel--
Have you seen the page on building GHC on Mac OS X?
http://cvs.haskell.org/trac/ghc/wiki/Building/MacOSX
In particular, it explains how to set up the readline library so that
GHC can find it.

If you try the instructions there and something still doesn't work,
feel free to post here again.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"The astonishment of life is the absence of any appearance of reconciliation
between the theory and practice of life."--Emerson
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Meaning abbreviations stat file GHC

2007-01-14 Thread Kirsten Chevalier

[redirecting to ghc-users]

On 1/13/07, Ron <[EMAIL PROTECTED]> wrote:

Dear,

I made a profile[1] of a test program:
Where can I find documentation for the meaning of everything mentioned
below? Or alternatively, can anyone explain them?

Where can I see the effect of using the -xt option in this profile?

Ron

[1]
/Main +RTS -p -s -xt -hc
1,372,408,024 bytes allocated in the heap
121,255,600 bytes copied during GC (scavenged)
  6,584,692 bytes copied during GC (not scavenged)
  2,768,896 bytes maximum residency (68 sample(s))

   2649 collections in generation 0 (  1.11s)
 68 collections in generation 1 (  0.49s)

  6 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time5.97s  (  6.63s elapsed)
  GCtime1.60s  (  1.88s elapsed)
  RPtime0.00s  (  0.00s elapsed)
  PROF  time0.19s  (  0.20s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time7.76s  (  8.71s elapsed)

  %GC time  20.6%  (21.5% elapsed)

  Alloc rate229,946,873 bytes per MUT second

  Productivity  76.9% of total user, 68.5% of total elapsed



I don't think that the format of this file is documented anywhere
(though it should be), but this information is really meant for GHC
implementors. Have you looked at the chapter on profiling in the GHC
manual yet?
http://www.haskell.org/ghc/docs/latest/html/users_guide/profiling.html
There's also a very sketchy intro to profiling in the GHC Commentary:
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Profiling
and you're welcome to improve it.

If the above documentation doesn't answer your questions, feel free to
reply to this mailing list with more specific questions; it might help
to explain exactly what you're trying to find out about your program's
behavior.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"What is research but a blind date with knowledge?" -- Will Henry
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc: out of memory error while compiling huge "let"

2007-01-12 Thread Kirsten Chevalier

On 1/12/07, David Morse <[EMAIL PROTECTED]> wrote:


Is there some simple syntactic refactoring I can do to make this work?
 E.g. busting the local bindings out of the "let" and into to the
global level?

The bindings are intertwined, but I could (with some effort) reorder
them so that b5000 would only reference b5001...b1 and never
b1...b4999.


Somehow I doubt that the answer is going to be that simple, but for
starters, what's your ghc command line? (In particular, are you
compiling with -O or not? If ghc is eating that much memory than I'd
assume you are, but one should never assume.)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"by God I *KNOW* what this network is for, and you can't have it."--Russ
Allbery
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC Runtime System

2007-01-11 Thread Kirsten Chevalier

On 1/11/07, Cristian Perfumo <[EMAIL PROTECTED]> wrote:

Hi Friends.
 I'm trying to modify GHC runtime in order to add some new functions
to STM API. Wich documentation (if there's any) do you suggest me to
read? I mean... what's the starting point to learn how to link a
Haskell function in STM.hs with a C function in STM.c?


Check out:
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts
to start with. As you learn more, you can add to the commentary if you
notice any places where it's incomplete. And if anything isn't clear,
you can always ask about it on this mailing list.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"'Compassion' doesn't mean 'letting fucktards do whatever they want just
because they want it.'" -- lj user="uberwald"
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Exception when compiling HAppS

2007-01-07 Thread Kirsten Chevalier

On 1/7/07, Dimitry Golubovsky <[EMAIL PROTECTED]> wrote:

On 1/7/07, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:

> > I am getting a strange error message when trying to compile
> > HAppS-0.8.4 with ghc-6.4.1always on the same file.
> >
> [snip]
> > *** Exception: waitForProcess: interrupted (Interrupted system call)
> >
>
> This could mean a lot of things. What OS and platform are you using?
>

bash$ uname -a
Linux dmghome 2.2.16 #9 Mon Sep 16 22:43:25 EDT 2002 i686 unknown



By way of figuring out which system call is getting interrupted, can
you run your "runghc" command with strace, like so:
bash$ strace [whatever you were typing to build happs before]
and paste the last couple of lines of strace's output?

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"What is research but a blind date with knowledge?" -- Will Henry
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Exception when compiling HAppS

2007-01-07 Thread Kirsten Chevalier

On 1/7/07, Dimitry Golubovsky <[EMAIL PROTECTED]> wrote:

Hi,

I am getting a strange error message when trying to compile
HAppS-0.8.4 with ghc-6.4.1always on the same file.


[snip]

*** Exception: waitForProcess: interrupted (Interrupted system call)



This could mean a lot of things. What OS and platform are you using?

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Would you be my clock if I promise not to hang you / Too close to the
window or
the picture of the pope? / I won't set you back and I won't push you forward /
I just want to look in your face and see hope" -- Dom Leone
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Building GHC on Mac OS 10.2.1

2006-12-29 Thread Kirsten Chevalier

The latest is that while I was able to successfully install gcc 3.3,
it made no difference at all. I was able to make some progress by
running configure with --disable-threaded-rts. But, now I get:


== make boot -r;
in /Users/krc/ghc-head/ghc/compat

../utils/mkdependC/mkdependC -f .depend-I. -Iinclude -I../includes
-- -O -I. -Iinclude -D__GHC_PATCHLEVEL__=1 -I../libraries/base/cbits
-I../libraries/base/include--\
cbits/directory.c cbits/rawSystem.c cbits/unicode.c
/usr/local/bin/ghc -M -optdep-f -optdep.depend  -osuf o-H16m -O
-I. -Iinclude -Rghc-timing -I../libraries -fglasgow-exts -no-recomp
Compat/Directory.hs Compat/RawSystem.h\
s Compat/Unicode.hs Distribution/Compat/FilePath.hs
Distribution/Compat/ReadP.hs Distribution/Compiler.hs
Distribution/GetOpt.hs Distribution/InstalledPackageInfo.hs Distribu\
tion/License.hs Distribution/Package.hs Distribution/ParseUtils.hs
Distribution/Version.hs Language/Haskell/Extension.hs
System/Directory/Internals.hs
<>
make all
/usr/local/bin/ghc -H16m -O -I. -Iinclude -Rghc-timing  -I../libraries
-fglasgow-exts -no-recomp-c System/Directory/Internals.hs -o
System/Directory/Internals.o  -ohi Sys\
tem/Directory/Internals.hi
System/Directory/Internals.hs:1: parse error on input `#'
<>
make[2]: *** [System/Directory/Internals.o] Error 1
make[1]: *** [boot] Error 2
make: *** [stage1] Error 1

My /usr/local/bin/ghc is ghc 6.0.1, which... *should* recognize
OPTIONS (or any other pragma), right? Various documentation claims you
should be able to bootstrap with anything newer than 5.0.4. I'm not
*entirely* sure where the existing old version of ghc I have installed
came from. But I think it's a standard build. Can anyone tell what's
up? I've built ghc I-don't-know-how-many-times now and I'm *still*
mystified by this.

Thanks,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Of the seven deadly sins, lust is definitely the pick of the litter."
-- Tom Robbins
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Building GHC on Mac OS 10.2.1

2006-12-29 Thread Kirsten Chevalier

On 12/29/06, Wolfgang Thaller <[EMAIL PROTECTED]> wrote:

> I'm trying to build the HEAD on a somewhat old PowerBook G4 running
> Mac OS 10.2.1. It would seem that I don't have a new enough version of
> gcc:
> % gcc --version
> gcc (GCC) 3.1 20020420 (prerelease)

Well, support for that version has definitely bitrotted, but it
shouldn't be impossible to fix. How far do you get, what kind of
errors do you get?



The link I included to my tale of woe on the wiki answers the
question, but, I admit, in a way that's a bit interleaved with
profanity. So, in short:

(after running make in ghc:)

gcc -O -DTABLES_NEXT_TO_CODE -I. -I../rts-c mkDerivedConstants.c
-o mkDerivedConstants.o
InfoTables.h:314: illegal member declaration, missing name, found `}'
OSThreads.h:135: #error "Threads not supported"
OSThreads.h:141: undefined type, found `OSThreadId'
OSThreads.h:145: illegal external declaration, missing `;' after
`OSThreadProcAttr'
OSThreads.h:145: illegal external declaration, missing `;' after `*'
OSThreads.h:147: undefined type, found `OSThreadId'
OSThreads.h:148: undefined type, found `OSThreadProc'
OSThreads.h:153: undefined type, found `Condition'
OSThreads.h:154: undefined type, found `Condition'
OSThreads.h:155: undefined type, found `Condition'
OSThreads.h:156: undefined type, found `Condition'
OSThreads.h:157: undefined type, found `Condition'
OSThreads.h:158: undefined type, found `Mutex'
OSThreads.h:163: undefined type, found `Mutex'
OSThreads.h:164: undefined type, found `Mutex'
OSThreads.h:169: undefined type, found `ThreadLocalKey'
OSThreads.h:170: undefined type, found `ThreadLocalKey'
OSThreads.h:171: undefined type, found `ThreadLocalKey'
Storage.h:211: undefined type, found `Mutex'
Storage.h:212: undefined type, found `Mutex'
../rts/Task.h:88: undefined type, found `OSThreadId'
../rts/Task.h:115: undefined type, found `Condition'
../rts/Task.h:116: undefined type, found `Mutex'
../rts/Task.h:225: illegal function prototype, found `*'
../rts/Task.h:225: illegal function definition, found `)'
../rts/Task.h:235: undefined type, found `ThreadLocalKey'
../rts/Capability.h:74: undefined type, found `Mutex'
../rts/Capability.h:197: undefined type, found `Mutex'
cpp-precomp: warning: errors during smart preprocessing, retrying in basic mode
make[1]: *** [mkDerivedConstants.o] Error 1
make: *** [stage1] Error 1

I ASSumed that this was a gcc 3.1 vs. gcc 3.3 issue, and then got
stuck trying to upgrade gcc (I'm now downloading the .dmg for it per
Judah's suggestion to see if it helps). I don't know if it really is
or not. At the least, if there is a dependency on newer gcc versions
or on include files not found in OS 10.2, it would be nice to have
configure warn you about it.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"You don't have to be a supermodel to do the animal thing / You don't have to be
a genius to open your face up and sing" -- Ani DiFranco
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Building GHC on Mac OS 10.2.1

2006-12-29 Thread Kirsten Chevalier

Hi all,
I'm trying to build the HEAD on a somewhat old PowerBook G4 running
Mac OS 10.2.1. It would seem that I don't have a new enough version of
gcc:
% gcc --version
gcc (GCC) 3.1 20020420 (prerelease)
and I can't seem to build a newer version of gcc (3.3) due to missing
system include files which I assume (though that assumption may be
wrong) are due to running 10.2 instead of 10.4. (For the full tale of
woe, see http://hackage.haskell.org/trac/ghc/wiki/KirstenSandbox). Am
I right in thinking that building GHC on Mac OS 10.2.1 is more or less
impossible, or has anyone managed to do it? I'm pretty close to just
giving up and buying a PC (various things make it difficult for me to
upgrade to Tiger).

Thanks,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Are you aware that rushing toward a goal is a sublimated death wish? It's no
coincidence we call them 'deadlines'." -- Tom Robbins
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: profiling experience

2006-12-06 Thread Kirsten Chevalier

On 12/6/06, Serge D. Mechveliani <[EMAIL PROTECTED]> wrote:

What may consitute this strange CAF cost of 96% ?

Kirsten Chevalier <[EMAIL PROTECTED]>
wrote
> I didn't look at your code all that carefully, but did you build the
> GHC libraries with "-prof -auto-all"? (Not just "-prof".) If you don't
> build the libraries with "-auto-all", then cost centres won't get
> inserted for library functions, and if it's really a standard library
> function that's taking all of that time, the profiling report won't
> indicate that.

I made ghc-6.6 from the official source in a standard way:

  ./configure ...;  make;  make install

Does this presume that this also generates the .p.o GHC library versions
for -prof -auto-all ?



No; you must have built the profiling libraries (i.e., building the
libraries with -prof), otherwise you wouldn't have been able to
compile your code for profiling. But, building the profiling libraries
in the standard way doesn't add "-auto-all" to the compile flags. So
if you want to build the libraries with "-auto-all", do:
make EXTRA_HC_OPTS=-auto-all

but be careful! As I said in my previous message, adding cost centres
disables some optimizations, so the profiling results you get from
this may not be accurate with respect to what would happen if you ran
your code after building it with -O and no profiling.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"I cannot remember a time when I did not take it as understood that everybody
has at least two, if not twenty-two, sides to him."--Robertson Davies
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: difficult profiling example

2006-12-04 Thread Kirsten Chevalier

On 12/2/06, Serge D. Mechveliani <[EMAIL PROTECTED]> wrote:

It looks correct that  searchLemmata  costs  90%.
I could believe that  splitDisjunctScheme and addEquationsWithReduction
take together about  8%  of what  searchLemma  costs.

But who  inside the  searchLemmata  loop  takes the rest of (90 - 8)%  ?



I didn't look at your code all that carefully, but did you build the
GHC libraries with "-prof -auto-all"? (Not just "-prof".) If you don't
build the libraries with "-auto-all", then cost centres won't get
inserted for library functions, and if it's really a standard library
function that's taking all of that time, the profiling report won't
indicate that.

On the other hand, one thing to watch out for with GHC's cost-centre
profiling is that a lot of optimizations get effectively disabled when
you build with "-auto-all" (or insert your own cost centres
liberally), so if you're profiling optimized codes, the results can
sometimes be misleading (especially if you build libraries with
"-auto-all" too). Using ticky-ticky profiling instead could be
helpful, but I don't think it works in 6.6. (I've gotten a limited
form of it working again and I'm hoping to check it into the HEAD
soon.)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: bang patterns give fundamentally new capabilities?

2006-12-04 Thread Kirsten Chevalier

On 12/3/06, John Meacham <[EMAIL PROTECTED]> wrote:

On Sat, Dec 02, 2006 at 11:02:28PM +, Simon Peyton-Jones wrote:

[snip]

> | Also, is there a way to do something similar but for 'lazy' rather than
> | 'seq'? I want something of type
> |
> | type World__ = State# RealWorld
> |
> | {-# NOINLINE newWorld__ #-}
> | newWorld__ :: a -> World__
> | newWorld__ x = realWord#  -- ???
> |
> | except that I need newWorld__ to be lazy in its first argument. I need
> | to convince the opimizer that the World__ newWorld__ is returning
> | depends on the argument passed to newWorld__.
>
> I don't understand what you meant here.  The definition of newWorld__ that 
you give is, of course, lazy in x.

it is getting type 'Absent' assigned to it by the demand analysis, I
want it to be lazy (and not strict)

3 newWorld__ :: a -> World__ {- Arity: 1 HasNoCafRefs Strictness: A -}



Well, yeah, that's because it *is* absent. If you want to convince the
demand analyzer that it isn't, then use x somewhere on the right-hand
side of the definition of newWorld__. Maybe I could be more helpful if
I knew what you were really trying to do here? (My best guess is that
you're trying to implement your own IO monad, which really shouldn't
be possible AFAIK unless there's something seriously wrong with GHC
that I don't know about. Unless you use The Function That Shall Not Be
Named.)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RULES and strictness

2006-12-01 Thread Kirsten Chevalier


when performing strictness/abscence/one-shot analysis, are rule bodies
taken into account?


No.


like, would the following cause trouble making const
no longer absent in its second argument?

const x y = x

{-# RULE "const/seq" forall a b . const a b = seq b a #-}

by trouble I mean the compiler failing or producing bad code in some
way, rather than the obvious trouble of changing the meaning of const.



No, because of the worker/wrapper transform. You can think of
strictness analysis as doing something like this in this case:

const x y = x
=>

const x y = constW x

constW x = let y = error "entered absent argument!" in x

(of course, strictness analysis only does the work of determining that
const is absent in its second argument, and the worker/wrapper
transform phase is a separate pass that happens later.)

So, from then on, GHC will inline const wherever possible, and the
rule "const/seq" will no longer be applicable, because it applies to
const, not constW. Note that even if const doesn't end up getting
inlined for some reason, the presence of the rule doesn't cause any
problems. It's perfectly valid to replace (const a b) with (constW a)
or with (seq b a).


it is noted in the deforestation papers that rules can change the
sharing properties of code and we are okay with that. I was wondering if
they could safely change the strictness or abscence properties of code
as well?



Given the example above, I think it's fairly safe to say that rules
can safely change strictness and absence properties, or at least
"safe" in the sense that it shouldn't cause the compiler to crash or
to generate code that crashes. (Since even GHC's strictness analysis
on its own, ignoring the presence of rules, hasn't been formally
proven correct yet, I'm being rather hand-wavy in saying that.) But,
it is kind of weird to have a rule that changes these properties. I
realize the example you gave is just for the sake of argument, but I
can't think of a real situation where you'd want to have a rule that
changed strictness properties (rather than expressing the strictness
you wanted in the code), though I'm open to being convinced otherwise.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"I flip on the television and watch sad movies / And look for sad sick people
like me" -- Tegan and Sara
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Data.HashTable weirdness

2003-11-08 Thread Kirsten Chevalier
I have some code that uses the Data.HashTable module (passing around a 
hash table as part of the state in a state monad). I had a function which
took a key and value and added it to the hash table, using the HashTable.insert
function. When I changed this function to delete the key from the table first,
using HashTable.delete, the behavior of the function changed. That is, at
first, looking up a key in the table gave a wrong result (seemingly, a "stale"
value), but after changing the function to delete the key before adding it,
my program behaved correctly.

This seems strange to me. According to my understanding of how a hash table
should work, inserting a key in the table should overwrite the previous value
for that key, so inserting a key should be equivalent to deleting it and then
inserting it. But clearly that's not the case here. Can anyone explain this?

--
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
"The information superhighway showed the average person what some nerd thinks
about Star Trek."--Homer Simpson
http://www.cs.berkeley.edu/~krc/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Question about profiling in GHC...

2003-10-28 Thread Kirsten Chevalier
On Mon, Oct 27, 2003 at 12:00:04PM -0500, [EMAIL PROTECTED] wrote:
>When I compile my program without "-prof -auto-all" option (no
>profiling  support), its  execution  time is about 140s (compiled with
>-O2).  When  compiled  with  profiling  support, the time spent by the
>program  is  about  180s  (I  used my  own timer to measure this).  Of
>course, the additional 40s is caused by the profiling annotation code.
>However, the profiler says (in the ".prof" file produced at the end of
>execution)  that  the time spent is about 85s. I suppose that the time
>measured  by  the profiler is only for evaluation of the main function
>of my program (I have compiled all modules with "-prof-all"). But what
>kind  of  computation  is performed in the rest 95s (180s - 85s) ?
>Garbage collection ???

Yes, it's probably garbage collection. To be sure, you can run your program
with the "-t" RTS option, which will create a file in the current working
directory named "foo.stat" if the executable is named "foo". The resulting
file will contain the total amount of time spent, the mutator time, and the
GC time. (I recently ran into this problem myself...)

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
"But just because we're conditioned to view some things as disgusting and
immoral doesn't mean that some things aren't, in actual point of fact,
disgusting and immoral. Human sacrifice, for instance. Or cannibalism. Or Ann
Coulter." -- Dan Savage   http://www.cs.berkeley.edu/~krc/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Heap profiling - breakdown by type

2003-09-15 Thread Kirsten Chevalier
Currently, the -hy RTS option for heap profiling by type doesn't print a
summary of the amount allocated for each type, only the amount of data that
was live at a given instant. How hard would it be to change it to print out
total amounts allocated over the entire run of the program for each type as 
well? I'd be willing to try to implement it, but any hints would be
appreciated (and I wouldn't be sad if someone else went ahead and did it 
:-)

Thanks,
Kirsten

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Nightly development snapshots?

2003-07-08 Thread Kirsten Chevalier
The most recent snapshot listed on 
<http://www.haskell.org/ghc/dist/current/dist/> is dated May 26 -- will
development snapshots be made available again sometime? 

Thanks,
Kirsten

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: More problems compiling GHC on Mac OS X

2003-03-17 Thread Kirsten Chevalier
On Mon, Mar 17, 2003 at 11:18:21AM +0100, Volker Stolz wrote:
> Am 17. Mar 2003 um 02:04 CET schrieb Kirsten Chevalier:
> > On Sun, Mar 16, 2003 at 04:09:31PM +0100, Volker Stolz wrote:
> > > In local.glasgow-haskell-users, you wrote:
> > > > Sendfile.hsc:94:
> > > > Couldn't match `IO ()' against `Fd -> Fd -> Int -> Int -> IO ()'
> > > 
> > > Should be fixed in CVS now, thanks!
> 
> *sigh*. I used fptools/mk/config.h for trying to test compilation of the
> fallback case. Unfortunately, there's anoher config.h around, so in fact the
> test run wasn't compiled with the correct #ifdefs. 
> 

I just did a cvs update and ran configure again, and I'm still getting the
same error message ("Sendfile.hsc:19: Variable not in scope: `c_sendfile'").


-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: More problems compiling GHC on Mac OS X

2003-03-17 Thread Kirsten Chevalier
On Mon, Mar 17, 2003 at 11:40:58AM +0100, Wolfgang Thaller wrote:
> As far as I can tell right now, "sendfile" is not supported on Mac OS X.
> There's no manual page, and it doesn't seem to be in any sytem library. 
> There is a prototype in sys/socket.h, but it's wrapped in an #ifdef 
> that's never #defined.
> When I last build the HEAD here, I didn't have any problems - 
> ./configure found out that sendfile is not supported, and everything is 
> fine until I try to use it (there wasn't yet a fallback implementation 
> then).
> What did configure say on the subject of sendfile?
>

configure says:

checking for sendfile in sys/sendfile.h... no
checking for sendfile in sys/socket.h... no

I tried building again just now, just to be sure, and still got the same error
message ("Sendfile.hsc:19: Variable not in scope: `c_sendfile'").

Thanks,
Kirsten

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: More problems compiling GHC on Mac OS X

2003-03-16 Thread Kirsten Chevalier
On Sun, Mar 16, 2003 at 04:09:31PM +0100, Volker Stolz wrote:
> In local.glasgow-haskell-users, you wrote:
> > Sendfile.hsc:94:
> > Couldn't match `IO ()' against `Fd -> Fd -> Int -> Int -> IO ()'
> 
> Should be fixed in CVS now, thanks!

Now I'm getting the following error instead:

../../ghc/compiler/ghc-inplace -H16m -O -Iinclude -package-name unix -O -Rghc-timing  
-package base -split-objs-c System/Sendfile.hs -o System/Sendfile.o  -ohi 
System/Sendfile.hi

Sendfile.hsc:19: Variable not in scope: `c_sendfile'

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More problems compiling GHC on Mac OS X

2003-03-16 Thread Kirsten Chevalier
I'm getting the following error message trying to compile the latest version
of GHC on Mac OS 10.2.1, using GHC 5.04.2 installed from binaries:

../../ghc/compiler/ghc-inplace -H16m -O -Iinclude -package-name unix -O -Rghc-timing  
-p\
ackage base -split-objs-c System/Sendfile.hs -o System/Sendfile.o  -ohi 
System/Sendf\
ile.hi

Sendfile.hsc:94:
Couldn't match `IO ()' against `Fd -> Fd -> Int -> Int -> IO ()'
Expected type: IO ()
Inferred type: Fd -> Fd -> Int -> Int -> IO ()
In a right-hand side of function `sendfile': squirt
In the definition of `sendfile':
sendfile inFd outFd startpos count = squirt
make[2]: *** [System/Sendfile.o] Error 1
make[1]: *** [all] Error 1
make: *** [build] Error 1

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Can't build GHC on Mac OS X

2003-03-13 Thread Kirsten Chevalier
Hi,
I installed GHC 5.04.2 from binaries on my machine (running Mac OS 10.2.1
and gcc 3.1) and proceeded to try to build the latest version of GHC
from cvs, resulting in the following error message:
[lots of stuff snipped]

==fptools== make all - --no-print-directory -r;
 in /Users/krc/Work/fptools/green-card/lib/hugs

gcc -fPIC -shared -I . -DSTRICT -o StdDIS.so StdDIS.c
gcc: unrecognized option `-shared'
ld: Undefined symbols:
_main
make[3]: *** [StdDIS.so] Error 1
make[2]: *** [all] Error 1
make[1]: *** [all] Error 1
make: *** [build] Error 1

Any idea what's up?

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: The semantics of Core?

2003-02-18 Thread Kirsten Chevalier
On Tue, Feb 18, 2003 at 12:01:02PM -0500, [EMAIL PROTECTED] 
wrote:
> I'm also looking for actual code for working with Core. :) The
> Language.Haskell.* stuff gives me a very high-level representation of
> Haskell source, and I'd rather work with something simple, like Core. I
> *suppose* I could use ghc -fvia-ext or helium -C or something like that,
> and then parse the file it spits out, but it feels like a long way to go
> when there should be shortcuts available. Another way is to rip out the
> code from ghc or helium that does this, but that's not so nice either :(
>

There is a parser, typechecker, interpreter, and printer for Core in
ghc/utils/ext-core in the fptools distribution. The typechecker and
interpreter don't work on Core produced by the latest version of GHC,
but the parser and printer should still work OK. It's a lot easier
than linking your code with code from GHC!

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Profiling question

2003-01-03 Thread Kirsten Chevalier
Hi,
I'd like to be able to determine the percentage of allocated objects of a 
particular type at specific points in a program's execution. I know that I
can use heap profiling to create a graph of memory usage broken down by type,
but is there any way to record this information at particular points in the
program (i.e., between two statements in a do-expression)?

Thanks,
Kirsten

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ext-core Questions

2002-12-30 Thread Kirsten Chevalier
On Fri, Dec 20, 2002 at 12:01:01PM -0500, [EMAIL PROTECTED] 
wrote:
 
> Secondly, in GHC produced Core programs, one sees frequently references to
> intermediate values from other Modules such as SystemziIO.lvl (print
> newline?) or GHCziNum.lvl1 (which seems to be an Integer constant) or even
> GHCziNum.a4 (which seems to be (>) :: Integer -> Integer -> Bool). The type
> of those names as well as any other names from imported Modules is not
> given, however. How then is it possible to type check a Core program?
>

To typecheck a Core program, you need the type environment obtained from
typechecking all the modules it imports -- i.e., at least the Prelude modules.
The Core typechecker in the utils/ext-core directory in the GHC distribution
gives an example.

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Ticky-ticky profiling?

2002-12-09 Thread Kirsten Chevalier
Hi,
I'm wondering what needs to be done in order to use ticky-ticky profiling --
section 5.7 in the Users' Guide says:

  "To be able to use ticky-ticky profiling, you will need to have built
  appropriate libraries and things when you made the system. See ?Customising
  what libraries to build,? in the installation guide."

but that section in the installation guide doesn't seem to exist. When I
try to compile programs with -ticky, I get lots of "Could not find interface
file" errors, so presumably I need to "build appropriate libraries and things".
If anyone could tell me what that specifically means, I'd appreciate it.

Thanks,
Kirsten

--
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: standalone core parser

2002-10-25 Thread Kirsten Chevalier
> What about the Core interpreter in fptools/ghc/utils/ext-core ?
> 
> There's a Happy parser source file there, Parser.y, as well as
> all sorts of other Core-related goodies.

FYI, one can use the parser and printer in fptools/ghc/utils/ext-core as
is, but the typechecker and interpreter need updating in order to work
with Core emitted by the latest version of GHC (the changes should be
pretty minor, but I haven't tried to make them). 

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: efficiency question

2002-02-10 Thread Kirsten Chevalier

On Sat, Feb 09, 2002 at 12:01:02PM -0500, [EMAIL PROTECTED] 
wrote:
> 
> > I'd say that's because in the second case you also got to apply the (,),
> > besides the (+)/(-) constructor during the transversing...
> > Am I right?
> 
> opss... I meant to write: the (,) constructor besides the (+)/(-)...
> J.A.
> 

I'd guess that it's not just that you have to apply the (,) constructor -- it
also has to do with the fact that the tuples it's constructing here are boxed.

-- 
Kirsten Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
"When nothing remains of me, / Not a particle, / I shall sparkle in the
footnote of an article." -- Daniel Aaron
http://www.cs.berkeley.edu/~krc/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users