[Haskell-cafe] Still not dead

2006-07-21 Thread Einar Karttunen
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] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
is quite transparent. - 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
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

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

2006-08-01 Thread Einar Karttunen
) 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

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

2006-09-13 Thread Einar Karttunen
decoder-function 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

[Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
(= 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

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] Re: [Haskell] BitSyntax for Haskell

2006-09-25 Thread Einar Karttunen
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

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

2006-09-28 Thread Einar Karttunen
, 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] Re: [Haskell] BitSyntax for Haskell

2006-09-28 Thread Einar Karttunen
(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

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

2006-09-28 Thread Einar Karttunen
, 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

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

2006-09-28 Thread Einar Karttunen
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

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

2006-10-30 Thread Einar Karttunen
. 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

Re: [Haskell-cafe] invalid character encoding

2005-03-19 Thread Einar Karttunen
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-cafe] Functional dependencies and type inference

2005-07-15 Thread Einar Karttunen
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

Re: [Haskell-cafe] weired

2005-07-16 Thread Einar Karttunen
*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] ForeignPtrs with liveness dependencies

2005-07-25 Thread Einar Karttunen
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

Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
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

Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
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

Re: [Haskell-cafe] Using unsafePerformIO

2005-08-01 Thread Einar Karttunen
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] Binary parser combinators and pretty printing

2005-09-13 Thread Einar Karttunen
://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

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

2005-09-15 Thread Einar Karttunen
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

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

2005-09-15 Thread Einar Karttunen
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] throwDyn typing fun

2005-11-11 Thread Einar Karttunen
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

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

2005-11-28 Thread Einar Karttunen
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] STM commit hooks

2005-11-29 Thread Einar Karttunen
. 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] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Einar Karttunen
. 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] Opening the same file multiple times

2005-12-11 Thread Einar Karttunen
no simpler solution? - 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 ekarttun@cs.helsinki.fi: | 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

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

2005-12-12 Thread Einar Karttunen
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] Optimizing a high-traffic network architecture

2005-12-14 Thread Einar Karttunen
--- 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

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

2005-12-15 Thread Einar Karttunen
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

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 ekarttun@cs.helsinki.fi 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

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

2005-12-21 Thread Einar Karttunen
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] binary IO

2005-12-28 Thread Einar Karttunen
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

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

2006-01-09 Thread Einar Karttunen
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

[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-11 Thread Einar Karttunen
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] I/O and utf8

2006-01-11 Thread Einar Karttunen
? 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

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

2006-02-09 Thread Einar Karttunen
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

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

2006-02-20 Thread Einar Karttunen
= 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] 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 ()

[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] Re: request for code review

2006-03-12 Thread Einar Karttunen
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

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

Re: [Haskell-cafe] GetOpt

2006-04-26 Thread Einar Karttunen
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] GetOpt

2006-04-27 Thread Einar Karttunen
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] Existentially-quantified constructors: Hugs is fine, GHC is not?

2006-05-10 Thread Einar Karttunen
-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

[Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
?): 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

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

Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
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-02 Thread Einar Karttunen
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] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
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] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
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

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

2004-09-20 Thread Einar Karttunen
(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

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

2004-09-29 Thread Einar Karttunen
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

[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

[Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
= 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

Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
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