[Haskell-cafe] Guidance on using asynchronous exceptions

2007-11-15 Thread Yang

To follow up on my previous post ("Asynchronous Exceptions and the
RealWorld"), I've decided to put together something more concrete in
the hopes of eliciting response.

I'm trying to write a library of higher-level concurrency
abstractions, in particular for asynchronous systems programming. The 
principal goal here is composability and safety. Ideally, one can apply 
combinators on any existing (IO a), not just procedures written for this 
library. But that seems like a pipe dream at this point.


In the code below, the running theme is process orchestration. (I've put 
TODOs at places where I'm blocked - no pun intended.)


I'm currently worried that what I'm trying to do is simply impossible in
Concurrent Haskell. I'm bewildered by the design decisions in the
asynchronous exceptions paper. I'm also wondering if there are any
efforts under way to reform this situation. I found some relevant
posts below hinting at this, but I'm not sure what the status is
today.

(Something like this is straightforward to build if I abandon
Concurrent Haskell and use cooperative threading, and if the
operations I wanted to perform could be done asynchronously.)

Relevant papers
---

http://citeseer.ist.psu.edu/415348.html
http://research.microsoft.com/users/simonpj/papers/concurrent-haskell.ps.gz
http://www.haskell.org/~simonmar/papers/web-server.ps.gz

Relevant posts/threads
--

http://osdir.com/ml/lang.haskell.prime/2006-04/msg00032.html
http://osdir.com/ml/lang.haskell.general/2001-11/msg00131.html
http://www.haskell.org/pipermail/haskell-prime/2006-April/001280.html
http://www.haskell.org/pipermail/haskell-prime/2006-April/001290.html
http://www.nabble.com/throwTo---block-statements-considered-harmful-tf2780268.html#a7758038
http://www.nabble.com/What-guarantees-(if-any)-do-interruptible-operations-have-in-presence-of-asynchronous-exceptions--tf2761696.html#a7699555

Misc


http://lambda-the-ultimate.org/node/1570
Advanced Exception Handling Mechanisms
http://www.springerlink.com/content/3723wg2t81248027/
http://64.233.169.104/search?q=cache:c4pS0FDKMXcJ:www.cs.ioc.ee/tfp-icfp-gpce05/tfp-proc/06num.pdf+concurrency+interrupts+abort+safe+asynchronous+exceptions+threads&h
http://64.233.169.104/search?q=cache:hmC-jl-iNkoJ:www.jot.fm/issues/issue_2007_11/article4.pdf+concurrency+interrupts+abort+safe+asynchronous+exceptions+threads&hl=en
http://www.mathematik.uni-marburg.de/~eden/paper/edenEuropar03.pdf


Code


module Main where

import Control.Concurrent
import Control.Concurrent.MVar
import Control.Exception
import Control.Monad
import Prelude hiding (log)
import System.IO
import System.Posix.Signals
import System.Process

log = putStrLn

startProc cmd = runCommand cmd
stopProc  p   = terminateProcess p
waitProc  p   = waitForProcess p

-- Run a process, blocking on it until it exits. If we're interrupted,
-- terminate the process. (IIRC, terminateProcess issues SIGTERM, and
-- the documentation is buggy; more detailed code should go here later
-- to retry with SIGKILL.)
runProc cmd = do
  log "launching proc"
  p <- startProc cmd
  waitProc p-- TODO allow interrupts only at this point
`finally` ( log "stopping" >> stopProc p >> log "stopped" )

-- Sleep for n seconds.
timeout n = do
  log "sleeping"
  threadDelay (n * 100) -- TODO allow interrupts only at this point
  log "waking"

-- TODO is there any way to block *only* the Cancel exception? (Even
-- if this could be done, though, it's still not a modular approach.)
spawn :: IO a -> (a -> IO ()) -> IO ThreadId
spawn f y = forkIO (block (f >>= y))

-- The any/sum/choice combinator. On return, guarantee that both tasks
-- have stopped.
(<|>) :: IO a -> IO b -> IO (Either a b)
a <|> b = do
  result <- newEmptyMVar :: IO (MVar (Either a b))
  tida   <- newEmptyMVar :: IO (MVar ThreadId)
  tidb   <- newEmptyMVar :: IO (MVar ThreadId)

  let yield lr x = do let name = case lr x of
   Left  _ -> "a"
   Right _ -> "b"
  log $ "saving result of " ++ name
  putMVar result (lr x)
  log $ "saved result of " ++ name

  let other = case lr x of
Left  _ -> tidb
Right _ -> tida
  log "taking other"
  t <- takeMVar other
  log "killing other"
  -- Later: replace the following with a throwTo
  -- so as to notify (rather than kill) the thread
  -- with a Cancel
  killThread t

  ta <- spawn a (yield Left)
  tb <- spawn b (yield Right)
  putMVar tida ta
  putMVar tidb tb

  log "waiting for result"
  res <- takeMVar result

  -- TODO wait for both tasks to have stopped

  log "returning result"
  return res

-- simple test --

cmd1 = "for i in `seq 1`; do sleep 1; echo hel

Re: [Haskell-cafe] Using Data.Binary for compression

2007-11-15 Thread David Roundy
On Thu, Nov 15, 2007 at 11:10:01AM -0800, Chad Scherrer wrote:
> > > Almost all 'real users' just use Codec.Compression.GZip.  It's very
> > > fast, very compositional, and (perhaps suprisingly) almost as
> > > effective as application-specific schemes.
> >
> > I was about to say the same thing. So so much simpler to use Duncan's
> > carefully written zlib binding,
> 
> I have several types of symbols, and for each type the probabilities
> are very predictable - to the point where they could even be
> hard-coded. And upon completion I can be sure the first two questions
> will be "Can we make it smaller?" and "Can we make it faster?". GZip
> (while very cool) is adaptive and general-purpose, so it's building
> frequency tables as it goes and ignoring the structure of the data I
> should be able to take advantage of.
> 
> With an awful lot of trouble, it must be possible to write something
> in C to go faster and yield better compression than gzip for this
> particular data. With the probability structure known in advance,
> there are just a lot of steps taken by gzip that are no longer needed.
> Besides this, gzip only assumes an arbitrary sequence of bytes, but my
> data are much more structured than this.

The catch is that gzip can beat even ideal arithmetic compression, if there
happen to be correlations between symbols.  So what you claim is correct
only if there are no correlations other than those taken into account in
your known probability structure.  Any chance you can tell us what this
mysterious data is?

But bit stream operations (and data compression) are seriously cool in any
case, so I hope you'll go ahead with this!
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskellforge?

2007-11-15 Thread Maurí­cio

Hi,

Is there a "Haskellforge" somewhere, i.e.,
something like a sourceforge for open source
Haskell programs, with darcs, automatic
cabalization etc.? Has anyone tried that
already?

Maurício

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


Re: [Haskell-cafe] let vs. where

2007-11-15 Thread jeff p
Hello,

> 
> taxRate = 0.06
>
> total cart = subtotal + tax
>   where
> subtotal = sum cart
> taxable  = filter isTaxable cart
> tax = (sum taxable) * taxRate
>
> This example defines two functions, taxRate, which returns a constant
> value, and total, which computes the total cost of the list of items
> in a shopping cart. (Although the taxRate definition appears to be
> defining a variable, it's best to think of it as a constant function,
> a function that takes no parameters and always returns the same
> value.) The definition of total is quite expressive, and highlights
> the intent of the function, by isolating and naming important
> sub-expressions in the computation. (total also refers to an isTaxable
> function, not presented here.)
> 
>
This explanation is just wrong.

A function is an expression whose type is an arrow; e.g. Int -> Int.
The type of taxRate is (Fractional t) => t. There is some leeway for
taxRate to be a function if someone provided a Fractional instance for
a function type; but that seems to be beyond the scope of the quoted
text which comes from an introductory explanation.

Furthermore, a constant function is a function which ignores its
argument; e.g. \x -> 0.06

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


RE: [Haskell-cafe] Erik Meijer's talk at Google?

2007-11-15 Thread Ghuloum, Anwar
I think google talks are often hosted at video.google.com, assuming the
speaker agrees to this and it can be publicly disclosed.

 

--

Anwar Ghuloum 葛安华

Microprocessor Technology Lab, Intel

  _  

From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]
org] On Behalf Of Galchin Vasili
Sent: Thursday, November 15, 2007 7:39 PM
To: haskell-cafe@haskell.org
Cc: Galchin Vasili
Subject: [Haskell-cafe] Erik Meijer's talk at Google?

 

Hello,

 Last week (?)  Erik Meijer gave a talk at Google. Has a video been
uploaded somewhere?

Kind regards, Vasya



smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] the "interact" function and Hugs/ghci on Windows ...

2007-11-15 Thread Justin Bailey
On Nov 15, 2007 6:25 PM, Galchin Vasili <[EMAIL PROTECTED]> wrote:
> Hello,
>
>  I have a Haskell script that contains several functions that are
> implemented in terms on "interact". When I do a "function application",
> Hugs/ghci is waiting for input from stdin. How do one denote EOF from stdin,
> so that the function evaluation can continue and do the IO () action , ie..
> write to stdout?

Usually CTRL-D or CTRL-Z.

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


[Haskell-cafe] the "interact" function and Hugs/ghci on Windows ...

2007-11-15 Thread Galchin Vasili
Hello,

 I have a Haskell script that contains several functions that are
implemented in terms on "interact". When I do a "function application",
Hugs/ghci is waiting for input from stdin. How do one denote EOF from stdin,
so that the function evaluation can continue and do the IO () action , ie..
write to stdout?

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


[Haskell-cafe] Performance problems with parallelizing QuickCheck using channels (Control.Concurrent.Chan)

2007-11-15 Thread Gwern Branwen
So I've been trying to get my QuickCheck tests to run in parallel. I did take a 
look at Don's Parallel QuickCheck library 
, but I didn't like how much code it 
had in it and I figured it'd be a good exercise to try to do myself.

After quite a lot of help from the good folk of #haskell, I eventually came up 
with this:
  module Pcheck (parTest, parCheck) where

  import Control.Monad (replicateM_, liftM)
  import Control.Concurrent.Chan (newChan, writeChan, getChanContents)
  import Control.Concurrent (forkIO)
  import Test.QuickCheck (quickCheck', Testable())

  -- | Takes a list of functions using parCheck, and returns True iff all return
  -- True. Evaluates them in parallel.
  parTest :: [IO Bool] -> IO Bool
  parTest = andTest . parList
  where andTest :: IO [Bool] -> IO Bool
andTest = liftM and

  {- | Test in parallel. Forks off a QuickCheck 'n' times; QuickCheck tests 
using
   the proposition 't'. Returns True if all tests were passed, else
   False. Should be run with parallelizing options like with +RTS -N4 -RTS 
&etc. -}
  parCheck :: (Testable prop) => prop -> Int -> IO Bool
  parCheck t n = do chan <- newChan
replicateM_ n $ forkIO $ (writeChan chan) =<< (quickCheck' 
t)
liftM (and . take n) $ getChanContents chan

  -- | Takes a list of functions (presumably using parCheck) and evaluates all 
in parallel.
  parList :: [IO a] -> IO [a]
  parList fs = do chan <- newChan
  mapM_ (\m -> forkIO $ m >>= writeChan chan) fs
  liftM (take n) $ getChanContents chan
  where n = length fs

I liked how simple the Channels library 

 seemed to be; I could just pass the channel as an argument and have every 
forkIO'd test simply chuck its Boolean result into it when done - which seem'd 
much simpler than using MVars and the other techniques for returning stuff from 
forkIO threads.

And so it compiles, it runs tests correctly, and so on. But the problem is that 
it does so slowly. I have another module of equations about nuclear bombs 
called nuke.hs, which has a number of QuickCheck properties defined. Here's 
what happens when main is defined as 'parTest [the various tests..]':

 ./nuke +RTS -N7 -sstderr -RTS 40.57s user 46.55s system 116% cpu 1:14.61 total
 ./nuke +RTS -N6 -sstderr -RTS 40.72s user 47.66s system 117% cpu 1:15.50 total
 ./nuke +RTS -N5 -sstderr -RTS 42.33s user 49.08s system 116% cpu 1:18.67 total
 ./nuke +RTS -N4 -sstderr -RTS 43.71s user 48.41s system 117% cpu 1:18.48 total
 ./nuke +RTS -N3 -sstderr -RTS 41.51s user 48.25s system 114% cpu 1:18.10 total
 ./nuke +RTS -N2 -sstderr -RTS 42.28s user 47.18s system 115% cpu 1:17.39 total
 ./nuke +RTS -N1 -sstderr -RTS 27.87s user 18.40s system 99% cpu 46.498 total

(From ; compiled as "=ghc -v --make -threaded -O2 
./nuke.hs".)

For some reason, running the parallel tests with a single thread is faster than 
running with 4 threads (I have a quad-core Intel processor)? I find this 
counter-intuitive to say the least. the par* functions are indeed operating in 
parallel, as evidenced by it using more than 100% CPU time, or, running on 
multiple cores, and all the tests are passed as True in both -N1 and -N[2-7] 
versions, so -N1 can't be bailing out early due to "and"'s laziness, and in 
general everything seems to be written correctly.

I am perplexed by this. Is Chan simply a very inefficient way of parallelizing 
things? Is it not as parallel as I think? Or am I missing something else 
entirely?

(Attached is the source of nuke.hs and pcheck.hs, as well as some data from 
-sstderr.)

--
gwern
.45 GIGN jya. wire ISI SADCC JPL embassy Recon World
-- module Nuke (main)
--   where
-- TODO: work in radiation deaths.

import Pcheck
import Test.QuickCheck
import Monad (liftM3)

{- For many equations and results, it is nonsensical to have negative results, but we don't want
to use solely natural numbers because then we lose precision. So we define a PosReal type which tries
to define the subset of real numbers which are 0 or positive; this way the type system checks for negative
results instead of every other function having conditionals checking for negative input or output. -}
newtype PosReal = MakePosReal Float deriving (Show, Eq, Ord)

-- Basic numerical operations on positive reals
instance Num PosReal where
fromInteger = toPosReal . fromInteger
x + y = MakePosReal (fromPosReal x + fromPosReal y)
x - y = toPosReal ((fromPosReal x) - (fromPosReal y))
x * y = MakePosReal (fromPosReal x * fromPosReal y)
abs x | x >= 0 = x
  | otherwise = x * (-1)
signum x | x >= 0 = 1
 | otherwise = (-1)

-- Define division on PosReals
instance Fractional PosReal where
x / y = toPosReal ((fromPosReal x) / (fromPosReal y))
fromRational x = MakePo

Re: [Haskell-cafe] let vs. where

2007-11-15 Thread Lennart Augustsson
No, Haskell functions take exactly one argument.

On Nov 14, 2007 1:05 AM, Robin Green <[EMAIL PROTECTED]> wrote:

> On Tue, 13 Nov 2007 13:51:13 -0800
> "Dan Piponi" <[EMAIL PROTECTED]> wrote:
>
> > Up until yesterday I had presumed that guards only applied to
> > functions. But I was poking about in the Random module and discovered
> > that you can write things like
> >
> > a | x > 1 = 1
> >   | x < -1 = -1
> >   | otherwise = x
> >
> > where 'a' clearly isn't a function.
>
> Isn't it a function taking zero arguments?
> --
> Robin
> ___
> 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


Re: [Haskell-cafe] Re: Flymake Haskell

2007-11-15 Thread Philip Armstrong

On Thu, Nov 15, 2007 at 09:19:10AM -0500, Denis Bueno wrote:

On Nov 15, 2007 7:25 AM, Philip Armstrong <[EMAIL PROTECTED]> wrote:



I can pass on patches if anyone cares.


I care!


Will dig them out asap then!

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Chart plotting libraries

2007-11-15 Thread Tim Docker
droundy:
>
> Chart has rather a complicated API.  I've written a simpler API (but
> somewhat less flexible), if anyone's interested (Tim wasn't).  My API is
> closer in complexity (of use) to matlab's plotting.

I'd describe the API as verbose rather than complicated. It takes 5-10
lines of haskell to define a chart - see the examples on the web page. I
think this is fine for use within other code, but I agree is too much
typing for interactive use.

Tim



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


Re: [Haskell-cafe] dropSpace not exported in ByteString

2007-11-15 Thread Don Stewart
olivier.boudry:
>On 11/15/07, Don Stewart <[EMAIL PROTECTED]> wrote:
> 
>  Let me know if the rule fires. If it isn't, that's a bug, essentially.
> 
>  -- Don
> 
>Don,
> 
>As you can see the rule fires.
> 
>C:\Temp>ghc --make -O2 -fasm -ddump-simpl-stats DropSpaceTest.hs
>...
>3 RuleFired
>1 FPS pack/packAddress
>2 FPS specialise dropWhile isSpace -> dropSpace
>...

Great! The first rule is also a good sign.

> 
>By the way, what's the reason dropSpaceEnd is defined but not exported nor
>used through a rule? I'm just curious.

Looking at the source, its not actually defined -- its commented out.
Perhaps you're looking at an older version of the source?

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


[Haskell-cafe] Erik Meijer's talk at Google?

2007-11-15 Thread Galchin Vasili
Hello,

 Last week (?)  Erik Meijer gave a talk at Google. Has a video been
uploaded somewhere?

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


Re: [Haskell-cafe] A small question

2007-11-15 Thread J. Garrett Morris
http://msdn2.microsoft.com/en-us/library/1w45z383(vs.71).aspx

I believe.

 /g

On Nov 15, 2007 12:56 PM, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> I notice that in GHC 6.8.1, if I compile a runnably program, as well as
> generating foo.exe, GHC now also generates a file foo.exe.manifest,
> which appears to contain some kind of XML data. Anybody know anything
> about this mysterious file?
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
The man who'd introduced them didn't much like either of them, though
he acted as if he did, anxious as he was to preserve good relations at
all times. One never knew, after all, now did one now did one now did
one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskellforge?

2007-11-15 Thread Duncan Coutts
On Thu, 2007-11-15 at 15:56 -0200, Maurí­cio wrote:
> Hi,
> 
> Is there a "Haskellforge" somewhere, i.e.,
> something like a sourceforge for open source
> Haskell programs, with darcs, automatic
> cabalization etc.? Has anyone tried that
> already?

There is the Haskell Community server http://community.haskell.org/

It hosts darcs repos at http://code.haskell.org/

You can request an account and projects via:
http://community.haskell.org/admin/

There are currently 44 registered developers and 41 hosted projects.

It may host more services in future, like bug trackers.

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


Re: [Haskell-cafe] Chart plotting libraries

2007-11-15 Thread Graham Fawcett
On Nov 15, 2007 10:33 AM, David Roundy <[EMAIL PROTECTED]> wrote:
> Chart has rather a complicated API.  I've written a simpler API (but
> somewhat less flexible), if anyone's interested (Tim wasn't).  My API is
> closer in complexity (of use) to matlab's plotting.

I'd be interested, for one.

Cheers,
Graham

Graham Fawcett
Centre for Teaching and Learning
University of Windsor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread SevenThunders

The good news is that my code compiles without error and much faster under
ghc 6.8.1.
The bad news is that there appear to be subtle bugs that did not occur when
I compiled things under
6.6.1.  One issue is that my code is somewhat complex and links into a  C
library as well.

The new behavior is that under certain conditions a certain matrix inner
product produces undefined floats, that should not be there.  If the code is
executed inside any function it fails but if the same code is reexecuted at
the ghci prompt it works.  Here is the gist of the code that I'm running

main = do
... lots of computations and let clauses
-- get a submatrix
  viewMatbotk wstart nsua su 1 suw
-- get another submatrix
  viewMatbotk 0 nsua arrstart npaths sua
 -- complex non conjugated inner product (multiply the two submatrices)
mulCFtF
mprint

If this is executed either in ghci as main or from a Dos prompt I get
a matrix filled with bad values including a few that look like
-1.#IND+1.87514i

If I recompile everything in ghc-6.6.1 it works like  charm.  I make sure
that I have deleted all the .o and .hi files.  There is a dll that contains
a C library I link to via running dlltool.exe.   If I print out all the
function inputs to the function viewMatbotk and then call them interactively
in ghc 6.8.1 and call mulCFtF interactively it works correctly.  both
viewMatbotk  and mulCFtF are C routines pulled in from the external library.  

I am at a complete loss how to debug this or how to pin down what exactly
has changed between 6.6.1 and 6.8.1 that breaks this code so badly.  This
type of error stinks of some kind of memory issue, e.g. corrupted pointers. 
Any suggestions would be appreciated.  Unfortunately the code base is rather
involved and potentially proprietary so I can't publish all of the details.
-- 
View this message in context: 
http://www.nabble.com/ghc-6.8.1-bug--tf4810375.html#a13763341
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] HTTP actions & proxy server

2007-11-15 Thread Jim Burton

How would I go about converting the little get program at
http://darcs.haskell.org/http/test/get.hs to use a proxy server? I tried
adding a call to setProxy like this but it doesn't work:

get :: URI -> IO String
get uri =
do
  browse $ setProxy (Proxy "myproxy:80" Nothing)
  eresp <- simpleHTTP (request uri)
  resp <- handleE (err . show) eresp
  case rspCode resp of
(2,0,0) -> return (rspBody resp)
_ -> err (httpError resp)
  where
showRspCode (a,b,c) = map intToDigit [a,b,c]
httpError resp = showRspCode (rspCode resp) ++ " " ++
rspReason resp

Thanks.
-- 
View this message in context: 
http://www.nabble.com/HTTP-actions---proxy-server-tf4815272.html#a13775608
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Asynchronous exceptions and the RealWorld

2007-11-15 Thread Yang
- I want to set timeouts on various IO operations in an existing 
library, ftphs. However, even if I wrap every call in `block`, it's 
unclear whether ftphs has been coded to deal with asynchronous 
exceptions, or whether state could be rendered inconsistent. Is there 
any solution for this aside from auditing/changing ftphs?


- I can't find any documentation on which calls are (either directly or 
indirectly, or parametrically) "interruptible operations" (to use the 
term from the Async Exceptions paper). For instance, I experimentally 
determined that hPutStrLn on a socket is *not*. Does such documentation 
exist anywhere? Furthermore, is there any way to embed this information 
in the type system, so that Haskellers don't produce 
async-exception-unaware code? (Effectively, introducing checked interrupts?)


- The above finding of hPutStrLn (as an example) is somewhat surprising, 
since the socket buffer may be full, causing the call to block 
indefinitely. We can unblock that call, but unless there's a way to 
atomically reinstate the block and save the result of the computation 
(the unit value), this effectively makes it impossible to determine 
whether the hPutStrLn returned. (Admittedly, this is a contrived 
example, since whether a call to hPutStrLn returns is usually not a 
useful result - but this is the first thing I tried, and I'm guessing 
there are more such IO operations that actually yield useful results.)


- Are there any higher-level concurrency libraries that actually tackle 
these hand-in-hand issues (safe asynchronous interruptible IO, 
two-phase-commit to prevent dropping results, choice, etc.)? I tried 
searching for a while, coming up with PiMonad, HAppS.Util, 
MissingH.Threads.Timeout, but none of them really address these issues. 
Perhaps this is just impossible in Concurrent Haskell, and one would 
need to resort to the sure-fire home-rolled solution using delimited 
continuations and cooperative scheduling for any serious concurrency 
abstractions for systems programming.


Thanks in advance for any answers!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let vs. where

2007-11-15 Thread Arnar Birgisson
On Nov 16, 2007 12:35 AM, Arnar Birgisson <[EMAIL PROTECTED]> wrote:
> [1]

I'm terribly sorry, that was meant to be:

[1] 
http://www.onlamp.com/pub/a/onlamp/2007/07/12/introduction-to-haskell-pure-functions.html

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


Re: [Haskell-cafe] (general question) Approaches for storing large amount of simple data structures

2007-11-15 Thread Don Stewart
bbrown:
> I have a project where I want to store a data structure on a file,
> binary or ascii.  And I want to use haskell to read and write the
> file. I will have about half a million records so it would be nice if
> the format was able to load quickly.  I guess I could, but I kind of
> want to avoid using XML.
> 
> I have the following structure in pseudo code.
>   -> keywords associated with that URL
>   -> title associated with that URL
>   -> links contained in that URL. (0 ... N)
> 
> What is an approach for saving 500 thousand of those types of records
> and where I can load the data into a haskell data type.

Data.Binary is the standard approach for large data/high performance
serialising to and from Haskell types. It composes well with the gzip
librarry too, so you can compress the stream on the way out, and
decompress lazily on the way in.

   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-0.4.1

The interface is really simple:

encode :: Binary a => a -> ByteString
decode :: Binary a => ByteString -> a

For marshalling Haskell type 'a' into a bytestring and back.

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


[Haskell-cafe] (general question) Approaches for storing large amount of simple data structures

2007-11-15 Thread bbrown
I have a project where I want to store a data structure on a file, binary or
ascii.  And I want to use haskell to read and write the file. I will have
about half a million records so it would be nice if the format was able to
load quickly.  I guess I could, but I kind of want to avoid using XML.

I have the following structure in pseudo code.

A URL -> id
  -> keywords associated with that URL
  -> title associated with that URL
  -> links contained in that URL. (0 ... N)

What is an approach for saving 500 thousand of those types of records and
where I can load the data into a haskell data type.

--
Berlin Brown
[berlin dot brown at gmail dot com]
http://botspiritcompany.com/botlist/?

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


Re: [Haskell-cafe] dropSpace not exported in ByteString

2007-11-15 Thread Don Stewart
olivier.boudry:
>Hi Don,
> 
>In fact I'm not really looking at performance, I don't expect performance
>to be a big issue in my application.
> 
>I was just looking at using some simple functions found in the
>documentation and avoid redefining them.
> 
>In fact dropSpace and dropSpaceEnd are doing exactly what I'm looking for.
>But of course if they're not exported it's not a problem and I'll use
>their dropWhile equivalent.
> 
>Thanks for your reply,

Let me know if the rule fires. If it isn't, that's a bug, essentially.

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


Re: [Haskell-cafe] dropSpace not exported in ByteString

2007-11-15 Thread Olivier Boudry
Hi Don,

In fact I'm not really looking at performance, I don't expect performance to
be a big issue in my application.

I was just looking at using some simple functions found in the documentation
and avoid redefining them.

In fact dropSpace and dropSpaceEnd are doing exactly what I'm looking for.
But of course if they're not exported it's not a problem and I'll use their
dropWhile equivalent.

Thanks for your reply,

Olivier.


On Nov 15, 2007 5:24 PM, Don Stewart <[EMAIL PROTECTED]> wrote:

>
> The latter:
>
>"FPS specialise dropWhile isSpace -> dropSpace"
>dropWhile isSpace = dropSpace
>
> check that the rule fires with -ddump-simpl-stats
>
> There's no rule for dropSpaceEnd, but you can certainly inline the defn
> in your code, if perf. matters.
>
> -- Don
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dropSpace not exported in ByteString

2007-11-15 Thread Don Stewart
olivier.boudry:
>Hi all,
> 
>I'm writing a Haskell program to do some address cleansing. The program
>uses the ByteString library.
> 
>Data.ByteString.Char8 documentations shows functions for removing
>whitespace from start or end of a ByteString. Those functions are said to
>be more efficient than the dropWhile / reverse mixes.
> 
>It looks exactly like what I'm searching for, but apparently those
>functions are not exported by the Data.ByteString.Char8 module. Are those
>functions only called by rules? Transformation of dropWhile isSpace into
>dropSpace? I've seen such a rule for dropSpace but did not found an
>equivalent rule for dropSpaceEnd.
> 
>Is there a way to call the dropSpace and dropSpaceEnd or do I have to code
>with dropWhile and hope that some rule will magically transform my
>dropWhileS into dropSpaceS?
> 

The latter:

"FPS specialise dropWhile isSpace -> dropSpace"
dropWhile isSpace = dropSpace

check that the rule fires with -ddump-simpl-stats

There's no rule for dropSpaceEnd, but you can certainly inline the defn
in your code, if perf. matters.

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


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread Alberto Ruiz
On Thursday 15 November 2007 19:58, SevenThunders wrote:
> Alberto Ruiz-2 wrote:
> > Hello,
> >
> > I have had exactly the same problem with my bindings to GSL, BLAS and
> > LAPACK.
> > The foreign functions (!) randomly (but very frequently) produced NaN
> > with ghc-6.8.1 -O. As usual, I first thought that I had a subtle bug
> > related to the foreign pointers, but after a lot of refactoring,
> > experiments, and tracing everything, I'm reasonably sure that memory is
> > safely used. What I have found is that the same errors can be reproduced
> > on ghc-6.6.1 with -O -fasm. So I tried -O -fvia-C on ghc-6.8.1 (which now
> > it is not the default) and apparently everything works well. So it seems
> > that now the ffi
> > requires and additional and explicit -fvia-C. In any case I don't know
> > why -fasm produces those strange NaN in precompiled foreign functions...
> >
> > Alberto
>
> Arrgh, the fix of using -fvia-C doesn't seem to be working for me.
> You got my hopes up for a moment :).
> I also am calling BLAS via C bindings.
> I am going to try to distill my case down to the bare minimum if possible
> and then provide an example. It may take a while.

Hmm, I' sorry... all seems to work well for me if I set -O -fvia-C for 
building the library and for final program compilation. But I will also try 
to find a minimum test case. In the meantime I have sent to Ian information 
to expose the problem with my library, although I know that such large amount 
of code will not be very helpful.

Have you tested ghc-6.6.1 with -O -fasm?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Chart plotting libraries

2007-11-15 Thread David Roundy
On Wed, Nov 14, 2007 at 10:36:06PM -0800, Don Stewart wrote:
> jon:
> > I'd like some free software to help me plot charts like the one from the 
> > ray 
> > tracer language comparison:
> > 
> >   http://www.ffconsultancy.com/languages/ray_tracer/results.html
> > 
> > I was using Mathematica but its stopped working and an upgrade is £2,000. 
> > Are 
> > there Haskell bindings to any free libraries or even Haskell 
> > implementations 
> > that would make something like this painless?
> > 
> > There isn't anything for OCaml (that I'm not still writing ;-) so this 
> > might 
> > be a good opportunity to force me to do a little more Haskell. :-)
> 
> A quick search of hackage.haskell.org,
> 
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Chart-2007.8.8
> 
> Using gtk and cairo. Homepage here:
> 
> http://dockerz.net/twd/HaskellCharts

Chart has rather a complicated API.  I've written a simpler API (but
somewhat less flexible), if anyone's interested (Tim wasn't).  My API is
closer in complexity (of use) to matlab's plotting.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread SevenThunders



Alberto Ruiz-2 wrote:
> 
> 
> Hmm, I' sorry... all seems to work well for me if I set -O -fvia-C for 
> building the library and for final program compilation. But I will also
> try 
> to find a minimum test case. In the meantime I have sent to Ian
> information 
> to expose the problem with my library, although I know that such large
> amount 
> of code will not be very helpful.
> 
> Have you tested ghc-6.6.1 with -O -fasm?
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

Good idea.  I just tried that.  However, it worked just fine even with -fasm
in ghc 6.6.1.  

One thought that I had
as well was to be sure to recompile my C code that interfaces to Haskell
using the HsFFI.h header from 6.8.1 instead of 6.6.1 just in case something
might have changed.  Unfortunately in my case it made no difference.

-- 
View this message in context: 
http://www.nabble.com/ghc-6.8.1-bug--tf4810375.html#a13781878
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Haskellforge?

2007-11-15 Thread Don Stewart
duncan.coutts:
> On Thu, 2007-11-15 at 15:56 -0200, Maurí­cio wrote:
> > Hi,
> > 
> > Is there a "Haskellforge" somewhere, i.e.,
> > something like a sourceforge for open source
> > Haskell programs, with darcs, automatic
> > cabalization etc.? Has anyone tried that
> > already?
> 
> There is the Haskell Community server http://community.haskell.org/
> 
> It hosts darcs repos at http://code.haskell.org/
> 
> You can request an account and projects via:
> http://community.haskell.org/admin/
> 
> There are currently 44 registered developers and 41 hosted projects.
> 
> It may host more services in future, like bug trackers.

lambdabot is hosted there too, now.

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


Re: [Haskell-cafe] Using Data.Binary for compression

2007-11-15 Thread Chad Scherrer
> > Almost all 'real users' just use Codec.Compression.GZip.  It's very
> > fast, very compositional, and (perhaps suprisingly) almost as effective
> > as application-specific schemes.
>
> I was about to say the same thing. So so much simpler to use Duncan's
> carefully written zlib binding,
>
> import Data.Binary
> import Codec.Compression.GZip
> import qualified Data.ByteString.Lazy as L
>
> main = L.writeFile "log.gz" . compress . encode $ [1..10::Int]
>
> Simple, purely functional, fast.
>
> -- Don

I have several types of symbols, and for each type the probabilities
are very predictable - to the point where they could even be
hard-coded. And upon completion I can be sure the first two questions
will be "Can we make it smaller?" and "Can we make it faster?". GZip
(while very cool) is adaptive and general-purpose, so it's building
frequency tables as it goes and ignoring the structure of the data I
should be able to take advantage of.

With an awful lot of trouble, it must be possible to write something
in C to go faster and yield better compression than gzip for this
particular data. With the probability structure known in advance,
there are just a lot of steps taken by gzip that are no longer needed.
Besides this, gzip only assumes an arbitrary sequence of bytes, but my
data are much more structured than this.

Considering the high performance achieved using idiomatic Haskell and
the ByteString and Binary libraries, I would think a similar approach
could be used for writing individual bits. Then it would be
(relatively) easy to write custom compression routines in Haskell with
reasonable performance - I don't think this can be said of any other
language.

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


Re: [Haskell-cafe] HTTP actions & proxy server

2007-11-15 Thread Justin Bailey
On Nov 15, 2007 9:01 AM, Jim Burton <[EMAIL PROTECTED]> wrote:
> How would I go about converting the little get program at
> http://darcs.haskell.org/http/test/get.hs to use a proxy server? I tried
> adding a call to setProxy like this but it doesn't work:

I think it needs to be a real URL:

  setProxy (Proxy "http://myproxy:80"; Nothing)

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


[Haskell-cafe] Vertigo / GHC / Memo

2007-11-15 Thread Peter Verswyvelen
Hi Haskell Lovers,

I’m trying to compile Vertigo (http://conal.net/Vertigo), which seems to be
a module from which I can really learn a lot of stuff.
 
However, it seems to use a Memo module, which does not seem to be part of
GHC (anymore?) As far as I understand, it uses a memo function to make sure
that when performing symbolic differentiation, it does not get stuck in an
endless loop.

As I realize no generic memoization function can be made, I guess it got
removed at some point?

Can anyone give me a hint how to find a suitable Memo module for Vertigo? 

As a sidenote, I must say the memoization section on Haskell.org is not
really helpful for a newbie like me... 

Thanks,
Peter

PS: I adapted the following code from SOE, but I'm not sure it does the job
correctly (it will certainly be slow...)

{-# OPTIONS_GHC -fglasgow-exts #-}

module Memo(memo) where

import Data.IORef
import System.IO.Unsafe

memo :: Eq a => (a->b) -> (a->b)
memo f = unsafePerformIO $ do
   cache <- newIORef []
   return $ \x -> 
 unsafePerformIO $ do
   vals <- readIORef cache
   case x `inCache` vals of
 Nothing -> do 
   let y = f x
   modifyIORef cache ((x,y):)
   return y
 Just y  -> do 
   return y

inCache :: Eq a => a -> [(a,b)] -> Maybe b
x `inCache` [] = Nothing
x `inCache` ((x',y'):xys) =
   if x == x' 
   then Just y' 
   else x `inCache` xys


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


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread SevenThunders



Alberto Ruiz-2 wrote:
> 
> Hello,
> 
> I have had exactly the same problem with my bindings to GSL, BLAS and
> LAPACK. 
> The foreign functions (!) randomly (but very frequently) produced NaN with 
> ghc-6.8.1 -O. As usual, I first thought that I had a subtle bug related to 
> the foreign pointers, but after a lot of refactoring, experiments, and 
> tracing everything, I'm reasonably sure that memory is safely used. What I 
> have found is that the same errors can be reproduced on ghc-6.6.1 
> with -O -fasm. So I tried -O -fvia-C on ghc-6.8.1 (which now it is not the 
> default) and apparently everything works well. So it seems that now the
> ffi 
> requires and additional and explicit -fvia-C. In any case I don't know 
> why -fasm produces those strange NaN in precompiled foreign functions...
> 
> Alberto
> 
> 
> 
Arrgh, the fix of using -fvia-C doesn't seem to be working for me.
You got my hopes up for a moment :).
I also am calling BLAS via C bindings. 
I am going to try to distill my case down to the bare minimum if possible
and then provide an example. It may take a while.

-- 
View this message in context: 
http://www.nabble.com/ghc-6.8.1-bug--tf4810375.html#a13779349
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] cabal Main-Is restriction

2007-11-15 Thread Duncan Coutts
On Thu, 2007-11-15 at 11:14 -0600, Nicolas Frisby wrote:
> It seems the meaning of the -main-is switch for GHC and the Main-Is
> build option for Cabal executables differ. With GHC, I can point to
> any function "main" in any module, but in Cabal I must point to a
> filename with precisely the module name "Main". This is tying my hands
> with regard to organizing a default executable and exposing some of
> its functionality as a library. Is there a way to get around this
> restriction?

I've filed your feature request in the Cabal trac:
http://hackage.haskell.org/trac/hackage/ticket/179

Do please add your suggestions in a comment there.

Login with username "guest" and password "haskell'" (note the apostrophe
at the end).

> Is this currently possible? I recognize the "add a separate
> Program-Main.hs file" workaround, but I'll avoid it if I can.

A workaround is to use:

main-is: Program/Main.hs
ghc-options: -main-is Program.Main


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


Re: [Haskell-cafe] Using Data.Binary for compression

2007-11-15 Thread David Roundy
On Wed, Nov 14, 2007 at 10:03:52PM -0800, Chad Scherrer wrote:
> I'd like to be able to use Data.Binary (or similar) for compression.
> Say I have an abstract type Symbol, and for each value of Symbol I
> have a representation in terms of some number of bits. For compression
> to be efficient, commonly-used Symbols should have very short
> representations, while less common ones can be longer.

I agree with others that it's probably not worth your effort to do
compression yourself except for fun, but it *is* fun, and interpret my
advice below in that light.  (Also, bitwise operations could be useful for
other things, like interacting with standard formats.  e.g. writing IEEE
doubles portably, something that Data.Binary doesn't do.)

...

> (2) This seems like it will work ok, but the feel is not as clean as
> the current Data.Binary interface. Is there something I'm missing that
> might make it easier to integrate this?

I would write this as a monad, analogous to PutM.  Make bit monads GetBits
and PutBitsM (with PutBits = PutBitsM ()), and then write functions like

writeBits :: PutBits -> Put
readBits :: GetBits a -> Get a

where writeBits and readBits would pad their reading/writing to the next
byte boundary (or perhaps Word32 boundary, for better performance?) as they
must.  So now this would have two main uses: users could use it to
serialize data (e.g. writing an IEEE Double serialization), or could use it
to write their own data compression, but putting *all* the serialization
into the Bits level.

This approach, of course, also would allow you to copy much of the
infrastructure of Binary into your new bit-level interface.

> (3) Right now this is just proof of concept, but eventually I'd like
> to do some performance tuning, and it would be nice to have a
> representation that's amenable to this. Any thoughts on speeding this
> up while keeping the interface reasonably clean would be much
> appreciated.

I think a monad as above would have the advantage of separating the
implementation from the interface, which should make it tuneable.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Weird ghci behaviour?

2007-11-15 Thread Simon Marlow


It's worth saying that right now, all you have to do to get the source file 
loaded is


  > :! touch M.hs
  > :reload

Put this in a macro, if you want:

  > :def src \s -> return (":! touch "++s)

I hear the arguments in this thread, and others have suggested changes before:

http://hackage.haskell.org/trac/ghc/ticket/1205
http://hackage.haskell.org/trac/ghc/ticket/1439

One of the suggestions was that if you name the source file rather than the 
module name, you get the source file loaded for that file, and any object 
code is ignored.  So any files you explicitly want to have full top-level 
scope for must be named in :load or on the GHCi command line.


The only problem with this is that someone who isn't aware of this 
convention might accidentally be ignoring compiled code, or might wonder 
why their compiled code isn't being used.  Well, perhaps this is less 
confusing than the current behaviour; personally I find the current 
behaviour consistent and easy to understand, but I guess I'm in the minority!


The other suggestion is to have a variant of :load that ignores compiled 
code (or for :load to do that by default, and rename the current :load to 
something else).  I don't have a strong preference.


Cheers,
Simon


Short form of my proposal: Make two separate commands that each have a
predictable behavior.  Make "ghci modulename" default to source loading, and
require a flag to load a binary.  I don't give a bikeshed what they are called.
 I don't care if the magic ":load" stays or goes or ends up with only one 
behavior.

This is different/orthogonal to the .o or .hs file extension sensitive proposal.

My arguments:

I run into annoyances because I often poke at things in ghci when trying to get
my package to compile.  So depending on which modules succeeded or failed to
compile I get different behavior when loading into ghci.  I am no longer
confused by this, but just annoyed.

I would say that the user gets surprised which leads to feeling that there is a
lack of control.

The '*' in the '*Main>' versus 'Main>' prompt is a UI feature for experts, not
for new users.  Making this more obvious or verbose or better documented does
not fix the lack of control the user feels.

The only flags that the user can easily find are those listed by --help:


chrisk$ ghci --help
Usage:

ghci [command-line-options-and-input-files]

The kinds of input files that can be given on the command-line
include:

  - Haskell source files (.hs or .lhs suffix)
  - Object files (.o suffix, or .obj on Windows)
  - Dynamic libraries (.so suffix, or .dll on Windows)

In addition, ghci accepts most of the command-line options that plain
GHC does.  Some of the options that are commonly used are:

-fglasgow-exts  Allow Glasgow extensions (unboxed types, etc.)

-i Search for imported modules in the directory .

-H32m   Increase GHC's default heap size to 32m

-cppEnable CPP processing of source files

Full details can be found in the User's Guide, an online copy of which
can be found here:

http://www.haskell.org/ghc/documentation.html


The -fforce-recomp and -fno-force-recomp flags only exist in the User's Guide.
Thus they are hard to find. Is there a ticket open for adding at least a list of
the recognized flags to ghc and ghci usage messages?

Ideally, I want a ":load modulename" to get the source and a ":bin modulename"
to get the binary (and a ":m ..." to get the binary).  I want "ghci modulename"
to get the source and "ghch -bin modulename" to get the binary.  Simple and
predictable and no surprises.

Cheers,
  Chris K


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


Re: [Haskell-cafe] let vs. where

2007-11-15 Thread hjgtuyl
On Thu, 15 Nov 2007 12:31:07 +0100, Henning Thielemann  
<[EMAIL PROTECTED]> wrote:

On Tue, 13 Nov 2007, Dan Piponi wrote:

On Nov 13, 2007 1:24 PM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> I tend to prefer where, but I think that guards & function  
declarations are

> more readable than giant if-thens and case constructs.

Up until yesterday I had presumed that guards only applied to
functions. But I was poking about in the Random module and discovered
that you can write things like

a | x > 1 = 1
  | x < -1 = -1
  | otherwise = x


Btw. I would write here
  min 1 (max (-1) x)
 or even better define a function for such clipping, since it is needed
quite often.


The value of 'a' needs only be calculated once; when defined at top level,  
'a' is a CAF; in a 'where' clause, the value is also calculated once.


--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread Ian Lynagh

Can any of you give us a testcase for this, please?


Thanks
Ian

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


[Haskell-cafe] Haskell Job Opportunity

2007-11-15 Thread Tom Hawkins
Hello,

Eaton (eaton.com, Eden Prairie, MN US) is seeking software engineers
for design and verification of electro-hydraulic control systems for
industrial, automotive, and aerospace applications.  Though I am still
trying to get Haskell on the official job description, here are a few
of the potential Haskell applications:

- Domain specific languages.
- Compiler design and embedded code generation.
- Model checking and equivalence checking.
- SAT decision procedures.
- Constrained random simulation.
- Software timing analysis.

General knowledge of the following would be helpful:

- Control theory.
- Real-time, embedded programming.
- Automotive and industrial systems.
- Hydraulics and fluid power.

If interested, send me a resume.

Thanks!

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


[Haskell-cafe] Re: Weird ghci behaviour?

2007-11-15 Thread Simon Marlow

Jonathan Cast wrote:

On 13 Nov 2007, at 11:03 PM, Jules Bean wrote:

Just to be clear: my proposal is that if you want it to go faster you do

ghci foo.hi

or

ghci foo.o

... so you still have the option to run on compiled code.

My suggestion is simply that "ghci foo.hs" is an instruction to load 
source code (similarly :load); while "ghci foo.o" is obviously an 
instruction to load compiled code.


Even just having

:m + *Foo


Currently :m doesn't load any modules, it just alters the "context" (what's 
in scope at the prompt), and fails if you ask for a module that isn't 
loaded.  It would make sense for :m +M to behave like :add if M wasn't 
loaded, though.  And perhaps :add *M or :load *M should ignore compiled 
code for M - that's another option.


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


Re[2]: [Haskell-cafe] let vs. where

2007-11-15 Thread Henning Thielemann

On Thu, 15 Nov 2007, Bulat Ziganshin wrote:

> Hello Henning,
>
> Thursday, November 15, 2007, 2:31:07 PM, you wrote:
>
> > Btw. I would write here
> >   min 1 (max (-1) x)
> >  or even better define a function for such clipping, since it is needed
> > quite often.
>
> min 1 . max (-1)  is pretty standard, although i renamed them:
> atMax 1 . atLeast (-1)

I like to add, that it is not just fancy to use functions instead of
guards here. If you work with wrappers for software synthesizers like
CSound and SuperCollider, you cannot map a Haskell function over a signal,
say
  map (\x -> case x of _ | x < -1 -> -1 | x>1 -> 1 | otherwise -> x) signal
but you can write
  Synth.min 1 $ Synth.max (-1) signal
 given that 'Synth.min' and 'Synth.max' call the pointwise minimum and
maximum functions of the software synthesizers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Flymake Haskell

2007-11-15 Thread Denis Bueno
On Nov 15, 2007 7:25 AM, Philip Armstrong <[EMAIL PROTECTED]> wrote:
> On Thu, Nov 15, 2007 at 02:56:32PM +0900, Daisuke IKEGAMI wrote:
> >Dear Stefan and Haskell-Cafe,
> >
> >Thanks to keeping your interest to the flymake-mode for Haskell.
> >
> >Stefan wrote:
> >> Could you explain to me what flycheck_haskell.pl does, and give an
> >> example of a problematic situation solved by the use of
> >> flycheck_haskell.pl.
> >
> >Sure.
> >
>
> I'll add in passing that fixing flymake to cope with multi-line errors
> was fairly simple & obviates the need for the extra perl script.
>
> I can pass on patches if anyone cares.

I care!

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


Re[2]: [Haskell-cafe] let vs. where

2007-11-15 Thread Bulat Ziganshin
Hello Henning,

Thursday, November 15, 2007, 2:31:07 PM, you wrote:

> Btw. I would write here
>   min 1 (max (-1) x)
>  or even better define a function for such clipping, since it is needed
> quite often.

min 1 . max (-1)  is pretty standard, although i renamed them:
atMax 1 . atLeast (-1)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Weird ghci behaviour?

2007-11-15 Thread Henning Thielemann

On Thu, 15 Nov 2007, Jules Bean wrote:

> Anecdotes have little value, but for what it's worth: in around 5 years
> of ghc use, I have never, not even once, wanted to load the module I was
> working on in its compiled form. I've occasionally noticed that
> dependent modules get loaded quickly from their .o's and thought that
> was handy, but that's all. During that time I have many times been
> annoyed that a .hs file which I load from the command line or via :load
> (or via C-c C-l in emacs mode) get loaded in interpreted form :)

I found compiled modules useful in GHCi when using computation intensive
functions, like those for signal processing.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Brazilian Haskellers ?

2007-11-15 Thread Ricardo Herrmann

I, for one, embrace that idea too (disguised Haskell evangelism) ... but in a
global scale. However, as long as we're not able to compete in the web-CRUD
arena, I think it will remain a niche. Hacking HAppS, Unify, HaskellDB now
would be more useful in that respect. We need to hijack Java/C programmers
and make'em take the red pill ;-)

Until now, all I did was increase the overall co-worker awareness of
functional programming in general at my employer (3 blue letters). As for
the university part, all of a sudden, in order to learn Haskell, I risked my
master's degree reimplementing everything in it, but, hey, it all works now
;-) That was questioned by all except for one of the qualifying exam
committee members, an ex Miranda programmer, but now there are more
professors interested in it.

Are there programming classes at Telecentros ? Felipe Lessa's beamer slides
based on the wikibook could be a good start point. 

Too much to do, so little time ... hehe

[]'s


Maurí­cio wrote:
> 
> Ricardo,
> 
> The idea is great. There's a lot of
> haskellers in Brazil and, if we want to
> make Haskell the brazilian language of
> choice, as we all do, it's time to get
> together. However, I think just a mail
> group isn't going to do much. We already
> have two communities in Orkut, and the
> volume of communication is really low,
> people just prefer to exchange ideas in
> this list. What we need is to discuss great
> projects that could get brazilians involved
> in Haskell. Maybe a wiki would do better.
> 
> For instance: I would love to do volunteer
> work in Telecentros, but all they have is
> OpenOffice classes. Wouldn't it be great
> if we could teach Haskell there? First we
> need to write good material, and then a few
> cool applications people would like to hack
> with - with variable names in Portuguese,
> of course, since ghc reads Unicode.
> 
> We could also write some applications in
> Haskell that would be usefull for public
> services. I have a friend in Diadema's
> municipal office and he says there's
> a lot of people there doing volunteer
> work help using Ubuntu. What if we
> check what are the software needs of our
> public services and try to write stuff in
> Haskell that can be used there? I imagine
> something in the line of what is listed in
> 'www.softwarepublico.gov.br'. Also, we
> could help nice scientific projects in our
> Universities to get the utilities they need
> in Haskell. I think a wiki would be great
> to start exchanging good ideas on where we
> could use our efforts.
> 
> Best luck. Conte comigo,
> Maurício
> 
>  > Thanks. I also put in that page a link pointing to the haskellers map
> in
>  > Frappr, in order to encourage new HUGs. I believe most of us are lazy 
> enough
>  > (in the good Haskell way) to plot them in xearth ;-)
>  >
>  >
>  >>> Hi brazilian haskellers,
>  >>>
>  >>> How about trying to form a HUG-BR ? Maybe (...)
>  >>>
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

-- 
View this message in context: 
http://www.nabble.com/Brazilian-Haskellers---tf4806561.html#a13767920
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Re: List of all powers

2007-11-15 Thread apfelmus

Brent Yorgey wrote:

apfelmus, does someone pay you to write so many thorough, insightful and
well-explained analyses on haskell-cafe?  I'm guessing the answer is 'no',
but clearly someone should! =)


Depending on length, my prices for posts range between λ9.99 and λ29.99 ;)


Regards,
apfelmus

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


Re: [Haskell-cafe] Haskell and html input elements

2007-11-15 Thread PR Stanley

Hi
What i have in mind is an interactive Haskell app which allows the 
user to enter text, push buttons, select radio buttons and so on. As 
I have already done a lot of xhtml coding I thought it might be 
easier to operate the program entirely via a web browser. However, 
I'm also interested in the idea of a straightahead MS Windows GUI for 
my program but dont' really know where to start.

Any advice would be most appreciated.
Cheers
Paul


At 17:13 12/11/2007, you wrote:


On Nov 12, 2007, at 8:38 AM, PR Stanley wrote:


Hi
back again!
How easy/hard is it to control a haskell program through a web
browser?


Hi,

It depends on exactly how you want to control it, but at least some
control is fairly easy.

If you simply want to start a batch Haskell program, and see its
output as HTML in a browser, you can use the cgi [1] or fastcgi [2]
libraries listed on Hackage.

If you want slightly more interactivity, it would make sense to write
your Haskell program as its own web server (which is actually
surprisingly easy) and have it respond to sequences of requests,
perhaphs storing intermediate state along the way. Giving something
like this a nice GUI on the user side will probably involve writing a
certain amount of JavaScript. One example of a program that works
this way is HERA [3], which is unfortunately not open-source at the
moment, but may be some day. Another potentially useful library is
HAppS [4], which abstracts out some of the functionality necessary
for web-based applications.

Is this sort of thing along the right track, or were you thinking of
something else?

Aaron

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ cgi-3001.1.5.1
[2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
fastcgi-3001.0.1

[3] http://haskell.org/haskellwiki/ Haskell_Equational_Reasoning_Assistant
[4] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ HAppS-0.8.4


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


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread Joel Koerwer
I'm also seeing unusual behavior from GSL under ghc-6.8.1. I get a
singular matrix error where there was none before, but if I prefix the
function's rhs with "m `seq`", where m is the matrix in question, the
error goes away.

I'll try removing the seq and compiling with -fvia-C tomorrow to see
if I can confirm that that makes the problem go away too. Certain
inputs cause it to fail repeatably, while others do not fail; I'm not
seeing random behavior like Alberto is. Strange indeed.

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


Re: [Haskell-cafe] Re: Weird ghci behaviour?

2007-11-15 Thread Jules Bean

Simon Marlow wrote:
The only problem with this is that someone who isn't aware of this 
convention might accidentally be ignoring compiled code, or might wonder 
why their compiled code isn't being used.  Well, perhaps this is less 
confusing than the current behaviour; personally I find the current 
behaviour consistent and easy to understand, but I guess I'm in the 
minority!



Anecdotes have little value, but for what it's worth: in around 5 years 
of ghc use, I have never, not even once, wanted to load the module I was 
working on in its compiled form. I've occasionally noticed that 
dependent modules get loaded quickly from their .o's and thought that 
was handy, but that's all. During that time I have many times been 
annoyed that a .hs file which I load from the command line or via :load 
(or via C-c C-l in emacs mode) get loaded in interpreted form :)


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


Re: [Haskell-cafe] let vs. where

2007-11-15 Thread Henning Thielemann

On Tue, 13 Nov 2007, Dan Piponi wrote:

> On Nov 13, 2007 1:24 PM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> > I tend to prefer where, but I think that guards & function declarations are
> > more readable than giant if-thens and case constructs.
>
> Up until yesterday I had presumed that guards only applied to
> functions. But I was poking about in the Random module and discovered
> that you can write things like
>
> a | x > 1 = 1
>   | x < -1 = -1
>   | otherwise = x

Btw. I would write here
  min 1 (max (-1) x)
 or even better define a function for such clipping, since it is needed
quite often.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Chart plotting libraries

2007-11-15 Thread Jules Bean

Tim Docker wrote:

don:

jon:


I'd like some free software to help me plot charts like the one from the
ray tracer language comparison:

A quick search of hackage.haskell.org,

http://dockerz.net/twd/HaskellCharts


I need to update the package to build under ghc-6.8.1, though I think it's
just a change to the cabal config, rather than any to any code.

As of 6.8.1 it needs to depends on the "new" package called
"old-locale-1.0.0.0". Presumably this API is intended to become
deprecated, though I don't see a replacement.


Data.Time.*, including Data.Time.Clock and Data.Time.Format, are the 
"new-style" API to times and dates, but they still use the TimeLocale 
data type from old-locale, so I guess that time-1.1.2 still "depends on" 
 old-locale-1.0.0.0.


I agree it seems strange because the naming convention "old-" does 
appear to suggest deprecation.


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


Re: [Haskell-cafe] Why are OCaml and Haskell being used at these companies?

2007-11-15 Thread Ketil Malde
Seth Gordon <[EMAIL PROTECTED]> writes:

>> Bioinformaticians are among the first to adopt functional
>> programming languages

>From my experience, Bioinformatics use a mixture of langauges - C to
implement various algorithms, a bit of Java for UI-oriented stuff, and
Perl to tie it all together.  (You can use Python instead, of
course, but expect to be considered something of a rebel.)

I think Haskell works nicely to combine at least the C and Perl
aspects, but as far as I can tell, I'm about the only one who does
this. 

There isn't a lot of comp.sci. in bioinformatics, beyond a handful of
relatively standard algorithms.  I guess it's one of those "practical"
fields.  I guess the important difference to the financial sector is
that the competitive advantage is in exclusive data, not exclusive
algorithms or analytical methods.  Thus, programmer productivity isn't
quite so important, you're just going to script togehter some
pre-packaged tools, often ten or fifteen year old software.

> FWIW, a few years ago, when I was stubbornly unemployed[*], I wrangled
> a fifteen-minute informational interview with Kenan Sahin[**].  He
> advised me to look for work related to medical devices

Sounds like good advice to me - pharmaceuticals seem to have enough
money, at least.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using Data.Binary for compression

2007-11-15 Thread Bulat Ziganshin
Hello Chad,

Thursday, November 15, 2007, 9:03:52 AM, you wrote:

> I'd like to be able to use Data.Binary (or similar) for compression.
> Say I have an abstract type Symbol, and for each value of Symbol I
> have a representation in terms of some number of bits. For compression
> to be efficient, commonly-used Symbols should have very short
> representations, while less common ones can be longer.

alternative may be using naive representation for serializing and then
running zip/bzip2 compression lib over it. it should be both faster
and provide better compression


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] ghc 6.8.1 bug?

2007-11-15 Thread Alberto Ruiz
Hello,

I have had exactly the same problem with my bindings to GSL, BLAS and LAPACK. 
The foreign functions (!) randomly (but very frequently) produced NaN with 
ghc-6.8.1 -O. As usual, I first thought that I had a subtle bug related to 
the foreign pointers, but after a lot of refactoring, experiments, and 
tracing everything, I'm reasonably sure that memory is safely used. What I 
have found is that the same errors can be reproduced on ghc-6.6.1 
with -O -fasm. So I tried -O -fvia-C on ghc-6.8.1 (which now it is not the 
default) and apparently everything works well. So it seems that now the ffi 
requires and additional and explicit -fvia-C. In any case I don't know 
why -fasm produces those strange NaN in precompiled foreign functions...

Alberto

On Thursday 15 November 2007 09:05, SevenThunders wrote:
> The good news is that my code compiles without error and much faster under
> ghc 6.8.1.
> The bad news is that there appear to be subtle bugs that did not occur when
> I compiled things under
> 6.6.1.  One issue is that my code is somewhat complex and links into a  C
> library as well.
>
> The new behavior is that under certain conditions a certain matrix inner
> product produces undefined floats, that should not be there.  If the code
> is executed inside any function it fails but if the same code is reexecuted
> at the ghci prompt it works.  Here is the gist of the code that I'm running
>
> main = do
> ... lots of computations and let clauses
> -- get a submatrix
>   viewMatbotk wstart nsua su 1 suw
> -- get another submatrix
>   viewMatbotk 0 nsua arrstart npaths sua
>  -- complex non conjugated inner product (multiply the two submatrices)
> mulCFtF
> mprint
>
> If this is executed either in ghci as main or from a Dos prompt I get
> a matrix filled with bad values including a few that look like
> -1.#IND+1.87514i
>
> If I recompile everything in ghc-6.6.1 it works like  charm.  I make sure
> that I have deleted all the .o and .hi files.  There is a dll that contains
> a C library I link to via running dlltool.exe.   If I print out all the
> function inputs to the function viewMatbotk and then call them
> interactively in ghc 6.8.1 and call mulCFtF interactively it works
> correctly.  both viewMatbotk  and mulCFtF are C routines pulled in from the
> external library.
>
> I am at a complete loss how to debug this or how to pin down what exactly
> has changed between 6.6.1 and 6.8.1 that breaks this code so badly.  This
> type of error stinks of some kind of memory issue, e.g. corrupted pointers.
> Any suggestions would be appreciated.  Unfortunately the code base is
> rather involved and potentially proprietary so I can't publish all of the
> details.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Using Data.Binary for compression

2007-11-15 Thread Dominic Steinitz
Don Stewart  galois.com> writes:

> 
> I was about to say the same thing. So so much simpler to use Duncan's
> carefully written zlib binding,
> 
> import Data.Binary
> import Codec.Compression.GZip
> import qualified Data.ByteString.Lazy as L
> 
> main = L.writeFile "log.gz" . compress . encode $ [1..10::Int]
> 
> Simple, purely functional, fast.
> 
Don,

But something like this is needed (or I least I would like it). I'd like 
functions to get and put bits as in NewBinary. Is this not a way of doing it?

Dominic.



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