Re: [Haskell-cafe] Bit streams programs in Haskell

2006-03-22 Thread Donald Bruce Stewart
per.gustafsson:
> 
> Haskell gurus,
> 
> We have made a proposal to extend the Erlang `binary' data type from
> being a sequence of bytes (a byte stream) to being a sequence of bits (a
> bitstream) with the ability to do pattern matching at the bit level.
> 
> Our experience in writing efficient (and beautiful) Haskell programs is
> close to (if not below) zero. Also, perhaps our mind might be suffering
> from severe case of strictness and might be completely unable to `think
> lazily'. So, we request your help in noticing obvious NO-NOs and stupid
> mistakes that we might have made. We even welcome completely different
> Haskell programs provided they adhere to the constraint mentioned
> above -- no mutation.

Ok, I rewrote the drop3 program to use packed, unboxed arrays as the
OCaml version does, instead of lazy boxed lists.

It now runs in 3.5s on my linux box, which is around which is around
what the OCaml version does.

$ ghc B.hs
$ ./a.out testdata.drop3
3.617
$ cmp testdata.drop3.haskell testdata.drop3.out

Comparing lazy list IO against packed array IO is a bit silly, so I suggest you
use the same buffer types in your Haskell code as you do in the OCaml code.
Otherwise the comparisons aren't very meaningful.  The problem is not so much
laziness, as you suggest, but that you're using a completely unsuitable data
type: lists, instead of (packed) strings.

You can most likely just translate your other OCaml programs into Haskell as I
have done here, which would be a good basis for a reasonable comparison.

You may also find the Haskell performance resource useful, 
http://www.haskell.org/haskellwiki/Performance

Cheers,
  Don
{-# OPTIONS -O2 #-}
--
-- Translated from the OCaml version.
--

import Control.Monad
import Data.Char
import Data.Array.IO
import Data.Array.Base
import Data.Bits
import Data.Word
import System
import System.CPUTime
import System.IO
import Text.Printf

iter :: Int
iter = 10

main = do
f <- getArgs >>= return . head
(arr,l)   <- slurp f 
t0<- getCPUTime
(arr',l') <- replicateM iter (drop0xx arr (l*8)) >>= return . head
t1<- getCPUTime
printf "%.3f\n" $ (fromInteger (t1 - t0) :: Float) / (fromInteger 10 ^ 12 
:: Float)
dump f arr' (1 + (snd . bounds) arr')

drop0xx = drop0xx' 0 0 0 []

drop0xx' :: Int -> Int -> Int -> [Int] -> Buffer -> Int -> IO (Buffer,Int)
drop0xx' inoff reg shifts acc str len
| inoff `seq` reg `seq` shifts `seq` acc `seq` str `seq` len `seq` False = 
undefined
| inoff' > len  = makeResult (reverse acc) reg shifts
| otherwise = do
triple <- getTriple str inoff
if triple >= 4 
then let reg' = (reg `shiftL` 3) .|. triple 
 in if shifts == 7
then drop0xx' inoff' 00  (reg':acc) str len
else drop0xx' inoff' reg' (shifts+1) accstr len
else drop0xx' inoff' reg shifts acc str len

where inoff' = inoff + 3

getTriple :: Buffer -> Int -> IO Int
getTriple str inoff | str `seq` inoff `seq` False = undefined 
getTriple str inoff = do
b0 <- str `unsafeRead` bitind >>= return . fromIntegral
b1 <- str `unsafeRead` (bitind+1) >>= return . fromIntegral
return $! (if bitoff < 6
  then  b0 `shiftR` (5-bitoff)
  else (b0 `shiftL` (bitoff-5)) .|. (b1 `shiftR` (13-bitoff)))
  .&. 7

  where bitoff = inoff .&. 7
bitind = inoff `shiftR` 3

makeResult :: [Int] -> Int -> Int -> IO (Buffer,Int)
makeResult list0 endpiece shifts = do
arr <- newArray_ (0,triplebytesize + endpiecesize-1) :: IO Buffer

let packList (triple:rest) ind = do 
 unsafeWrite arr ind $ fromIntegral $ (triple `shiftR` 16) .&. 
255
 unsafeWrite arr (ind+1) $ fromIntegral $ (triple `shiftR`  8) .&. 
255
 unsafeWrite arr (ind+2) $ fromIntegral $ triple   .&. 
255
 packList rest (ind+3)

packList [] ind = 
let c1 = endpiece `shiftL` ((shifts*3 - 8) .&. 255)
s0 = shifts * 3 - 8
in case endpiecesize of
0 -> return ()
1 -> do unsafeWrite arr ind $ fromIntegral $
  endpiece `shiftL` (s0 .&. 255)
2 -> do unsafeWrite arr ind $ fromIntegral $
  endpiece `shiftL` (s0 .&. 255)
unsafeWrite arr (ind+1) $ fromIntegral $
  endpiece `shiftL` ((s0-8) .&. 255)
packList list0 0
return (arr, triplebytesize * 8 + shifts * 3)

where endpiecesize   = getNeededBytes shifts 
  triplebytesize = 3 * length list0

getNeededBytes shifts | shifts < 3 = 0
  | shifts < 6 = 1
  | otherwise  = 2
  


type Buffer = IOUArray Int Word8

slurp :: FilePath -> IO (Buffer, Int)
slur

Re: [Haskell-cafe] Bit streams programs in Haskell

2006-03-22 Thread Chris Kuklewicz
Per Gustafsson wrote:
>
> Haskell gurus,
>

I am not a guru, but I'll clean up some of this.

> Our experience in writing efficient (and beautiful) Haskell programs is
> close to (if not below) zero. Also, perhaps our mind might be suffering
> from severe case of strictness and might be completely unable to `think
> lazily'. So, we request your help in noticing obvious NO-NOs and stupid
> mistakes that we might have made. We even welcome completely different
> Haskell programs provided they adhere to the constraint mentioned
> above -- no mutation.
>
> Best regards,
>
> Kostis Sagonas and Per Gustafsson
>

I can't test this, but I have attached a new version of huffman.hs that may
perform a bit better.  I don't know if all the changes I made helped instead of
hurt.  I doubt it was sped up by much.

-- 
Chris Kuklewicz
--module Huffman where
import System.IO
import Data.Bits
import Data.Word
import Data.Array.IO
import Data.Array.Unboxed hiding ((!))
import Data.Array.Base(unsafeAt)
import System(getArgs)
import System.CPUTime(getCPUTime)
import Foreign.Marshal.Array (withArrayLen)
import Control.Exception(bracket)

data HuffTree  = Leaf Word8 | Branch HuffTree HuffTree 

type A = UArray Int Word8

(!) = unsafeAt

iter = 10

{-- the do_iter function repeats a function iter times
 it is not pretty, but it is hard to convince haskell to 
 repeat a computation many times --}

do_iter 1 func input = let x = func input
   in return x
do_iter k func input =  let x = func input
in seq (last x) (do_iter (k-1) func input)

main =
do 
 [arg] <- getArgs
 handle <- openFile arg ReadMode
 let size = 200
 arrM <- newArray (0,pred size) 0 :: IO (IOUArray Int Word8)
 read_size <- hGetArray handle arrM size
 -- convert to immutable array
 arr <- unsafeFreeze arrM :: IO (UArray Int Word8)
 t0 <- getCPUTime
 res <- do_iter iter huff arr
 t1 <- getCPUTime
 putStr ((show ((fromInteger(t1-t0)::Float)/(1.0::Float
 bracket (openBinaryFile (arg++".haskell") WriteMode)
 hClose
 (\file -> withArrayLen res (flip (hPutBuf file)))

huff:: A -> [Word8]
huff arr  = let (hufftree, newindex) = build_tree 4 arr 
limit = get_32bit_int newindex arr
in huffdecode ((newindex+4)*8) arr hufftree (limit+((newindex+4)*8))

huffdecode :: Int -> A -> HuffTree -> Int -> [Word8]
huffdecode index arr tree limit = helper index tree
  where helper index (Leaf charval) | index == limit = []
| otherwise  = charval : helper index 
tree 
helper index (Branch left right) | index `seq` True = 
helper (index+1) (if get_bit arr index then right else left)

get_bit :: A -> Int -> Bool
{-# INLINE get_bit #-}
get_bit arr bitoffset =
let byte = arr ! (shiftR bitoffset 3)
in testBit (shiftL byte (bitoffset .&. 7)) 7

build_tree :: Int->A->(HuffTree,Int)
build_tree index arr =
let size = get_16_bitint index arr
build_tree_2 index limit
| (limit-index) == 1 = Leaf (arr ! index)
| otherwise  = let left_size = get_16_bitint index arr
   in Branch (build_tree_2 (index+2)   
(index+2+left_size))
 (build_tree_2 (index+4+left_size) 
limit  )
in (build_tree_2 (index+2) (index+2+size)
   ,(index+2+size))

get_16_bitint :: Int -> A -> Int
{-# INLINE get_16_bitint #-}
get_16_bitint index arr =
(shiftL (fromIntegral (arr ! index)) 8) .|. 
(fromIntegral (arr ! (index+1)))

get_32bit_int :: Int -> A -> Int
{-# INLINE get_32bit_int #-}
get_32bit_int index arr =
(shiftL (fromIntegral (arr ! index)) 24) .|. 
(shiftL (fromIntegral (arr ! (index+1))) 16) .|.
(shiftL (fromIntegral (arr ! (index+2))) 8) .|. 
(fromIntegral (arr ! (index+3))) 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bit streams programs in Haskell

2006-03-22 Thread David F. Place
One thing I noticed, is that you are measuring IO in the Haskell  
version of drop3.  hGetContents is lazy.


On Mar 22, 2006, at 4:43 PM, Per Gustafsson wrote:


Also, perhaps our mind might be suffering
from severe case of strictness and might be completely unable to  
`think
lazily'. So, we request your help in noticing obvious NO-NOs and  
stupid

mistakes that we might have made.



David F. Place
mailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-22 Thread Chris Kuklewicz
Robert Dockins wrote:
> 
> On Mar 22, 2006, at 2:16 PM, David F. Place wrote:
> 
>> Hi All,
>>
>> I really appreciate all the help I received when I asked you to
>> critique my PrefixMap module a few weeks ago.  I think I am making
>> good progress in correcting the "lisp" in my Haskell programming. 

The style of the code and choice of names is good.

>> I'll be very grateful to anyone who can take a glance at the attached
>> short program and say if any unidiomatic usages pop out.
> 
> 
> That '(check s) . (take 1)' bit looks a little odd to me.  I would
> simply have written 'check' to match like:
> 
> check puzzle [] = 
> check puzzle (solution : _ ) = 
> 

A simpler version of replace:

replace :: Sudoku -> Int -> Int -> Int -> Sudoku
replace s r c x =
  let (above,row:below) = splitAt r s
  (left,_:right) = splitAt c row
  in above++((left++(x:right)):below)

And a simpler version of toList in keeping with your style:

toList :: Set -> [Int]
toList i = concatMap f [9,8..1]
where
  f b = if testBit i b then [b] else []

(The above is also a little less prone to off-by-one errors since testBit is the
opposite of setBit)

> 
> Also, I like to put off doing IO as long as possible, so I'd probably
> have 'sodoku' return a String or [String] and move the putStr into
> main.  Its an easy way to make your code more reusable.
> 
> Also, your parser is pretty hackish (but I suspect you knew that already).
> 
A minimal change to the parser that still does no sanity checking but may be a
little more robust is

import Data.Char

readSudoku :: [String] -> String -> Sudoku
readSudoku ["line"] input =
takeBy 9 $ map digitToInt $ filter isDigit $ head $ lines input
readSudoku _ input =
map (map digitToInt . filter isDigit) $ lines input


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bit streams programs in Haskell

2006-03-22 Thread Per Gustafsson


Haskell gurus,

We have made a proposal to extend the Erlang `binary' data type from
being a sequence of bytes (a byte stream) to being a sequence of bits (a
bitstream) with the ability to do pattern matching at the bit level.

This proposal has now been fully implemented all
these at the level of the BEAM virtual machine and in the HiPE
compiler. Most probably, they will be part of the next major
Erlang/OTP open source release. (We write "most probably" because we
do not really control what Ericsson desides to release as part of its
open source system.)

We wanted to evaluate the performance of our implementation and the
succintness of our syntax, particularly against other `similar'
languages. For this reason, we wrote five reasonably representative
benchmarks, showing the things that one could employ bit stream pattern
matching and bit-level comprehensions for.

The benchmarks (drop3, five11, huffman, uudecode, and uuendode) have
all been written in Erlang, O'Caml and Haskell. For some of them, C
and Java versions exist. They can be found in the following homepage:

  http://bitbenches.infogami.com/

As you will see there, the Haskell numbers are significantly slower
than those of Erlang and O'Caml. We are wondering why this is so.

For each language, we have spent a considerable effort in writing the
benchmarks in -- at least what we feel -- is the most natural and
efficient way one can write them.

The only constraint we impose is that for functional languages, data
structures without any explicit mutation have to be used in the part
of the program for which measurements are taken.

Our experience in writing efficient (and beautiful) Haskell programs is
close to (if not below) zero. Also, perhaps our mind might be suffering
from severe case of strictness and might be completely unable to `think
lazily'. So, we request your help in noticing obvious NO-NOs and stupid
mistakes that we might have made. We even welcome completely different
Haskell programs provided they adhere to the constraint mentioned
above -- no mutation.

Best regards,

Kostis Sagonas and Per Gustafsson


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-22 Thread Robert Dockins


On Mar 22, 2006, at 2:16 PM, David F. Place wrote:


Hi All,

I really appreciate all the help I received when I asked you to  
critique my PrefixMap module a few weeks ago.  I think I am making  
good progress in correcting the "lisp" in my Haskell programming.   
I'll be very grateful to anyone who can take a glance at the  
attached short program and say if any unidiomatic usages pop out.



sudoku :: Sudoku -> IO ()
sudoku s = ((mapM_ putStrLn) . (check s) . (take 1) . solveSudoku) s



check puzzle [] = [showSudoku puzzle,"No solutions."]
check puzzle [solution]
  | solution `solves` puzzle =
  ["Puzzle:",showSudoku puzzle,"Solution:",showSudoku  
solution]

  | otherwise = ["Program Error.  Incorrect Solution!"]



That '(check s) . (take 1)' bit looks a little odd to me.  I would  
simply have written 'check' to match like:


check puzzle [] = 
check puzzle (solution : _ ) = 


Also, I like to put off doing IO as long as possible, so I'd probably  
have 'sodoku' return a String or [String] and move the putStr into  
main.  Its an easy way to make your code more reusable.


Also, your parser is pretty hackish (but I suspect you knew that  
already).



FYI, solveSudoku has a bug; if you enter an invalid puzzle it will  
return non-solutions.



It solves sudoku puzzles.  (What pleasure do people get by doing  
these in their heads?!?)


I have no idea.


Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-22 Thread Jared Updike
On 3/22/06, David F. Place <[EMAIL PROTECTED]> wrote:
> Hi All,
>
> I really appreciate all the help I received when I asked you to
> critique my PrefixMap module a few weeks ago.  I think I am making
> good progress in correcting the "lisp" in my Haskell programming.
> I'll be very grateful to anyone who can take a glance at the attached
> short program and say if any unidiomatic usages pop out

Try

> cellIndex r c = 3*(r `div` 3) + c `div` 3

It's much much shorter and should produce the same results.

> It solves
> sudoku puzzles.  (What pleasure do people get by doing these in their
> heads?!?)
>

They are probably asking the same question: why take hours to write a
program to do it when with my mad sudoku solving skills I can solve it
in X seconds? My roommate is like this.

Cheers,
   Jared.

--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Code Review: Sudoku solver

2006-03-22 Thread David F. Place

Hi All,

I really appreciate all the help I received when I asked you to  
critique my PrefixMap module a few weeks ago.  I think I am making  
good progress in correcting the "lisp" in my Haskell programming.   
I'll be very grateful to anyone who can take a glance at the attached  
short program and say if any unidiomatic usages pop out.  It solves  
sudoku puzzles.  (What pleasure do people get by doing these in their  
heads?!?)


Cheers, David



sudoku.hs
Description: Binary data



David F. Place
mailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wheres this going wrong

2006-03-22 Thread Udo Stenzel
Neil Rutland wrote:
> ttyyppee LLiinnee == 
> [[((((SSttrriinngg,,SSttrriinngg)),,((SSttrriinngg,,IInntt)),,((SSttrriinngg,,IInntt)),,((SSttrriinngg,,BBooooll)),,
> ((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll)),,
> ((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,BBooooll))))]]

What's wrong with a record?

*> data Line = Line { a1 :: String, a2 :: Int, ... }

While you're at it, you might want to give the fields sensible names.


> Anyway when i enter something such as lookup "a1" i get back a load of stuff
> about Eq.

lookup expects a list of pairs, but you're passing it a tuple.  A list
would have to be homogenous, your tuple isn't, therefore lookup cannot
do what you want.  Just use a record.


Udo.
-- 
Languages shape the way we think, or don't. -- Erik Naggum


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wheres this going wrong

2006-03-22 Thread Sebastian Sylvan
On 3/22/06, Neil Rutland <[EMAIL PROTECTED]> wrote:
>
>
>
> Hi there,
>
> Thanks to some advise by one of the other posters i have chosen to try and
> set up a list that uses lookup to find the values of the elements within it.
>
> However what i have attempted so far has resulted in odd answers or errors.
> Anyway here it is, i have given each element a string at the start to put
> the lookup domain in - anyway here it is
>
> type Line =
> [((String,String),(String,Int),(String,Int),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool))]
>
> vicsLine :: Line
> vicsLine = [(("a1","Walthamstow
> Central"),("a2",1),("a3",2),("a4", False), ("a5", True),
> ("a6", False), ("a7", False), ("a8", False), ("a9", False), ("a10", False),
> ("a11", False), ("a12", False))]
>
> Anyway when i enter something such as lookup "a1" i get back a load of stuff
> about Eq.
>
> So the question is - what am i doing wrong. I am hoping that when i enter a1
> it should return for me Walthamstow Central.
>

What shoul happen if you enter "a2"?
lookup takes a "key" and  a list of key/value pairs, and maybe returns
the value.
For instance, one list may look like this:
db = [(1,"Hello"), (2,"world")]

If you then use 'lookup 1 db', you'd get 'Just "Hello"', if you type
'lookup 12 db' you'd get 'Nothing' since there is no pair where 12 is
the first value.

Now, it's important that the list you pass to lookup is of the form: [(a,b)]
In other words it MUST be a list of PAIRS. The second value of the
pair may be of any type (including a complex type with lists and
tuples and what-not) but it must be the SAME type for all the elements
in the list. This isn't just a restriction on lookup, btw, the
elements of a list must always be of the same type:
OK: [(1,"hello"),(2,"bye")]
Not OK: [(2,"hello"),(2,14)] -- 14 has a different type than "hello"!

So, what I think you want is something like this:

type Name = String
type Minutes = Int

type StationInfo = [Line] -- maybe something more here?
type Station = (Name,StationInfo)

type LineInfo = [(Minutes, Station)] -- maybe somthing more here?
type Line = (Name,LineInfo)

-- use lookups on these two
-- Its important that both Station, and Line are of the form (a,b)
(and not, say (a,b,c))
type StationDB = [Station]
type LineDB = [Line]

StationInfo would then be a large tuple, perhaps containing a list of
the names of the lines which pass through it (then you could have
another list containing these lines which would map the name of a line
to a LineInfo which would, I suppose, contain a list of station
names).

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Wheres this going wrong

2006-03-22 Thread Neil Rutland

Hi there,
Thanks to some advise by one of the other posters i have chosen to try and set up a list that uses lookup to find the values of the elements within it.
However what i have attempted so far has resulted in odd answers or errors. Anyway here it is, i have given each element a string at the start to put the lookup domain in - anyway here it is
type Line = [((String,String),(String,Int),(String,Int),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool),(String,Bool))]
vicsLine :: LinevicsLine = [(("a1","Walthamstow Central"),("a2",1),("a3",2),("a4", False), ("a5", True), ("a6", False), ("a7", False), ("a8", False), ("a9", False), ("a10", False), ("a11", False), ("a12", False))]
Anyway when i enter something such as lookup "a1" i get back a load of stuff about Eq.
So the question is - what am i doing wrong. I am hoping that when i enter a1 it should return for me Walthamstow Central.
Cheers everyone - i'm getting there slowly and all your help is much appreciated.
Neil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-22 Thread Isaac Jones
I think someone should volunteer to set up "Planet Haskell" ala Planet
Debian, Planet Gnome, Planet Perl, etc.

These sites are "Blog aggregators".  Basically they just collect the
RSS feeds of the community and post their blogs to a web page in a
cute format (the gnome one is especially cute, but you probably could
have guessed that).

There's already software out there for this, so nothing new needs to
be written.  I think we need a volunteer to set this up somewhere?
Preferably someone with their own server, and we'll worry about
setting up the DNS later :)

peace,


  isaac

See:

http://planet.debian.org/
http://planet.gnome.org/
http://planet.perl.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Porting GHC to OSX86?

2006-03-22 Thread Gregory Wright


Hi,

DP will support the i386 build as soon as Wolfgang makes his
changes available.  As I understand, from earlier messages on one
of the ghc* lists, this is almost done for the pre-6.6 branch, but not
yet backported to the 6.4.x branch.

Also, DP uses a binary bootstrap compiler to build ghc, rather than
starting from the .hc files.  I've been meaning to try it, but I can't
promise any schedule as work and life have distracted me from
code recently.

Best Wishes,
Greg

(darwinports ghc maintainer)


On Mar 22, 2006, at 6:16 AM, Deling Ren wrote:


It's not supported on i386 platform yet :(

On Mar 22, 2006, at 12:34 AM, Thomas Davie wrote:



On Mar 21, 2006, at 8:09 PM, Deling Ren wrote:


Hi there,

Has anyone made any attempt to port GHC to Mac OS X on x86?  
Wolfgang Thaller’s binary package runs over Rosetta but slow (not  
surprising). It can not be used to compile a native version  
either (I got some errors related to machine registers).


I tried to do a bootstrap but can't find the ".HC" files  
mentioned in the manual. They don't seem to be on the download  
page of GHC. Any ideas?


Why not use darwin ports to build it?

Bob


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Reading files efficiently

2006-03-22 Thread Simon Marlow

Donald Bruce Stewart wrote:


Well, I know this works:

$ cat A.lhs
#!/usr/bin/env runhaskell
> main = putStrLn "gotcha!"

$ ./A.lhs 
gotcha!


But for files with no .hs or .lhs extension? Anyone know of a trick?


GHC 6.6 will allow this, because we added the -x flag (works just like 
gcc's -x flag).  eg. "ghc -x hs foo.wibble" will interpret foo.wibble as 
a .hs file.  I have an uncommitted patch for runghc that uses -x, I need 
to test & commit it.


Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Porting GHC to OSX86?

2006-03-22 Thread Deling Ren

It's not supported on i386 platform yet :(

On Mar 22, 2006, at 12:34 AM, Thomas Davie wrote:



On Mar 21, 2006, at 8:09 PM, Deling Ren wrote:


Hi there,

Has anyone made any attempt to port GHC to Mac OS X on x86?  
Wolfgang Thaller’s binary package runs over Rosetta but slow (not  
surprising). It can not be used to compile a native version either  
(I got some errors related to machine registers).


I tried to do a bootstrap but can't find the ".HC" files mentioned  
in the manual. They don't seem to be on the download page of GHC.  
Any ideas?


Why not use darwin ports to build it?

Bob


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: strange ghc program behaviour

2006-03-22 Thread Koen . Roelandt
>From ghc-6.4, the runtime system no longer flushes open files; it
>truncates them instead.  You should close (or flush) the file explicitly
>with 'hClose' or 'hFlush' before the program terminates.


I added 'hClose' to processXmlWith in the Wrapper module. That solved the 
problem.
Thank you!
Malcolm, concerning HaXml choking on finding an ampersand (or %) in an 
attribute value (my earlier post): this occurred when the ampersand was 
part of an entity. I solved it by replacing the values for & and % in the 
Lex module (not very elegant, I admit). 

Cheers,

K.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Porting GHC to OSX86?

2006-03-22 Thread Thomas Davie


On Mar 21, 2006, at 8:09 PM, Deling Ren wrote:


Hi there,

Has anyone made any attempt to port GHC to Mac OS X on x86?  
Wolfgang Thaller’s binary package runs over Rosetta but slow (not  
surprising). It can not be used to compile a native version either  
(I got some errors related to machine registers).


I tried to do a bootstrap but can't find the ".HC" files mentioned  
in the manual. They don't seem to be on the download page of GHC.  
Any ideas?


Why not use darwin ports to build it?

Bob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Returning a list element?

2006-03-22 Thread Dominic Steinitz
Donald Bruce Stewart  cse.unsw.edu.au> writes:

> > mainMenu =
> >sequence_ $ map putStrLn ["line1", "line2", "line3"]
> 
> I argue if you want to sequence_ a map you should write mapM_:
> 
> mapM_ putStrLn ["line1", "line2", "line3"]

Nice

> 
> mapM is under-appreciated? More under-appreciated are line gaps:
> 
> main = putStr "line1\n\
>   \line2\n\
>   \line3\n"
> 

Or if you don't like hand writing in all the newlines you could use

   putStrLn . concat . intersperse "\n"
   



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe