Re: [Haskell-cafe] Deriving class instances using DrIFT

2006-10-30 Thread Einar Karttunen
On 29.10 19:56, John Meacham wrote:
> Since DrIFT can only understand haskell source code, it can't derive
> instances for anything you don't have the original source to. such as
> things in the pre-compiled libraries that come with ghc. you will likely
> have to write out those instances by hand. 
> 
> Another possibility is that you could replicate just the data
> declarations by hand, and use DrIFT -r to just spit out the derivations
> and put those in a file on their own.

How about using Template Haskell for getting the definition and then
giving that to DrIFT?

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


Re: [Haskell-cafe] source code for haskell web server?

2006-09-28 Thread Einar Karttunen
On 28.09 15:33, Bulat Ziganshin wrote:
> Hello Einar,
> 
> Thursday, September 28, 2006, 1:25:55 PM, you wrote:
> 
> > Historically HAppS has used ByteStrings in HTTP, while most other
> > libraries have used Strings.
> 
> why not use StringLike class here? you can find implementation at
> darcs get --partial http://darcs.haskell.org/SoC/fps-soc/

http://darcs.haskell.org/SoC/fps-soc/Data/Stringable.hs ?

1) Because it didn't exist at the time
2) Lots of code would need even more type parameters
3) Would still need specialize pragmas to get acceptable performance
4) No easy way of adding ByteStrings without unpacking first which is slow
5) One can already easily write functions that handle setting anything
string-like as the body.

But moving from [ByteString] into a lazy ByteString makes sense.

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


[Haskell-cafe] Eager global IO actions (per module initialization)

2006-09-28 Thread Einar Karttunen
Hello

I am needing a way to run initializers defined in various modules 
in an eager fashion before main. I am doing this to load
deserialization functions for a Typeable function.

Basically I have code like:

$(inferDecoderAndRegisterItOnStartup ''MyType)

which defines a class instance, but additionally I want to
call 'registerDecoderForType "MyType" decodeMyType' automatically
on startup.

Calling registerDecodeForType for all types in main gets very tedious
and error-prone when doing things by hand. Thus an automated solution
would be very nice.

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


[Haskell-cafe] Re: [Haskell] BitSyntax for Haskell

2006-09-28 Thread Einar Karttunen
On 26.09 10:01, Adam Langley wrote:
> >For the decoding part:
> >* Provide a monadic interface
> 
> Are you suggesting a monad to pass in the input around, or that it
> returns mzero on error? The latter makes more sense to me.

Yes. Also make it possible for user supplied functions to fail
in better ways than to produce Either or use error.

> >* Add a test part to ReadType:
> >Test :: ReadType a -> (a -> Bool) -> ReadType Test
> >(or a -> m ()) in the monadic case.
> 
> Again, I'm not clear what you are thinking of here?

In some protocols I am using there are some fixed bytes
which I want to ignore (no Haskell value produced), but
check that they are valid in the data stream.

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


Re: [Haskell-cafe] source code for haskell web server?

2006-09-28 Thread Einar Karttunen
On 27.09 13:03, Pasqualino 'Titto' Assini wrote:
> There is also the HAppS application server and the HaskellNet library.
> 
> Would not be possible to merge the protocol-handling parts of all these
> libraries into a generic Internet Haskell server that could then be expanded
> to support CGIs, transactions, etc.?
>

It would be very nice to have a common format.

Historically HAppS has used ByteStrings in HTTP, while most other
libraries have used Strings.

The HAppS format is:
http://happs.org/auto/apidoc/HAppS-Protocols-HTTP-LowLevel.html#t%3ARequest

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


[Haskell-cafe] Re: [Haskell] BitSyntax for Haskell

2006-09-25 Thread Einar Karttunen
On 23.09 15:00, Adam Langley wrote:
> Erlang's bit syntax[1] is a great for building and breaking up binary
> structures. I've knocked up something similar (although a little
> clumsy) for Haskell:
> 
> http://www.imperialviolet.org/binary/bitsyntax/
> http://www.imperialviolet.org/binary/bitsyntax/BitSyntax.hs
> 
> I'm sure that this isn't the best possible way to do this, but it
> suffices at this stage for many problems.

This looks very nice.

Here are some feature wishes:

BitBlock: add a way to encode length prefixed ByteStrings.

For the decoding part:
* Provide a monadic interface
* Add a test part to ReadType: 
Test :: ReadType a -> (a -> Bool) -> ReadType Test
(or a -> m ()) in the monadic case.
* Add a way to limit the size of a LengthPrefixed:
e.g. [Unsigned 4, LengthPrefixed] is very unsafe, the app should
have a way to control the maximum length.

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


Re: [Haskell-cafe] sections for record settors

2006-09-19 Thread Einar Karttunen
On 20.09 01:05, Misha Aizatulin wrote:
> > It would be nice if there was some
> > sort of section-like syntax to access the settor function
> 
>   Indeed - I'd like it as well. Also these threads seem to deal with
> similar questions:
> http://www.haskell.org/pipermail/haskell/2005-February/015354.html
> http://www.haskell.org/pipermail/haskell-cafe/2005-January/008875.html
> http://www.haskell.org/pipermail/template-haskell/2005-February/000409.html
> 

Having a pure Haskell solution would be nice - but I think getting
better record types has more priority.

One can already simulate this with using DrIFT to derive setter/update
functions for the record members.

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


Re: [Haskell-cafe] Traversing a graph in STM

2006-09-18 Thread Einar Karttunen
On 18.09 01:23, Josef Svenningsson wrote:
> On 9/17/06, Jan-Willem Maessen <[EMAIL PROTECTED]> wrote:
> >You can associate a unique name with each traversal, and store a set
> >of traversals at each node (instead of a mark bit).  But this set
> >grows without bound unless you follow each traversal with a "cleaning
> >traversal" which removes a traversal tag from the set.  And you'd
> >need some way to generate the unique names.
> >
> Well, if your set implementation used weak pointers there would be no
> need for a cleaning traversal. The garbage collector will take care of
> that. The only slightly tricky thing is to keep a live pointer to the
> unique traversal name during the entire of the traversal. But I don't
> think that should be a big problem.
>

This suffers from the problem that two traversals reading the
same parts of the graph would have a good chance to make each other
retry.

I am thinking of going the StableName route. But as this happens
inside STM Data.HashTable does not help much (without using
unsafeIOToSTM and dealing with retries).

If StableNames were in Ord using Set (StableName T)
would be nice. But in the current implementation one has to resort
to IntSet Int [StableName T] which is not pretty at all.

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


Re: [Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
On 13.09 08:48, Chris Kuklewicz wrote:
> And the concurrent searches are isolated from each other?  Or are you 
> performing a single search using many threads?

Isolated from each other. Mainly dreaming of the per-transaction
variables attached to the nodes :-)

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


[Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
Hello

Is there an elegant way of traversing a directed graph in STM?

type Node  nt et = TVar (NodeT nt et)
type Edge  et= TVar et
data NodeT nt et = NodeT nt [(Node nt et, Edge et)]

type MyGraph = Node String Int

When implementing a simple depth first search we need a way to
mark nodes (= TVars) as visited. In addition multiple concurrent
searches should be possible.

Is it possible to avoid passing around an explicit Set of visited
nodes? And is there a better way of getting TVar identity than
StableNames?

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


Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-12 Thread Einar Karttunen
On 12.09 15:28, Misha Aizatulin wrote:
>   I've been using existentially quantified data constructors like
> 
> > data Box = forall a. Cxt a => Box a

If you can include Typeable into the mix then serializing works.

Serialize the value as " ".

When deserializing use a Map  
and get the appropriate decoder from there for the type in question.

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Einar Karttunen
On 31.07 16:27, Brian Hulley wrote:
> None of the above type classes would be compatible with Data.ByteString! 
> (You mentioned this issue before wrt Data.Edison.Seq but it just clicked 
> with me now for the above refactoring.) For compatibility, the element type 
> would need to appear also thus:
> 
>   class Foldable f_a a | f_a -> a where
>fold :: (a -> b -> b) -> b -> f_a -> b
> 

With the new System FC (when it is merged) we could make these classes
nicer.

class ElementType c a | c -> a

instance ElementType [a] a
instance ElementType ByteString Char
instance IArray a e => ElementType (a i e) e

class Foldable c where
  fold :: ElementType c a => (a -> b -> b) -> b -> c -> b

This won't work at the moment due to limitations in GHC, but seems
like a cleaner solution.

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


Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
On 30.07 12:12, Jason Dagit wrote:
> Depending on the type of sandboxing that you need/want #2 might be
> possible with GHC.  Take lambdabot for example.  lambdabot has made it
> safe to allow arbitrary expression evaluation by disallowing IO and
> not importing unsafePerformIO and similar "unsafe" functions.
>

This is possible as lambdabot has the source code rather than
an arbitrary Haskell expression at runtime.

Basically how does one differentiate between:

(\x -> unsafePerformIO somethingNasty `seq` (x+1))
and
(\x -> x + 1)

at runtime.

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


Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
On 29.07 14:07, Brian Sniffen wrote:
> I'm very excited by the ability to pass functions or IO actions
> between threads of the same program.  But I don't see any language or
> library support for doing so between programs, or between sessions
> with the same program.  OCaml provides a partial solution:
> 
> <http://caml.inria.fr/pub/docs/manual-ocaml/libref/Marshal.html>
> 
> Though all it's really sending is an address and a hash of the binary
> program.  Even SerTH doesn't help with functional types.  I seek the
> knowledge of the Haskell Cafe: is there a reasonable way of addressing
> this problem?

There is sadly no real good way of doing it on top of GHC. If both
sides are running an identical executable image one can hack it to
work (see parallel Haskell for the code to do it). But in general
I don't think it is worth the trouble. The problem is:

1) versioning (I like being able to upgrade applications while keeping 
serialized state)
2) trust (GHC does not have sandboxing)

YHC may have an answer for YHC users.

I have some code which allows one to register functions and call them
transparently over a network - even supporting callbacks. Thus code
does not move, but code location is quite transparent.

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


[Haskell-cafe] Still not dead

2006-07-21 Thread Einar Karttunen
Hello

As many of you may have noticed I have been away for some months.
This has been due to health problems which have unfortunately
kept me unable to work on Haskell projects.

I am not dead and will be working on resolving the backlog
of messages (will probably take a week). I will be slowly
back to hacking things when I get everything fixed.

- Einar Karttunen

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


Re: [Haskell-cafe] Existentially-quantified constructors: Hugs is fine, GHC is not?

2006-05-10 Thread Einar Karttunen
On 10.05 13:27, Otakar Smrz wrote:
>data ... = ... | forall b . FMap (b -> a) (Mapper s b)
> 
>... where FMap qf qc = stripFMap f q
> 
> the GHC compiler as well as GHCi (6.4.2 and earlier) issue an error
> 
> My brain just exploded.
> I can't handle pattern bindings for existentially-quantified
> constructors.

You can rewrite the code in a way that GHC accepts it. Just
avoid pattern binding your variables. I had the same problem
in HAppS code and needed to lift some code to the top
level to solve it.

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


Re: [Haskell-cafe] throwing sugar into the void.

2006-05-07 Thread Einar Karttunen
On 07.05 01:12, Marc A. Ziegert wrote:
> data Type a
> typeOf :: a -> Type a
> typeOf = undefined
> #define TYPE(a) (undefined::Type (a))
> ...
> sizeOf :: (Storable a) => Type a -> Int

I think the name Proxy is used for this in other places.

data Proxy a = Proxy
class Storable a where
...
sizeOf :: Proxy a -> Int

proxy :: a -> Proxy a
proxy _ = Proxy

Note here that there are no undefined values used thus one does not need to be
careful with evaluation.

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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Einar Karttunen
On 27.04 12:32, Mirko Rahn wrote:
> So it would be much better to define the options in the library and to 
> provide this definitions to the user program somehow. I tought about 
> this topic several times and came up with a solution that works for me 
> but is far from being perfect. It uses existentials and a main 
> disadvantage is the need of explicit traversing. Moreover some new 
> boilerplate code is necessary.

HAppS has a typeclass for this kind of thing also:

http://test.happs.org/auto/apidoc/HAppS-Util-StdMain-Config.html
http://test.happs.org/HAppS/src/HAppS/Util/StdMain/Config.hs

and for an example instance see:

http://test.happs.org/HAppS/src/HAppS/Protocols/SimpleHTTP.hs

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


Re: [Haskell-cafe] GetOpt

2006-04-26 Thread Einar Karttunen
On 26.04 11:29, Anton Kulchitsky wrote:
> I just started to study Haskell and it is my almost first big experience 
> with functional languages (except Emacs Lisp and Python). I enjoyed all 
> small exercises and started a bigger business writing a general utility. 
> However, I have a problem from the beginning. The utility get some file 
> and convert it to another format. It is a kind of small compiler. It 
> also accepts many parameters and behaves depending on them. The problem 
> is how to do this neat! How should I write my program to accept and 
> neatly work with options

One solution is to have a datatype for configuration:

> data Config = Config { mode:: Mode,
>infile  :: Maybe FilePath,
>outfile :: Maybe FilePath
>  }
> nullConfig = Config Normal "-" "-"
> data Mode   = Normal | Version | Help

and handle options as functions from Config to Config:

> Option ['i']   ["input"]   (ReqArg (\x c -> c { infile = Just x }) "file") 
> "input file name"

and then handle the parsed options like:

> case conf of
>   Config Normal (Just i) (Just o) -> ...
>   Config Normal _    _-> both input and output must be specified
>   Config Help   __-> help message

- Einar Karttunen

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


Re: [Haskell-cafe] More STUArray questions

2006-03-12 Thread Einar Karttunen
On 12.03 18:44, Martin Percossi wrote:
> However, just out of curiosity, I'm still curious at how I could do the
> runSTMatrix, which would really be the icing on the cake in terms of client
> usability.

You might want to look at the definition of Data.Array.ST
(at http://darcs.haskell.org/packages/base/Data/Array/ST.hs)
runSTUArray is defined as follows:

runSTUArray :: (Ix i)
   => (forall s . ST s (STUArray s i e))
   -> UArray i e
runSTUArray st = runST (st >>= unsafeFreezeSTUArray)

A similar way should work for matrixes.

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


[Haskell-cafe] Re: request for code review

2006-03-12 Thread Einar Karttunen
On 12.03 01:47, Shannon -jj Behrens wrote:
> monad.  Perhaps controversially, I've continued to use |> in a bunch
> of places that the monad didn't get rid of because I think it's more
> readable, but I'm still open for argument on this topic.  Using the

What about using (>>>) from Control.Arrow?

> -- For convenience:
> currTokType :: ParseContext -> TokenType
> currTokType ctx = ctx |> currTok |> tokenType

currTokType = currTok >>> tokenType

> currTokValue :: ParseContext -> String
> currTokValue ctx = ctx |> currTok |> tokenValue

currTokValue = currTok >>> tokenValue

> -- Create the final output string given a ParseContext.
> consolidateOutput :: ParseContext -> String
> consolidateOutput ctx =
>   ctx |> output |> reverse |> concat

consolidateOutput = output >>> reverse >>> concat

and so on.

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


Re: [Haskell-cafe] Looking for an efficient tree in STM

2006-03-08 Thread Einar Karttunen
On 08.03 13:32, Tomasz Zielonka wrote:
> > This seems suprisingly hard to implement - a normal binary tree with
> > links as TVar is very slow and does not scale very well.
> 
> By "normal" you mean unbalanced? Do you think it's slow because it's not
> balanced, or because of STM?

Unbalanced in this case because balancing produces even more problematic
effects (TVar writes). I used random inserts in the test which kept the tree in
a good balance, and tested the same tree without STM to see whether that
was the problem - so I am fairly sure that balancing is not the issue.

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


[Haskell-cafe] Looking for an efficient tree in STM

2006-03-08 Thread Einar Karttunen
Hello

Does anyone have an efficient tree implemented in STM that
supports concurrent updates in an efficient fashion? This
seems suprisingly hard to implement - a normal binary
tree with links as TVar is very slow and does not scale
very well.

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


Re: [Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
Here is a version that works fine:


myRawSystem cmd args = do 
(inP, outP, errP, pid) <- runInteractiveProcess cmd args Nothing Nothing
hClose inP
os <- pGetContents outP
es <- pGetContents errP
ec <- waitForProcess pid
case ec of
  ExitSuccess   -> return ()
  ExitFailure e ->
  do hPutStrLn stderr ("Running process "++unwords (cmd:args)++" FAILED 
("++show e++")")
 hPutStrLn stderr os
 hPutStrLn stderr es
 hPutStrLn stderr ("Raising error...")
 fail "Running external command failed"

pGetContents h = do
mv <- newEmptyMVar
let put [] = putMVar mv []
put xs = last xs `seq` putMVar mv xs
forkIO (hGetContents h >>= put)
takeMVar mv

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


[Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
Hello

Using system or any variant of it from System.Process
seems broken in multithreaded environments. This
example will fail with and without -threaded.

When run the program will print "hello: start" and
then freeze. After pressing enter (the first getChar)
System.Cmd.system will complete, but without that
it will freeze for all eternity.

What is the best way to fix this? I could use System.Posix,
but that would lose windows portablity which is needed.


import Control.Concurrent
import System.Cmd

main = do forkIO (threadDelay 10 >> hello)
  getChar
  getChar

hello = do putStrLn "hello: start"
   system "echo hello world!"
       putStrLn "hello: done"


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


Re: [Haskell-cafe] standard poll/select interface

2006-02-09 Thread Einar Karttunen
On 09.02 22:24, Bulat Ziganshin wrote:
> as i understand this idea, transformer implementing async i/o should
> intercept vGetBuf/vPutBuf calls for the FDs, start the appropriate
> async operation, and then switch to another Haskell threads. the I/O
> manager thread should run select() in cycle and when the request is
> finished, wake up the appropriate thread. what's all. if you will ever
> need, this implementation can then be used to extend GHC's System.IO
> internals with the support for new async i/o managers (as i
> understand, select() is now supported by GHC, but poll(), kqueue() is
> not supported?). the only difference that my lib gives an opportunity
> to test this implementation without modifying GHC I/O internals, what
> is somewhat simpler. so, interface for async vGetBuf/vPutBuf routines
> should be the same as for read/write:
> 
> type FD = Int
> vGetBuf_async :: FD -> Ptr a -> Int -> IO Int
> vPutBuf_async :: FD -> Ptr a -> Int -> IO Int

Please don't fix FD = Int, this is not true on some systems,
and when implementing efficient sockets one usually wants
to hold more complex state.

> JM> Don't take the absence of a feature in jhc to mean I don't like or want
> JM> that feature. There are a lot of things I don't have but that I'd
> JM> definitly want to see in the language simply because I was only shooting
> JM> for H98 to begin with and was more interested in a lot of the back end
> JM> stuff. You should figure out the nicest design that uses just the
> JM> extensions needed for the design you want. it could help us decide what
> JM> goes into haskell-prime to know what is absolutely needed for good
> JM> design and what is just nice to have.
> 
> this simply means that the Streams library cannot be used with JHC,
> what is bad news, because it is even more rich than GHC's System.IO.
> jhc had chance to get modern I/O library. but it lost that chance :)

I think it is more like "all haskell-prime programs". Seriously,
if we design a new IO subsystem it would be quite nice to be
able to use it from standard conforming programs.

Maybe things can be reformulated in a way that will be compatible
with haskell-prime.

> please look. at this moment Sreams library lacks only a few important
> features, already implemented in GHC's System.IO: sockets, line
> buffering and async i/o. moreover, i don't have an experience in
> implementing the async i/o, so foreign help is really necessary

If you want I can look at getting network-alt to implement the
interface.

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


Re: [Haskell-cafe] I/O and utf8

2006-01-11 Thread Einar Karttunen
On 10.01 10:25, Bulat Ziganshin wrote:
> i have the question about this issue - i also want to provide
> autodetection mechanism, which relies on first bytes of text files to
> set proper encoding. what is the standard rules to encode utf8/utf16
> encoding used for text in file in these first bytes?

The BOM is used to mark the encoding
(http://en.wikipedia.org/wiki/Byte_Order_Mark), but most
UTF-8 streams lack it. I have not seen it used in UTF-8 files either.

Do you plan on supporting things like HTTP where the character set
is only known in the middle of the parsing?

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


[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-11 Thread Einar Karttunen
On 09.01 11:32, Simon Marlow wrote:
> Sebastian Sylvan wrote:
> 
> >It would be neat if the PackedString library contained functions such
> >as hGetLine etc. It does have a function for reading from a buffer,
> >but it won't stop at a newline...
> >But yeah, fast string manipulation is difficult when using a
> >linked-list representation...
> 
> My version of the packed string library does have an hGetLine.  Don 
> Stewart was merging my version with his fps at some point, Don - any 
> news on that?

Getting a fast FastPackedString will solve the problems with many
benchmarks. A similar thing for arrays would be nice - although
this is more about inteface:

> module Data.Array.UnsafeOps where
>
> import Data.Array.Base hiding((!))
>
> {-# INLINE (!) #-}
> (!) :: MArray a e m => a Int e -> Int -> m e
> (!) = unsafeRead
>
> {-# INLINE set #-}
> set :: MArray a e m => a Int e -> Int -> e -> m ()
> set = unsafeWrite
>
> {-# INLINE swap #-}
> swap :: MArray a e m => a Int e -> Int -> Int -> m ()
> swap arr x y = do xv <- arr ! x
>   yv <- arr ! y
>   set arr x yv
>   set arr y xv
>
> {-# INLINE combineTo #-}
> combineTo :: MArray a e m => a Int e -> Int -> (e -> e -> e) -> a Int e -> 
> Int -> m ()
> combineTo a0 i0 f a1 i1 = do v0 <- a0 ! i0
>  v1 <- a1 ! i1
>  set a0 i0 $! f v0 v1

and so forth. Usually imperative solutions have something like
"a[i] += b[i]", which currently is quite tedious and ugly to
translate to MArrays. Now it would become "combineTo a i (+) b i".

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


Re: [Haskell-cafe] In for a penny, in for a pound.

2006-01-09 Thread Einar Karttunen
On 09.01 12:56, Donald Bruce Stewart wrote:
> Entries that may currently be worth submitting:
>takfp - http://www.haskell.org/hawiki/TakfpEntry

Committed.

>pidigits (currently 2nd!) - http://www.haskell.org/hawiki/PidigitsEntry 

Committed.

>mandelbrot- http://www.haskell.org/hawiki/MandelbrotEntry

Committed.

>harmonic  - http://www.haskell.org/hawiki/HarmonicEntry

Already present in the CVS.

>fannkuch (pure and impure) - http://www.haskell.org/hawiki/FannkuchEntry

I think these could do with some work. Optimizing the impure one
at least.

I took the liberty of submitting some of these. Please keep in future
the comment lines in the entries, because Shootout wants the names
of the contributers.

- Einar Karttunen

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


Re: [Haskell-cafe] binary IO

2005-12-28 Thread Einar Karttunen
On 27.12 07:00, Tomasz Zielonka wrote:
> Some time ago I was playing with DNS too. I have a library that can
> construct and interpret DNS packets, but it's a bit incomplete right
> now. It reads packets as Strings, but it should be quite straightforward
> to make it read and interpret FastPackedStrings.
> 
> http://www.uncurry.com/repos/TzDNS


Nice, here is my shot at DNS - 
http://cs.helsinki.fi/u/ekarttun/haskell/hdnsd-20051227.tar.bz2
feel free to take bits if you are interested. The serialization/deserialization
uses Ptrs.

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


Re: [Haskell-cafe] Haskell Speed

2005-12-23 Thread Einar Karttunen
On 23.12 19:14, Daniel Carrera wrote:
> I'm taking a look at the "Computer Language Shootout Benchmarks".
> 
> http://shootout.alioth.debian.org/
> 
> It looks like Haskell doesn't do very well. It seems to be near the 
> bottom of the pile in most tests. Is this due to the inherent design of 
> Haskell or is it merely the fact that GHC is young and hasn't had as 
> much time to optimize as other compilers?

Some reasons for this include:

* Efficient string handling functions are packaged separately (faststring etc)
  And thus not included in shootout.
* The tests change faster than Haskell people write efficient versions
  of the programs.
* Most of the Haskell results are taking an imperative implementation
  and just translating it.
* In many cases other languages use arrays while the Haskell implementation
  uses lists. Haskell does have efficient arrays.


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


[Haskell-cafe] Re: [Haskell] A simple server (or how to do io).

2005-12-21 Thread Einar Karttunen
On 21.12 01:13, Pupeno wrote:
> So, I install a signal handler with installHandler... and then ? how do I 
> prevent the program for quiting ? am I missing some kind of event loop here ?
> 

Here is a small server program:

main = performForkWithUnixySessionStuff work

-- this is just for testing, replace with real implementation
performForkWithUnixySessionStuff x = x

work = do s1 <- runStreamServer ...
  s2 <- runDgramServer ...
  mv <- newEmptyMVar
  installHandler someSignal (Catch (putMVar mv ())) Nothing
  takeMVar mv
  someCleanupActions
  killServer s1
  killServer s2

For simple testing you might want to just use getLine to wait for the right
time to exit.

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


Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-16 Thread Einar Karttunen
On 16.12 07:03, Tomasz Zielonka wrote:
> On 12/16/05, Einar Karttunen  wrote:
> > To matters nontrivial all the *nix variants use a different
> > more efficient replacement for poll.
> 
> So we should find a library that offers a unified
> interface for all of them, or implement one ourselves.
> 
> I am pretty sure such a library exists. It should fall back to select()
> or poll() on platforms that don't have better alternatives.

network-alt has select(2), epoll, blocking and very experimental kqueue
(the last one is not yet committed but I can suply patches
if someone is interested.

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


Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-15 Thread Einar Karttunen
On 15.12 17:14, John Meacham wrote:
> On Thu, Dec 15, 2005 at 02:02:02PM -, Simon Marlow wrote:
> > With 2k connections the overhead of select() is going to start to be a
> > problem.  You would notice the system time going up.  -threaded may help
> > with this, because it calls select() less often.
> 
> we should be using /dev/poll on systems that support it. it cuts down on
> the overhead a whole lot. 'poll(2)' is also mostly portable and usually
> better than select since there is no arbitrary file descriptor limit and
> it doesn't have to traverse the whole bitset. a few #ifdefs should let
> us choose the optimum one available on any given system.

To matters nontrivial all the *nix variants use a different
more efficient replacement for poll.

Solaris has /dev/poll
*BSD (and OS X) has kqueue
Linux has epoll

Also on linux NPTL+blocking calls can actually be very fast
with a suitable scenario. An additional problem is that
these mechanisms depend on the version of the kernel
running on the machine... Thus e.g. not all linux machines
will have epoll.

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


Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-14 Thread Einar Karttunen
On 14.12 23:07, Joel Reymont wrote:
> Something like this? Comments are welcome!

> timeout :: Int
> timeout = 500 -- 1 second

Is that correct?

> {-# NOINLINE timers #-}
> timers :: MVar Timers
> timers = unsafePerformIO $ newMVar M.empty
> 
> --- Call this first
> initTimers :: IO ()
> initTimers =
> do forkIO $ block checkTimers
>return ()

Here is a nice trick for you:

{-# NOINLINE timers #-}
timers :: MVar Timers
timers = unsafePerformIO $ do mv <- newMVar M.empty
  forkIO $ block checkTimers
  return mv


initTimers goes thus away.

> --- Not sure if this is the most efficient way to do it
> startTimer :: String -> Int -> (IO ()) -> IO ()
> startTimer name delay io =
> do stopTimer name
>now <- getClockTime
>let plus = TimeDiff 0 0 0 0 0 delay 0
>future = addToClockTime plus now
>block $ do t <- takeMVar timers
>   putMVar timers $ M.insert (future, name) io t

I had code which used a global IORef containing
the current time. It was updated once by a second
by a dedicated thread, but reading it was practically
free. Depends how common getClockTime calls are.

> --- The filter expression is kind of long...
> stopTimer :: String -> IO ()
> stopTimer name =
> block $ do t <- takeMVar timers
>putMVar timers $
>M.filterWithKey (\(_, k) _ -> k /= name) t

And slow. This is O(size_of_map)

> --- Tried to take care of exceptions here
> --- but the code looks kind of ugly

Is there a reason you need block for checkTimers?
What you certainly want to do is ignore exceptions
from the timer actions.


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


Re: [Haskell-cafe] Opening the same file multiple times

2005-12-12 Thread Einar Karttunen
On 12.12 12:06, Duncan Coutts wrote:
> It states in the Haskell Report 21.2.3:
> 
> http://haskell.org/onlinereport/io.html

Thanks, for the pointer, but am looking for an extension
in the non-haskell98 API to do it.

It seems that things are quite problematic:

1) Use openFile or GHC.Handle.openFd

Works in Hugs, fails as the standard mandates in GHC
due to locking. This is fine.

2) Use openFile + handleToFd + unlockFile

This seems like a good plan. Except handleToFd will close the Handle.

3) Using System.Posix.IO

Using the fd{Read,Close,Write} functions from System.Posix.IO
could solve the problem - except that there is no way to
write binary buffers (Ptr Word8) with the API. Thus no
solution.

4) Use System.Posix.IO.openFd + fdToHandle

This appears to be nice on surface. Except fdToHandle locks
the file, thus back to drawing board.

5) Use System.Posix.IO.openFd + fdToHandle + unlockFile

Thus we have:

* lock mutex - otherwise there is a race condition
* System.Posix.IO.openFd - open the file emulating openFile
* fdToHandle - convert the file to Handle locking it
* unlockFile (fromIntegral fd) - now unlock the original fd
* unlock mutex

Is this really the most simple way of doing things?
Most of the operations will also hit the disk, and
be slow (safe) FFI calls.

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


Re: [Haskell-cafe] Opening the same file multiple times

2005-12-11 Thread Einar Karttunen
On 11.12 22:26, Donn Cave wrote:
> Quoth Einar Karttunen :
> | It seems that opening the same file multiple times (one writer
> | and multiple readers) is not supported at least on *nix with
> | GHC. I want to use one Handle to use append data till the
> | end of the file while other Handles perform random access
> | IO with seeks on the file.
> 
> How is it not supported?  What happens with something like this

Try the same in ghc / ghci:

[EMAIL PROTECTED]:~$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.4.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base-1.0 ... linking ... done.
Prelude> :m IO
Prelude IO> af <- openFile "z" AppendMode
Prelude IO> sf <- openFile "z" ReadMode
*** Exception: z: openFile: resource busy (file is locked)
Prelude IO> 

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


[Haskell-cafe] Opening the same file multiple times

2005-12-11 Thread Einar Karttunen
Hello

It seems that opening the same file multiple times (one writer
and multiple readers) is not supported at least on *nix with
GHC. I want to use one Handle to use append data till the
end of the file while other Handles perform random access
IO with seeks on the file.

Sharing the same Handle for all the threads is not possible
since they perform seeks and may thus mess each other up.
Hiding the Handle behind a mutex would limit concurrency
more than I like.

Thus I wanted to open multiple Handles to the file, but
this seems quite hard. My best guess is to create a function 
like:

#ifdef mingw32_HOST_OS
openUnlocked fn mode = openBinaryFile fn mode
#else
openUnlocked fn mode = withMVar mutex $ do
  h  <- openBinaryFile fn mode
  fd <- handleToFd h
  unlockFile $ fromIntegral fd
  return h

{-# NOINLINE mutes #-}
mutex = unsafePerformIO $ newMVar ()
#endif

Is there really no simpler solution?

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


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Einar Karttunen
On 06.12 20:57, Tomasz Zielonka wrote:
> On Tue, Dec 06, 2005 at 02:52:03PM +, Joel Reymont wrote:
> > Well, I do need to have access to all those thread handles.

Since thread creation is inside IO anyways you might want to
look at Control.Concurrent.QSem which solves this in an
easy fashion. If you want to use STM then a global 
TVar Int should work fine.

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


[Haskell-cafe] STM commit hooks

2005-11-29 Thread Einar Karttunen
Hello

I have been playing with STM and want to log transactions to disk. 
Defining a logging function like:

log h act = unsafeIOToSTM $ hPrint h act

works most the time. Aborts can be handled with:

abort h = log h Abort >> retry
atomic' h act = atomically (act `orElse` abort h)

But is it possible to handle a commit?

commit h = unsafeIOToSTM (hPrint h Commit >> hSync h)
atomically2 h act = atomically ((act >> commit h) `orElse` abort h)

This won't work because the transaction is validated and 
maybe aborted after the commit is logged to disk.

Another alternative would be:

atomically3 h act = atomically (act `orElse` abort h) >> atomically (commit h)

But this does not work either. Given Trx1 and Trx2, the following may occur:

1) Trx1 commits

2) Trx2 commits (and depends on Trx1)
3) Trx2 commit is logged to disk


This means that the log would be inconsistent. Is there a way to implement
the commit that works?

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


Re: [Haskell-cafe] Haskell GUI on top of Xlib?

2005-11-28 Thread Einar Karttunen
On 26.11 22:00, Dimitry Golubovsky wrote:
> Thanks Duncan for this link: a very interesting reading.
> 
> Duncan Coutts wrote:
> 
> >Are you aware of the XCB library:
> >http://xcb.freedesktop.org/


I managed to parse the XCB XML protocol descriptions to
Haskell data structures, next I'll try to emit some
nice code from that. If it works well the end result
should be a pure Haskell X library.

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


[Haskell-cafe] throwDyn typing "fun"

2005-11-11 Thread Einar Karttunen
Hello

It seems that the type of throwDyn and throwDynTo are dangerously close.
ThrowDyn works in with any of the arguments of throwDynTo, which can
cause evil situations.

throwDyn :: Typeable exception => exception -> b

Which means e.g. "throwDyn someThreadId SomeException" will work 
when you wanted to say "throwDynTo someThreadId SomeException"
and they both have types which unify with IO ().

I think using a
class Typeable => DynamicException a where ...
and throwDyn :: DynamicException a => a -> b
could make more sense.

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


[Haskell-cafe] Safe FFI calls, -threaded and killThread

2005-10-25 Thread Einar Karttunen
Hello

I noticed that killThread in GHC behaves in a problematic fashion with
-threaded when the killed thread is in a midle of performing a safe
FFI call. If the behaviour (blocking until the call is done) is intended
adding documentation might be nice.

The example below demonstrates the problem. Tthe program gets stuck
in the killThread call which is not very intuitive. Wrapping every
killThread in forkIO does not sound very nice either.

- Einar Karttunen



import Control.Concurrent
import Foreign.C

foreign import ccall threadsafe "sleep" sleep :: CInt -> IO CInt

main = do mv <- newEmptyMVar
  tid <- forkIO $ sleep 100 >> putMVar mv ()
  threadDelay 1
  e <- isEmptyMVar mv
  if e then do putStrLn "killing sleeper"
   killThread tid
   putStrLn "done"
   else do putStrLn "sleeper already done"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FPS lib

2005-10-18 Thread Einar Karttunen
On 18.10 10:44, Bulat Ziganshin wrote:
> 2) as i say you before, i need to sort filenames in windows fashion
> (case-ignoring), so if you will include case-ignoring comparision
> operators - i will be glad

Case ignoring comparisons make only sense on characters - not on bytes. 
And fps is ignoring character set conversion issues. I think the proper
way is to provide a layer on top of (and separate from) fps that does
conversion into character strings where things like case make sense.

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


[Haskell-cafe] Failure and comonads

2005-09-26 Thread Einar Karttunen
Hello

With the resent discussion on comonads on #haskell (mostly due to Uustalo's
excellent paper) I am wondering is it possible to model failure with 
comonads?

It seems to me that Reader,Writer and State can be implemented with both
monads and comonads. IO can be implemented as a monad but OI wants 
linear types. Streams make fine comonads. Is there anything corresponding
to Maybe or List?

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


Re: [Haskell-cafe] Binary parser combinators and pretty printing

2005-09-15 Thread Einar Karttunen
On 15.09 21:53, Bulat Ziganshin wrote:
> EK> data Packet = Packet Word32 Word32 Word32 [FastString]
> 
> well. you can see my own BinaryStream package at http://freearc.narod.ru
> 
> class BinaryData a where
>   read :: ...
>   write :: ...

I don't think this is a very good solution. Keeping the on-wire datatypes 
explicit makes sense to me. Also things like endianess will need to be 
taken into account. If the encoding is derived automatically then 
changing the Haskell datatype will change the on-wire representation.
This is not wanted when interfacing with external protocols.

For typeclasses I would rather have:
getWord32BE :: Num a => MyMonad a
than
get :: MyClass a => MyMonad a

Note the difference between the Haskell type determining the on-wire 
type and it being explicit. I already have working TH code for the 
case where I want to derive automatic binary serialization for 
Haskell datatypes (SerTH).

> EK> Maybe even the tuple could be eliminated by using a little of TH.
> 
> it may be eliminated even without TH! :+: and :*: should work,
> although i don't tried this

I don't know how generics work in newer versions of GHC, but 
it may be worth investigating.

- Einar Karttunen

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


Re: [Haskell-cafe] Binary parser combinators and pretty printing

2005-09-14 Thread Einar Karttunen
On 13.09 23:31, Tomasz Zielonka wrote:
> How about all these points together?:
> 
> a) Simple monadic interface

I think I already have this - minus packaging and documentation.

> b) Using better combinators

This is lacking.

> c) Using TH to generate code for the simple cases

I have TH for generating code, but that is not yet general 
purpose (the code comes from SerTH).

> d) Using type-classes

As most real-world protocols will need customization I cannot 
see much improvement here. Keeping the types of the serialized
data explicit makes sense. Otherwise changing an innocent Haskell
data declaration would cause on-wire data mismatch rather than
compile-time type errors.

> I've played with such frameworks a couple of times and I feel it's time
> to make a library useful for others. If you're interested, we could
> cooperate.
> 

I would be interested in cooperation and getting an usefull library released. 
Currently my parsers just use [FastString] (thus support lazy IO), peek and 
poke.

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


[Haskell-cafe] Binary parser combinators and pretty printing

2005-09-13 Thread Einar Karttunen
Hello

I am trying to figure out the best interface to binary parser
and pretty printing combinators for network protocols. 

I am trying to find the most natural syntax to express
these parsers in Haskell and would like opinions and
new ideas.

As an example I will use a protocol with the following packet structure:
0  message-id
4  sender-id
8  receiver-id
12 number of parameters
16 parameters. Each parameter is prefixed by 32bit length followed by 
   the data.

We will use the following Haskell datatype:

data Packet = Packet Word32 Word32 Word32 [FastString]

1) Simple monadic interface

getPacket = do mid <- getWord32BE
   sid <- getWord32BE
   rid <- getWord32BE
   nmsg<- getWord32BE
   vars<- replicateM (fromIntegral nmsg) (getWord32BE >>= getBytes)
   return $ Packet mid sid rid nmsg vars

putPacket (Packet mid sid rid vars) = do
  mapM_ putWord32BE [mid, sid, rid, length vars]
  mapM_ (\fs -> putWord32BE (length fs) >> putBytes fs) vars


This works but writing the code gets tedious and dull. 

2) Using better combinators

packet = w32be <> w32be <> w32be <> lengthPrefixList w32be (lengthPrefixList 
w32be bytes)
getPacket = let (mid,sid,rid,vars)  = getter packet in Packet mid sid rid vars
putPacket (Packet mid sid rid vars) = setter packet mid sid rid vars

Maybe even the tuple could be eliminated by using a little of TH.
Has anyone used combinators like this before and how did it work?

3) Using TH entirely

$(getAndPut 'Packet "w32 w32 w32 lengthPrefixList (w32 bytes)")

Is this better than the combinators in 2)? Also what sort of 
syntax would be best for expressing nontrivial dependencies - 
e.g. a checksum calculated from other fields.

4) Using a syntax extension

Erlang does this with the bit syntax 
(http://erlang.se/doc/doc-5.4.8/doc/programming_examples/bit_syntax.html)
and it is very nifty for some purposes. 

getPacket = do << mid:32, sid:32, rid:32, len:32 rest:len/binary >>
   ...

The list of lists gets nontrivial here too...


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


Re: [Haskell-cafe] Using unsafePerformIO

2005-08-01 Thread Einar Karttunen
"Dinh Tien Tuan Anh" <[EMAIL PROTECTED]> writes:
> will be written without unsafePerformIO:
>co' (x:xs) = do
>   c1 <- co' xs
>   c<- f (x:xs)
>   if (c==1)
>   then return 1:c1
>   else return 0:c1
>

You might want to use unsafeInterleaveIO :: IO a -> IO a. 
It allows IO computation to be deferred lazily.

In the particular example 
co' (x:xs) = do c1 <- unsafeInterleaveIO (co' xs)
c  <- f (x:xs)
if (c==1) then return (1:c1) else return (0:c1)


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


Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> No, unfortunately not.  You have foo's finalizer which refers to bar via
> a touchForeignPtr.  If both foo and bar are unreachable (references from
> finalizers don't count), then both foo and bar's finalizers will be
> started together, and may run in any order.

I didn't realize the "references from finalizers don't count" rule.
What would happen if the finalizer of foo would resurrect bar after 
bar's finalizer has been run?

> So touchForeignPtr does only one thing: it expresses the precise
> relationship "bar is alive if foo is alive".  If both are not alive,
> then both finalizers can run, in any order.

So reference counting the objects is the solution?

> I realise this is very subtle.  By all means suggest improvements to the
> docs.

Mentioning that references from finalizers don't count could help
someone not to repeat my mistakes.

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


Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
>> Now the association becomes
>> associate (Foo _ ref) bar =
>>   atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))
>
> Isn't that equivalent to using addForeignPtrFinalizer?  I don't think
> this fixes anything: the finalizer for bar can still run before the
> finalizer for foo.

foo has a single finalizer which is defined like:

fooFinalizer cfoo ref = do cdeleteFoo cfoo
   vs <- readIORef ref
   mapM_ (\c -> c) vs

and foo is created like

createFoo ptr = do ref <- newIORef []
   fp <- newForeigPtr ptr (fooFinalizer ptr ref)
   return (Foo fp ref)

As the finalizer of foo references the IORef which contains
the list of actions containing the "touchForeignPtr bar"
the finalizer of foo is run first. The finalizer to bar
should be able to run only when the touchForeignPtr has been 
executed in the mapM_ which only happens after foo 
has been cleaned up - if I understand things correctly.

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


Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> You might be able to find more information on this in the mailing list
> archives.  It's true that touchForeignPtr isn't enough to enforce an
> ordering on the running of finalizers, but it *can* be used to express a
> liveness relationship between one ForeignPtr and another (ForeignPtr A
> is alive if ForeignPtr B is alive).  This should be enough if you're
> dealing with pointer relationships between memory objects, for example,
> where it doesn't matter which one gets freed first when they're both
> unreferenced.

The order of the cleanup functions is significant in this case,
so that does not unfortunately help.

> If you really do need ordering, maybe it would be possible to use
> reference counting in your case?

I ended up using the following design, which seems to work fine:
data Foo = Foo (ForeignPtr Foo) (IORef [IO ()])
Each ForeignPtr Foo has a single finalizer which first calls the C-side
cleanup function for Foo and then executes all the IO-actions inside the 
IORef. 

Now the association becomes
associate (Foo _ ref) bar = 
  atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))

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


[Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-25 Thread Einar Karttunen
Hello

What is the correct way to express liveness dependencies for
ForeignPtrs? I am wrapping a C library and need a way to keep 
ForeignPtrs alive until the finalizer for an another ForeignPtr 
has been executed. 

Basically I have two types, ForeignPtr A and ForeignPtr B and a function
associate :: ForeignPtr A -> ForeignPtr B -> IO (). I want to keep all
of the ForeignPtr Bs associated with a given ForeignPtr A alive until its
finalizer has been run. The relationship is M:N - each ForeignPtr A may
be associated with multiple ForeignPtr B and each ForeignPtr B may be
associated with multiple ForeignPtr A.

GHC documentation tells that touchForeignPtr is not enough as it makes
no guarantees about when the finalizers are run. If it helps the
finalizers are C functions which neither block nor perform callbacks
into Haskell. 

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


Re: [Haskell-cafe] weired

2005-07-16 Thread Einar Karttunen
wenduan <[EMAIL PROTECTED]> writes:
> The following function which converts a number represents a sum of money 
> in pence didn't work as expected and the result didn't make any sense to me:
>
> penceToString :: Price -> String
> penceToString  p  =
>   let  str  =  show p
>len  =  length str
>   in
> if len ==1 then "0.0" ++ str else
>  if len ==2 then "0." ++ str else (take (len-2) str) ++ "." ++ 
> (drop (len - 2) str )
>
> *Main> penceToString 234566678786
> "-6710990.94"

You are encountering the fact the Int is a fixed size type (32 bits on
many common architectures). Thus 

*Main> 234566678786 :: Int
-671099094

Which explains the result. 

To make the program work use Integer instead of Int.


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


[Haskell-cafe] Functional dependencies and type inference

2005-07-15 Thread Einar Karttunen
Hello

I am having problems with GHC infering functional dependencies related
types in a too conservative fashion.

> class Imp2 a b | a -> b
> instance Imp2 (Foo a) (Wrap a)
>
>
> newtype Wrap a = Wrap { unWrap :: a }
> data Foo a = Foo
> data Proxy (cxt :: * -> *)
>
> foo :: Imp2 (ctx c) d => Proxy ctx -> (forall a b. (Imp2 (ctx a) b) => a -> 
> b) -> c -> d
> foo p f x = f x

The type of "foo (undefined :: Proxy Foo)" is inferred as
"forall c. (forall a b. (Imp2 (Foo a) b) => a -> b) -> c -> Wrap c"
which shows the outmost functional dependence is working fine. ctx
is carried to the inner Imp2. 

However "foo (undefined :: Proxy Foo) Wrap" will fail complaining that 

Couldn't match the rigid variable `b' against `Wrap a'
  `b' is bound by the polymorphic type `forall a b. (Imp2 (ctx a) b) => a 
-> b'
at :1:0-32
  Expected type: a -> b
  Inferred type: a -> Wrap a
In the second argument of `foo', namely `Wrap'

My guess is that GHC cannot see that the functional dependency
guarantees that there are no instances which make the inferred 
type invalid. Any solutions to this problem?


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


[Haskell-cafe] Open mutable records

2005-05-22 Thread Einar Karttunen
Hello

I recently ended up hacking a quite concise implementation of
mutable open (extensible) records in Haskell. Most of the ideas 
came from the HList-paper, but this seems like a very simple way of
doing things.

Run with ghci -fglasgow-exts -fallow-overlapping-instances.

Import some stuff we are going to need later:

> import Control.Monad.Reader
> import Data.IORef
> import System

Monad for mutable record calculations - to get implisit this/self in the
OO sense.

> newtype OO t r = OO (ReaderT t IO r) deriving(Monad, MonadReader t, MonadIO)
>
> with :: s -> OO s a -> OO b a
> with this (OO c) = liftIO (runReaderT c this)
>
> ooToIO :: OO s a -> IO a
> ooToIO (OO c) = runReaderT c undefined

Records

First the record constructor - followed by the terminator.

> data a :.: r = RC !a !r
> infixr :.:
> data END = END

Next we define a field access method.

> class Select r f t | r f -> t where (!) :: r -> f -> Ref t
> instance Select (Field f t :.: r) f t where (!) (RC (F x) _) _ = x
> instance Select r f t => Select (a :.: r) f t where (!) (RC _ t) = (!) t

And finally the type of mutable fields.

> type Ref a = IORef a
> newtype Field name rtype = F (Ref rtype)

Next we define a way to construct record values.

> infixr ##
> (##) :: v -> OO s r -> OO s ((Field f v) :.: r)
> (##) v r = do { h <- liftIO (newIORef v); t <- r; return (RC (F h) t) }
> end = return END :: OO s END

Get the value of a field.

> value :: Select s f t => f -> OO s t
> value a  = do x <- asks (\s -> s!a) 
>   liftIO (readIORef x)

Or set the value of a field.

> (<-:) :: Select s f t => f -> t -> OO s () 
> a <-: b  = do x <- asks (\s -> s!a)
>   liftIO (writeIORef x b)

And as a convenience add value to an int field.

> (+=) :: Select s f Int => f -> Int -> OO s Int
> a += b   = do x <- asks (\s -> s!a)
>   val <- liftIO (readIORef x)
>   let z = val+b
>   z `seq` liftIO (writeIORef x z)
>   return z

Now implement the classic ocaml OO tutorial:

> data X = X
> type Point = Field X Int :.: END
>
> newPoint :: OO s Point
> newPoint = 0 ## end
>
> getX :: Select s X t => OO s t
> getX = value X
>
> move d = X += d

> data Color = Color
> type ColoredPoint = Field Color String :.: Point
>
> newColoredPoint :: String -> OO s ColoredPoint
> newColoredPoint c = c ## 0 ## end
>
> color :: Select s Color t => OO s t
> color = value Color

The code looks in more complex examples like this:
((~=) is prepending into list fields.)

newArrival :: Patient -> OO Hospital ()
newArrival patient = do
  with patient (HospitalVisits += 1)
  staff <- value FreeStaff
  if staff > 0 then do FreeStaff += (-1)
   Examination ~= patient
   with patient (do HospitalTime += 3
RemainingTime <-: 3)
   else do Triage ~= patient


> main = ooToIO (do c1 <- newPoint
>   c2 <- newColoredPoint "green"
>   with c1 $ move 7
>   with c2 $ move 4
>   let p x = liftIO (print x)
>   p =<< with c1 getX
>   p =<< with c2 getX)


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


Re: [Haskell-cafe] invalid character encoding

2005-03-19 Thread Einar Karttunen
Wolfgang Thaller <[EMAIL PROTECTED]> writes:
> In what way is ISO-2022 non-reversible? Is it possible that a ISO-2022 
> file name that is converted to Unicode cannot be converted back any 
> more (assuming you know for sure that it was ISO-2022 in the first 
> place)?

I am no expert on ISO-2022 so the following may contain errors,
please correct if it is wrong.

ISO-2022 -> Unicode is always possible.
Also Unicode -> ISO-2022 should be always possible, but is a relation
not a function. This means there are an infinite? ways of encoding a
particular unicode string in ISO-2022.

ISO-2022 works by providing escape sequences to switch between different
character sets. One can freely use these escapes in almost any way you
wish. Also ISO-2022 makes a difference between the same character in
japanese/chinese/korean - which unicode does not do.

See here for more info on the topic:
http://www.ecma-international.org/publications/files/ecma-st/ECMA-035.pdf


Also trusting system locale for everything is problematic and makes
things quite unbearable for I18N. e.g. on my desktop 95% of things run
with iso-8859-1, 3% of things use utf-8 and a few apps use EUC-JP...

Using filenames as opaque blobs causes the least problems. If the
program wishes to display them in a graphical environment then they have
to be converted to a string, but very many apps never display the
filenames...

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


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
Tomasz Zielonka <[EMAIL PROTECTED]> writes:
>   import Control.Concurrent (forkIO, threadDelay)
>   import Control.Concurrent.STM
>
>   withTimeout :: Int -> STM a -> IO (Maybe a)
>   withTimeout time fun = do
>   mv <- atomically newEmptyTMVar
>   tid <- forkIO $ do
>   threadDelay time
>   atomically (putTMVar mv ())
>   x <- atomically (fmap Just fun `orElse` (takeTMVar mv >> return 
> Nothing))
>   killThread tid
>   return x

Isn't this buggy if fun just keeps working without throwing an exception
or using retry? I meant wholly inside STM - if we use IO as the
signature then using the TMVar has few advantages over using an MVar.

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


[Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
Hello

What is the best way of doing an computation with a timeout?

A naive implementation using two threads is easy to create - but 
what is the preferred solution?

withTimeout :: forall a. Int -> IO a -> IO (Maybe a)
withTimeout time fun =
  do mv <- newEmptyMVar
 tid <- forkIO (fun  >>= tryPutMVar mv . Just >> return ())
 forkIO (threadDelay time >>  killThread tid >> tryPutMVar mv Nothing >> 
return ())
 takeMVar mv 


btw How would I do the same with the new STM abstraction?

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


[Haskell-cafe] ArrowLoop examples?

2004-10-23 Thread Einar Karttunen
Hello

Are there any examples of using ArrowLoop outside the signal
functions? Instances are declared for ordinary functions and 
Kleisli arrows, but how should they be actually used?

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Seeking reference(s) relating to FP performance

2004-09-29 Thread Einar Karttunen
On 29.09 19:00, John Goerzen wrote:
> 3. ghc doesn't seem to do very well in terms of performance, though it
> does at least beat out Java in many cases.

Please note that many of the GHC programs are not posed for
performance, but rather elegance. E.g. the nestedloop got
seven times faster with minor corrections (not reflected
on the website yet).

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
On 20.09 15:05, Dylan Thurston wrote:
> You know about the PackedString functions, right?
> 
> http://www.haskell.org/ghc/docs/6.0/html/base/Data.PackedString.html

Yes, but they are quite broken. I am using FastPackedString from 
darcs for many purposes, which is like PackedString in many 
ways.

PackedStrings use full unicode codepoints (4*size in bytes), but
having a char > 256 in them does not work if one wants to do IO.
This means essentially that the wasted space cannot be used in any
meaningfull way. 

Also concatenating PackedStrings is not very nice:
concatPS pss = packString (concat (map unpackPS pss))

And most important they need a conversion (unpackPS), before
using them with external libraries which expect Strings.

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
On 20.09 12:59, Henning Thielemann wrote:
> > Handling large amounts of text as haskell strings is currently not
> > possible as the representation (list of chars) is very inefficient. 
> 
> Efficiency is always a reason to mess everything. But the inefficiency
> applies to lists of every data type, so why optimizing only Strings, why
> not optimizing Lists in general, or better all similar data structures, as
> far as possible? Why not doing it in a transparent way by an optimizer in
> the compiler? This is certainly the more complicated task, but the more
> promising target for the long term. I very like to apply List functions to
> Strings, so the definition String = [Char] seems to me the most natural
> definition. 

Optimizing all lists would be nice but choosing allways the correct
behaviour would be quite hard. Of course if such an optimization would
exists Strings would benefit from it. 

Making strings an abstract type would not preclude using such
optimizations. But Strings could be optimized even before the
optimization existed.

The list of chars seems natural when thinking in terms of
transformations, but it is not very natural when trying to interact
with external world.

> > It is currently hard to define typeclass instances for strings as 
> > String ( = [Char]) overlaps with [a]. Implementations provide
> > solutions for this, but there should not be a need for workarounds
> > in the first place.
> 
> That's a problem, I also like to hear opinions about that. E.g. Show
> instance of String doesn't output ['b','l','a'] but "bla". 
> 

This is because Show has a special case for lists:

class Show
  showsPrec :: Int -> a -> ShowS
  show  :: a   -> String
  showList  :: [a] -> Shows

This is not very elegant and does not help when using a boilerplate style
traversal.

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
Hello

Strings in haskell seem to be one major source of problems. I try 
to outline some of the problems I have faced and possible solutions.


Size

Handling large amounts of text as haskell strings is currently not
possible as the representation (list of chars) is very inefficient. 


Serialization

Most of the time when serializing a string, we want to handle it as an
array of Word8. With lists one has to account for cycles and infinite 
length which make the encoding much more verbose and slow. 

The problem is not that some strings may not be trivially
serializable, but rather that it is hard to find the easy
cases.


Typeclass instances

It is currently hard to define typeclass instances for strings as 
String ( = [Char]) overlaps with [a]. Implementations provide
solutions for this, but there should not be a need for workarounds
in the first place.


Show/Read

The current Show/Read implementation makes it impossible to use
with large strings. A read implementation needs to traverse the file 
looking for the terminating '"' and handling escape codes. 

A better solution would be to have an efficient (size prefixed)
representation, maybe in a separate Serializable typeclass. But
this would need the ablity to derive Serializable instances for
algebraic datatypes automatically to avoid lots of useless code.


Possible solutions

The optimal solution should be compact and fast. A list of chunks
is one solution - it would make it possible to e.g. mmap files (modulo
encoding) and support fast concatenation. 

In addition one would need to support infinite and cyclic structures.
Adding an alternative which corresponds to the current string
abstraction would be sufficient.

type CharT = Word8

data Str = S [(Ptr CharT, Int)]
 | I [CharT]


A major problem is breaking old code. The main problem is that many
functions are defined only on lists which forces strings to be lists. 
Making the functions polymorphic would solve a lot of problems and 
not only for Strings. There should be no performance penalty (at least
in theory) when the compiler knows which instance is used at compile
time.

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
On 01.09 13:09, Jan-Willem Maessen - Sun Labs East wrote:
> I was, however, curious what use you had in mind where writes were 
> racing, but where you nonetheless wanted to perform blind non-blocking 
> reads.  Such situations are generally fraught with peril.  In this 
> case, the peril is starvation of the debug thread---which you may or 
> may not actually care about.

I was trying to implement safe tryReadChan, which seems to be 
very simple with tryReadMVar, without it it seems to suffer
from various concurrency problems.

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
On 01.09 18:30, MR K P SCHUPKE wrote:
>   while channel not empty
>   read next event
>   if event high priority process now
>   else queue event in FIFO
>   process first event in FIFO

That suffers from the same problem as I described.

do e <- isEmptyChan ch -- is the channel empty?
   case e of
True -> processFifo
False-> readChan ch >>= highPriorityOrPush

Now there is danger of blocking on the readChan. (consider a case
where we create two similar server processes reading the same
channel). Now we create a tryReadChan, but we cannot implement
it with tryTakeMVar, as that would break dupChan. Rather we
need a tryReadMVar or a different channel abstraction.

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
On 01.09 09:27, Jan-Willem Maessen - Sun Labs East wrote:
> Einar Karttunen wrote:
> >Hello
> >
> >Is it possible to implement an operation like 
> >tryReadMVar :: MVar a -> IO (Maybe a)
> >in a good fashion? The semantics should be 
> >"Read the value of the MVar without taking
> >it if it is filled, otherwise return Nothing".
> >
> >There are several easy and flawed implementations:
> >...
> >tryReadMVar mv = do mc <- tryTakeMVar mv
> >case mc of
> > Nothing -> return mc
> > Just v  -> putMVar mv v >> return mc
> >
> >Now this can block on the putMVar if there was a thread switch 
> >and someone filled the MVar behind our back. 
> 
> This sets off alarm bells in my head.  What are you actually trying to 
> do, and why is correct for mutiple threads to race to "putMVar"?

There are several cases in which multiple threads racing putMVar is
correct. Consider e.g. a server thread encapsulating state, which 
needs to rate limit its clients. The server is put behind a MVar
to which all the clients putMVar and thus block until the server 
is ready e.g. 

plumbIn :: MVar SCoreT -> HId -> Handle -> IO ()
plumbIn mv hid h = hGetContents h >>= loop
where loop s = let (m,r) = readInput s in putMVar mv (Msg m hid) >> loop r

The server thread uses tryTakeMVar for its job. 

Now add a debug function:

debug :: MVar SCoreT -> IO ()
debug mv = tryReadMVar mv >>= maybe (putStrLn "Nothing") print

And suddenly we have a created a subtle bug in the code with 
flawed tryReadMVar implementation.

- Einar Karttunen 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
Hello

Is it possible to implement an operation like 
tryReadMVar :: MVar a -> IO (Maybe a)
in a good fashion? The semantics should be 
"Read the value of the MVar without taking
it if it is filled, otherwise return Nothing".

There are several easy and flawed implementations:

tryReadMvar mv = do e <- isEmptyMVar mv
case e of
 True -> return Nothing
 False-> readMVar mv >>= return . Just

This does not work because there can be a thread switch 
between the isEmpty and readMVar.

tryReadMVar mv = do mc <- tryTakeMVar mv
case mc of
 Nothing -> return mc
 Just v  -> putMVar mv v >> return mc

Now this can block on the putMVar if there was a thread switch 
and someone filled the MVar behind our back. 

Using tryPutMVar does not help much as it just creates another 
race condition:

tryReadMVar mv = do mc <- tryTakeMVar mv
case mc of
 Nothing -> return mc
 Just c  -> tryPutMVar mv v >> return mc

Consider what happens if the tryPutMVar fails:

-- read till we get the value with foobar in the middle
loopTill mv = do foobar 
 mc <- tryReadMVar mv
 case mc of
  Nothing -> loopTill mv
  Just v  -> return v

maybe (loopTill mv) process (tryReadMVar mv)

error = do mv <- newEmptyMVar
   forkIO (mapM_ (\i -> putMVar mv i) [1..10])
   mapM_ (\_ -> loopTill mv >>= print >> takeMVar mv >>= print) [1..10]

If a tryPutMVar fails, then there will be less than ten values to 
read which will make the process block in takeMVar.

This seems quite straightforward in C with GHC (might be wrong
in the SMP case with locking?):

tryReadMVarzh_fast
{
W_ mvar, info;

/* args: R1 = MVar closure */
mvar = R1;
info = GET_INFO(mvar);

if (info == stg_EMPTY_MVAR_info) 
  RET_NP(0, stg_NO_FINALIZER_closure);

RET_NP(1, vStgMVar_value(mvar);
}

What is the best way to do this?

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe