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

2006-09-13 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 name of type value. When deserializing use a Map name of type

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Ketil Malde
Daniel Fischer [EMAIL PROTECTED] writes: Maybe I've misused the word segfault. I think so. A segfault is the operating-system complaining about an illegal memory access. If you get them from Haskell, it is likely a bug in the compiler or run-time system (or you were using unsafeAt, or FFI).

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all. Quoting Jason Dagit [EMAIL PROTECTED]: I was making an embedded domain specific language for excel spreadsheet formulas recently and found that making my formula datatype an instance of Num had huge pay offs. Just so you know, what we're talking about here is a way to make that

[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 (=

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

2006-09-13 Thread Chris Kuklewicz
Einar Karttunen wrote: 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

[Haskell-cafe] Re: evaluate vs seq

2006-09-13 Thread apfelmus
Michael Shulman wrote: On 9/11/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: * (a `seq` return a) = evaluate a *right now*, then produce an IO action which, when executed, returns the result of evaluating a. Thus, if a is undefined, throws an exception right now. is a bit misleading

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

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ross Paterson
On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote: One of the proposals that comes up every so often is to allow the declaration of a typeclass instance to automatically declare instances for all superclasses. So, for example: class (Functor m) = Monad m where

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Daniel Fischer wrote: Most certainly not. I'm pretty sure this is to a bug in your code. Something retains a data structure which is actually unneeded. Probably Apparently. And my money is on a load of lines from the file (of which I need only the first and last Char). Then you're

Re: [Haskell-cafe] foreach

2006-09-13 Thread Udo Stenzel
Lemmih wrote: main = do args - getArgs flip mapM_ args $ \arg - flip mapM_ [1..3] $ \n - putStrLn $ show n ++ ) ++ arg Or even: main = do args - getArgs putStr $ unlines [ show n ++ ) ++ arg | arg - args, n - [1..3] ] I'm really at a loss

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Ketil Malde wrote: Daniel Fischer [EMAIL PROTECTED] writes: Maybe I've misused the word segfault. I think so. A segfault is the operating-system complaining about an illegal memory access. If you get them from Haskell, it is likely a bug in the compiler or run-time system (or you were

Re: [Haskell-cafe] foreach

2006-09-13 Thread Henning Thielemann
On Wed, 13 Sep 2006, Donald Bruce Stewart wrote: lemmih: On 9/13/06, Tim Newsham [EMAIL PROTECTED] wrote: I was rewriting some non-haskell code in haskell and came up with this construct: foreach l f = mapM_ f l main = do args - getArgs foreach args (\arg

[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann
On Tue, 12 Sep 2006, Aaron Denney wrote: On 2006-09-12, Bryan Burgers [EMAIL PROTECTED] wrote: And another problem I can see is that, for example, the Integers are a group over addition, and also a group over multiplication; Not over multiplication, no, because there is no inverse. I

Re[2]: [Haskell-cafe] Slow IO

2006-09-13 Thread Bulat Ziganshin
Hello Ketil, Wednesday, September 13, 2006, 10:41:13 AM, you wrote: But a String is something like 8 or 12 bytes per character, a ByteString gets you down to 1. 12-16. Char itself, pointer to the next list element, and two boxes around them - this count for 16 bytes on 32-bit CPU. but cells

Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Bulat Ziganshin
Hello Henning, Wednesday, September 13, 2006, 1:12:35 PM, you wrote: Adding sugar or using Template Haskell for such a simple task is a bit unreasonable. I think Tim should use mapM a little bit and then he will probably need no longer a special syntax. i disagree. lack of good syntax makes

Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Bulat Ziganshin
Hello Udo, Wednesday, September 13, 2006, 12:53:38 PM, you wrote: main = do args - getArgs flip mapM_ args $ \arg - flip mapM_ [1..3] $ \n - putStrLn $ show n ++ ) ++ arg Or even: main = do args - getArgs putStr $ unlines [ show n ++ ) ++ arg

[Haskell-cafe] Re: foreach

2006-09-13 Thread Henning Thielemann
On Wed, 13 Sep 2006, Bulat Ziganshin wrote: Wednesday, September 13, 2006, 1:12:35 PM, you wrote: Adding sugar or using Template Haskell for such a simple task is a bit unreasonable. I think Tim should use mapM a little bit and then he will probably need no longer a special syntax. i

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Lennart Augustsson
The sum function really only needs the argument list to be a monoid. And the same is true for the product function, but with 1 and * as the monoid operators. Sum and product are really the same function. :) I don't think Haskell really has the mechanisms for setting up an algebraic class

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann
On Wed, 13 Sep 2006, Lennart Augustsson wrote: The sum function really only needs the argument list to be a monoid. And the same is true for the product function, but with 1 and * as the monoid operators. Sum and product are really the same function. :) ... which got the same name, too,

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: ... which got the same name, too, namely 'foldl'. You mean foldr. The place of foldl is a bit tricky, but in this case it requires that the monoid be Abelian. Cheers, Andrew Bromage ___

Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-13 Thread Jan-Willem Maessen
On Sep 5, 2006, at 7:05 AM, Chris Kuklewicz wrote: Bulat Ziganshin wrote: Hello Bertram, Tuesday, September 5, 2006, 12:24:57 PM, you wrote: A quick hack up to use Data.ByteString uses a lot less ram, though profiling still shows 95% of time spent in the building the Map. Data.HashTable may

Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Daniel Fischer
Am Mittwoch, 13. September 2006 11:07 schrieben Sie: Daniel Fischer wrote: Most certainly not. I'm pretty sure this is to a bug in your code. Something retains a data structure which is actually unneeded. Probably Apparently. And my money is on a load of lines from the file (of

[Haskell-cafe] [OT] A DSL for state machines

2006-09-13 Thread Stephane Bortzmeyer
Sorry, this is a bit off-topic but I post here because: * it is about a DSL and many Haskellers are fond of DSLs, * the first implementation is written in Haskell. http://www.cosmogol.fr/ describes a proposal to the IETF to standardize the language used for finite state machines (which are

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

2006-09-13 Thread Misha Aizatulin
Einar Karttunen 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 name of type value. When deserializing use a Map name of type

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

2006-09-13 Thread Ralf Lammel
I start wondering, how OO languages solve the same problem. Conceptually, what is needed is a mapping of the head of the input to a type. This is indeed a recurring problem in OO languages; think of object serialization or XML/Object mapping. One common way of accomplishing the mapping is to

Re: [Haskell-cafe] foreach

2006-09-13 Thread Brandon Moore
Tim Newsham wrote: I was rewriting some non-haskell code in haskell and came up with this construct: foreach l f = mapM_ f l main = do args - getArgs foreach args (\arg - do foreach [1..3] (\n - do putStrLn ((show n) ++ ) ++ arg) ) ) which is reminiscent of foreach in other languages. Seems

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Brian Hulley
Henning Thielemann wrote: On Wed, 13 Sep 2006, Lennart Augustsson wrote: I don't think Haskell really has the mechanisms for setting up an algebraic class hierarchy the right way. Consider some classes we might want to build: SemiGroup Monoid AbelianMonoid Group AbelianGroup SemiRing Ring ...

[Haskell-cafe] ffi question

2006-09-13 Thread Maverick
Hi, I have a question about ffi in Hugs98 (WinHugs-May2006.exe), the Hugs98 documentation says:"Only the ccall, stdcall and dotnet calling conventions are supported. All others are flagged as errors."But I can't get a dotnet import, the ffihugs returns me an error:ffihugs

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Jacques Carette
Your solution would imply[1] that all Rational are multiplicatively invertible -- which they are not. The Rationals are not a multiplicative group -- although the _positive_ Rationals are. You can't express this in Haskell's type system AFAIK. Your basic point is correct: if you are willing

Re: [Haskell-cafe] foreach

2006-09-13 Thread Tim Newsham
foreach l f = mapM_ f l ... rename to forM_ as per previous emails ... I would like to add to this. The previous loop runs the code once independantly for each item in the list. Sometimes you want to carry state through the loop: v = init foreach x list do code v =

[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Aaron Denney
On 2006-09-13, Ross Paterson [EMAIL PROTECTED] wrote: On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote: One of the proposals that comes up every so often is to allow the declaration of a typeclass instance to automatically declare instances for all superclasses. So, for

Re: [Haskell-cafe] Re: evaluate vs seq

2006-09-13 Thread Michael Shulman
On 9/13/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: So `seq` forces its first argument. When we define f x = x `seq` (Return x) we thereby get f _|_== _|_ f [] == Return [] f (x:xs) == Return (x:xs) To compare, the semantics of (evaluate) is evaluate _|_== ThrowException

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

2006-09-13 Thread Ashley Yakeley
Misha Aizatulin wrote: This is indeed the only solution I see so far. It has a serious problem though: as soon as I write the mapping, I limit once and for all the set of all types that can be used with my box. And I do so in a non-extensible way - if someone later would like to use my box

Re: [Haskell-cafe] foreach

2006-09-13 Thread Michael Shulman
On 9/13/06, Henning Thielemann [EMAIL PROTECTED] wrote: If you want more sugar, what about the list monad? main = do args - getArgs sequence_ $ do arg - args n - [1..3] return (putStrLn $ show n ++ ) ++ arg) Or, what about using ListT

Re: Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Jeremy Shaw
At Wed, 13 Sep 2006 15:24:39 +0400, Bulat Ziganshin wrote: because REAL code is somewhat larger than examples. try to rewrite the following: directory_blocks - (`mapM` splitBy (opt_group_dir command) files_to_archive) ( \filesInOneDirectory - do datablocks - (`mapM`

Re: [Haskell-cafe] MonadList?

2006-09-13 Thread Michael Shulman
On 9/13/06, Bertram Felgenhauer [EMAIL PROTECTED] wrote: Michael Shulman wrote: class MonadList m where option :: [a] - m a [...] There's no need for an extra class, it can be done with MonadPlus: option :: MonadPlus m = [a] - m a option = msum . map return But this doesn't always give

[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ashley Yakeley
Aaron Denney wrote: I know of no good way to express that a given data type obeys the same interface two (or more) ways. The best approach here is to use data structures instead of classes: data Monoid a = MkMonoid { monoidNull :: a, monoidFunc :: a - a - a } -- Ashley Yakeley

Re: [Haskell-cafe] MonadList?

2006-09-13 Thread Twan van Laarhoven
Michael Shulman wrote: The frequent occurence of ListT $ return in my code when I use the ListT monad transformer has made me wonder why there isn't a standard typeclass `MonadList', like those for the other monad transformers, encapsulating the essence of being a list-like monad -- in this

Re: [Haskell-cafe] Weak pointers and referential transparency???

2006-09-13 Thread tpledger
Brian Hulley wrote: [EMAIL PROTECTED] wrote: [...] My reading of the semantics (http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#4) is that you can be sure the proxy *object* is gone. My problem is that I don't know what to make of the word object in the

[Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson
Dear Haskell Cafe, When programming the other day I ran into this problem. What I want to do is a function that would work like this: splitStreams::Ord a=[(a,b)]-[(a,[b])] splitStreams [(3,x),(1,y),(3,z),(2,w)] [(3,[x,z]),(1,[y]),(2,[w])] I don't care about the order that the pairs are

Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Twan van Laarhoven
Magnus Jonsson wrote: Dear Haskell Cafe, When programming the other day I ran into this problem. What I want to do is a function that would work like this: splitStreams::Ord a=[(a,b)]-[(a,[b])] splitStreams [(3,x),(1,y),(3,z),(2,w)] [(3,[x,z]),(1,[y]),(2,[w])] A O(n log(n)) algorithm

Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson
Nice try Twan but your example fails on infinite lists. I cleaned up your example so that it compiles: import qualified Data.Map as Map splitStreamsMap :: Ord a = [(a,b)] - Map.Map a [b] splitStreamsMap = foldl add Map.empty where add m (a,b) = Map.insertWith (++) a [b] m splitStreams ::

[Haskell-cafe] Optimization problem

2006-09-13 Thread tpledger
Magnus Jonsson wrote: [...] but your example fails on infinite lists [...] take 2 $ snd $ head $ splitStreams (map (\x - (0 ,x)) [1..]) Any approach, even sieving, will struggle with infinite lists, won't it? (take 2 . snd . head . splitStreams) [(i, i) | i - [0..]] Regards, Tom

[Haskell-cafe] program execution and laziness

2006-09-13 Thread Tim Newsham
I'm having a problem with program execution in win32 which seems to be tied to laziness. The function I'm using is: runCmd cmd outdir dir base ext = do let argv = words cmd (i,o,e,p) - runInteractiveProcess (head argv) (drop 1 argv) Nothing Nothing hClose i out - hGetContents

Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson
On Thu, 14 Sep 2006 [EMAIL PROTECTED] wrote: Any approach, even sieving, will struggle with infinite lists, won't it? (take 2 . snd . head . splitStreams) [(i, i) | i - [0..]] Yes, if you expect two messages but only one comes then you'll wait forever, true. Regards, Tom

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread David Menendez
Ross Paterson writes: Such features would be useful, but are unlikely to be available for Haskell'. If we concede that, is it still desirable to make these changes to the class hierarchy? I've collected some notes on these issues at