[Haskell-cafe] Fwd: shootout

2011-07-30 Thread Ben
hello cafe-istas --

for those of you who are into these things, a lot of the shootout programs are 
suffering from make errors and thus do not have benchmarks.

http://shootout.alioth.debian.org/u64q/haskell.php

best, ben

Begin forwarded message:

 From: Don Stewart don...@gmail.com
 Date: July 30, 2011 9:52:12 AM PDT
 To: Ben midfi...@gmail.com
 Cc: Don Bruce Stewart d...@cse.unsw.edu.au
 Subject: Re: shootout
 
 Best to bring this up on haskell-cafe@
 
 On Sun, Jul 31, 2011 at 12:34 AM, Ben midfi...@gmail.com wrote:
 FYI, a lot of the haskell programs on the shootout suffer from make errors 
 and thus do not have benchmarks.
 
 best, ben


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


[Haskell-cafe] A language that runs on the JVM or .NET has the advantage of Oracle Microsoft making those layers more parallelizable.

2011-07-30 Thread KC
Are there plans a foot (or under fingers) to make a version of Haskell
that runs on the JVM?

-- 
--
Regards,
KC

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


Re: [Haskell-cafe] A language that runs on the JVM or .NET has the advantage of Oracle Microsoft making those layers more parallelizable.

2011-07-30 Thread Henning Thielemann


On Sat, 30 Jul 2011, KC wrote:


Are there plans a foot (or under fingers) to make a version of Haskell
that runs on the JVM?


http://www.haskell.org/haskellwiki/GHC:FAQ#Why_isn.27t_GHC_available_for_.NET_or_on_the_JVM.3F

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


Re: [Haskell-cafe] A language that runs on the JVM or .NET has the advantage of Oracle Microsoft making those layers more parallelizable.

2011-07-30 Thread austin seipp
No, there aren't. At least none that I know of. Don Stewart did work
years ago on a JVM backend for GHC for his Bachelors thesis. You may
be able to find it online (I don't know the name, sorry.) This was
never integrated mainline however.

These questions have been asked many many times, but the real answer
is it's a whole lot of work. Not impossible, but a whole lot of
work. And it's not clear what the ultimate tradeoffs are. See this for
some more info:

http://www.haskell.org/haskellwiki/GHC:FAQ#.NET.2FJVM_Availability

In particular I'm reminded of the story of Don Syme, F# author, who
initially did work I believe for a Haskell.NET compiler, but
inevitably abandoned it and went to create F#. See some of the history
behind F#, SML.NET and Haskell.NET here:

http://www.infoq.com/interviews/F-Sharp-Don-Syme#

In particular you can just look at Don's answers to the related questions.

Hope it helps.

On Sat, Jul 30, 2011 at 5:07 PM, KC kc1...@gmail.com wrote:
 Are there plans a foot (or under fingers) to make a version of Haskell
 that runs on the JVM?

 --
 --
 Regards,
 KC

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




-- 
Regards,
Austin

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


Re: [Haskell-cafe] (no subject)

2011-07-30 Thread Chris Smith
On Sat, 2011-07-30 at 15:07 -0700, KC wrote:
 A language that runs on the JVM or .NET has the advantage of Oracle 
 Microsoft making those layers more parallelizable.

On top of the answers you've got regarding whether this exists, let me
warn you against making assumptions like the above.  There are certainly
good reasons for wanting Haskell to run on the JVM or CLR, but
parallelism doesn't look like one of them.

The problem is that the cost models of things on the JVM or CLR are so
different that if you directly expose the threading and concurrency
stuff from the JVM or CLR, you're going to kill all the Haskell bits of
parallelism.  A huge contribution of Haskell is to have very
light-weight threads, which can be spawned cheaply and can number in the
tens of thousands, if not hundreds of thousands.  If you decide that
forkIO will just spawn a new Java or CLR thread, performance of some
applications will change by orders of magnitude, or they will just plain
crash and refuse to run.  Differences of that scope are game-changing.
So you risk, not augmenting Haskell concurrency support by that of the
JVM or CLR, but rather replacing it.  And that certainly would be a
losing proposition.

Maybe there's a creative way to combine advantages from both, but it
will require something besides the obvious one-to-one mapping of
execution contexts.

-- 
Chris


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


Re: [Haskell-cafe] XCode Dependency for HP on Mac

2011-07-30 Thread Mark Lentczner
Hiho - I'm the maintainer of the Mac installer for HP. I thought I'd
chime in a bit:

On Mac OS X, developer tools is essentially synonymous with Xcode.
That is, to get the set of standard utilities needed for development
on compiled executables (notably the binutils), you install Xcode.
True, it also includes the IDE called Xcode, but the vast bulk of that
installation are things like headers, link libraries, command line
tools, and other utilities for development of compiled executables in
general.

As several have pointed out, you can download Xcode for free. If you
have Lion, you can get Xcode 4 for free from the Mac Store. Xcode 3
for 10.6 and 10.5. Traditionally, Apple has included Xcode on one of
the CD-ROMs that came with a new computer, and/or as an installer
already present on the hard disk. (I haven't bought a new Air...
yet... but perhaps someone can check to see if the Xcode installer is
one the SSD volume already?)

It is conceivably possible to build and distribute some of those
tools, but not the whole bundle. But the difficulty of getting such a
build just right, and all the pieces in the right place, seems absurd
to attempt to recreate when Apple has done it, and gives it away for
free. Apple's versions of bintools also includes many extensions extra
options for the OS X environment (like supporting multi-arch binaries)
Finally, there is also licensing questions regarding the parts
supplied by the OS vendor (headers, stub libs, debug libs, etc)

Given the above, perhaps it is a little more clear why we choose to
not include the system development tools in the Haskell Platform
installer.

- Mark

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


Re: [Haskell-cafe] Fwd: shootout

2011-07-30 Thread Thorsten Hater
Good Evening,

can anybody confirm that this implementation is somewhat faster
than the current benchmark (at expense of memory consumption)?

Cheers, Thorsten


On 30.07.2011 23:08, Ben wrote:
 hello cafe-istas --

 for those of you who are into these things, a lot of the shootout programs 
 are suffering from make errors and thus do not have benchmarks.

 http://shootout.alioth.debian.org/u64q/haskell.php

 best, ben

 Begin forwarded message:

 From: Don Stewart don...@gmail.com
 Date: July 30, 2011 9:52:12 AM PDT
 To: Ben midfi...@gmail.com
 Cc: Don Bruce Stewart d...@cse.unsw.edu.au
 Subject: Re: shootout

 Best to bring this up on haskell-cafe@

 On Sun, Jul 31, 2011 at 12:34 AM, Ben midfi...@gmail.com wrote:
 FYI, a lot of the haskell programs on the shootout suffer from make 
 errors and thus do not have benchmarks.

 best, ben

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

{-# LANGUAGE BangPatterns #-}
module Main where

import System.Environment

import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as C
import qualified Data.ByteString as S
import Data.ByteString.Internal

import Data.Word

-- Look Up Table
data P = P !Word8 !Float
type LUT =  [P]

iubs, homs :: LUT
iubs = cdf [('a',0.27),('c',0.12),('g',0.12),('t',0.27),('B',0.02)
   ,('D',0.02),('H',0.02),('K',0.02),('M',0.02),('N',0.02)
   ,('R',0.02),('S',0.02),('V',0.02),('W',0.02),('Y',0.02)]

homs = cdf [('a',0.3029549426680),('c',0.1979883004921)
   ,('g',0.1975473066391),('t',0.3015094502008)]

-- compile LUT from assoc list
cdf :: [(Char,Float)] - LUT
cdf ls = reverse $ cdf' [] 0 ls
where cdf' acc _ [] = acc
  cdf' acc !c ((v,k):ls) = cdf' ((P v' c'):acc) c' ls
  where !c'  = k + c
!v' = c2w v

-- extract Char from List by Key
choose :: LUT - Float - Word8
choose lut !f = choose' lut
where choose' ((P v k):ls)| f = k = v
  | otherwise = choose' ls

-- PRNG
im, ia, ic :: Int
im  = 139968
ia  = 3877
ic  = 29573

data R = R !Float !Int

imd :: Float
imd = fromIntegral im

rand :: Int - R
rand seed = R newran newseed
where
!newseed = (seed * ia + ic) `rem` im
!newran  = (fromIntegral newseed) / imd
-- /PRNG

-- Write properly aligned output
fasta !n s | n = 60   = go ts t n 60
   | otherwise = go ts t n n
where (t:ts) = L.toChunks s
  go ss s !n !m | n == 0  = return ()
| ll   m = S.putStr   l  go (tail ss) (head ss) (n-ll) (m-ll)
| ll == m  n' = 60 = S.putStrLn l  go ss r n' 60
| ll == m  n'   60 = S.putStrLn l  go ss r n' n'
  where (l,r) = S.splitAt m s
ll = S.length l
!n' = n-m

-- build cache from PRNG
data Q = Q !Int !Int

cacheUF ls = L.unfoldr go $ Q 42 139968
  where go (Q _ 0)  = Nothing
go (Q sd n) = Just (choose ls f, Q s (n-1))
where (R f s) = rand sd

alu =  C.pack GGCCGGGCGCGGTGGCTCACGCCTGTAATCCCAGCACTTTGG\
   \GAGGCCGAGGCGGGCGGATCACCTGAGGTCAGGAGTTCGAGA\
   \CCAGCCTGGCCAACATGGTGAAAGTCTCTACTAT\
   \ACATTAGCCGGGCGTGGTGGCGCGCGCCTGTAATCCCA\
   \GCTACTCGGGAGGCTGAGGCAGGAGAATCGCTTGAACCCGGG\
   \AGGCGGAGGTTGCAGTGAGCCGAGATCGCGCCACTGCACTCC\
   \AGCCTGGGCGACAGAGCGAGACTCCGTCTCA

fastas n = do putStrLn  ONE Homo sapiens alu
  fasta (n*2) $ L.cycle alu
  putStrLn TWO IUB ambiguity codes
  fasta (n*3) $ L.cycle $ cacheUF iubs
  putStrLn THREE Homo sapiens frequency
  fasta (n*5) $ L.drop d $ L.cycle $ cacheUF homs
where  d = fromIntegral (n*3) `mod` 139968

main = do n - getArgs = readIO . head
  fastas n
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe