Re: [Haskell-cafe] more thoughts on Finally tagless

2010-03-09 Thread Martijn van Steenbergen
Tom Schrijvers wrote: data EvalDict sem = EvalDict { val :: Int - sem Int, add :: sem Int - sem Int - sem Int } An alternative option is to capture the structure in a GADT: data Eval a where Val :: Int - Eval Int Add :: Eval Int - Eval Int - Eval Int And then write what were instances

Re: [Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-02 Thread Martijn van Steenbergen
On 3/31/10 12:44, Heinrich Apfelmus wrote: go Next (Single x t1) = liftM (Single x) (rewrite f t1) go Next (Fork t1 t2 ) = liftM2 Fork (rewrite f t1) (rewrite f t2) In particular, liftM and liftM2 make it apparent that we're

Re: [Haskell-cafe] Hackage accounts and real names

2010-04-05 Thread Martijn van Steenbergen
+1 for lifting this restriction. On 4/4/10 23:28, David House wrote: An issue came up on #haskell recently with Hackage accounts requiring real names. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Weird behaviour with positional parameters in HDBC-mysql

2010-04-07 Thread Martijn van Steenbergen
Dear café (CC John and Chris), I'm having some trouble with getting positional parameters in HDBC-mysql to work. Most of the time they work fine, but sometimes (and often enough that it's a serious bother) the parameters don't reach the server correctly. Let me first describe my setup: *

Re: [Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-08 Thread Martijn van Steenbergen
On 4/6/10 15:31, Heinrich Apfelmus wrote: In fact, it doesn't actually work for monads, I think you have to wrap it in a newtype. :D The same effect can be achieved with `ap` , though: Fortunately, by now most (standard) monads are also applicatives. :-) Besides generalizing to an arbitrary

[Haskell-cafe] Re: Weird behaviour with positional parameters in HDBC-mysql

2010-04-17 Thread Martijn van Steenbergen
Thanks! That's great news. Yes, all seems fine now. :-) It was a very interesting bug to isolate. At one point I was in the situation where compiling with -O2 fixed the problem and -O0 didn't, seemingly consistently. By the way, I got two warnings while compiling: * Warning: Fields of

Re: [Haskell-cafe] Cabal-install: bus error

2010-05-04 Thread Martijn van Steenbergen
On 5/3/10 23:46, Jason Dagit wrote: This happened to a co-worker on her mac. We used gdb to track the bus errors to the network library. Once we tracked it down to there, we did some combination of deleting $HOME/.cabal, building/installing the latest version of Network and then relinking

Re: [Haskell-cafe] learning advanced haskell

2010-06-14 Thread Martijn van Steenbergen
On 6/14/10 10:39, Ivan Lazar Miljenovic wrote: By being told that using them would solve some problem you're complaining about on #haskell or the mailing lists, you look at examples, read up on them, etc. Short version: don't worry about advanced concepts until you have to. If all else fails,

Re: [Haskell-cafe] parsec: how to get end location

2010-06-14 Thread Martijn van Steenbergen
On 6/14/10 0:10, Roman Cheplyaka wrote: Of course most parsers don't consume trailing newlines. But I was writing general function to use in many places in the code which would recover the end location. In most cases it just subtracts 1 from the column number, but what if it just happened so

Re: [Haskell-cafe] Code Example and Haskell Patterns

2010-07-09 Thread Martijn van Steenbergen
On 7/8/10 21:36, Stephen Tetley wrote: Hello I suspect you will have to choose single examples for each of the patterns/ abstractions you are interested in. Doaitse Swierstra's library UU.Parsing is the originator or the Applicative style. Its latest incarnation is the library uu-parsinglib.

Re: [Haskell-cafe] List manager and duplicate copies of messsages

2010-07-21 Thread Martijn van Steenbergen
On 7/21/10 12:48, José Romildo Malaquias wrote: Hello. I have noticed that I do not receive duplicate copies of messages from haskell-cafe, although Avoid duplicate copies of messages? is set to No in the mailing list membership configuration. I want the copies because I archive all the

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-28 Thread Martijn van Steenbergen
On 7/28/10 14:53, S. Doaitse Swierstra wrote: see: file:///Users/doaitse/.cabal/share/doc/uu-parsinglib-2.4.2/html/index.html Readers might have more luck with the following URLs: http://hackage.haskell.org/package/uu-parsinglib

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-28 Thread Martijn van Steenbergen
On 7/27/10 9:58, Sebastian Fischer wrote: On Jul 27, 2010, at 9:15 AM, Sjoerd Visscher wrote: Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a Semiring, Yes, but it's hard to define an Eq instance for arbitrary regular expressions that reflects equivalence of regexps.

Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Martijn van Steenbergen
On 7/30/10 9:29, Stefan Holdermans wrote: Jason, There is one case where you can break out of a monad without knowing which monad it is. Well, kind of. It's cheating in a way because it does force the use of the Identity monad. Even if it's cheating, it's still very clever and

Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Martijn van Steenbergen
On 7/30/10 12:29, Tillmann Rendel wrote: C K Kashyap wrote: I am of the understanding that once you into a monad, you cant get out of it? That's not correct. There are many monads, including Maybe, [], IO, ... All of these monads provide operations (=), return and fail, and do notation

[Haskell-cafe] Reverse unification question

2010-08-02 Thread Martijn van Steenbergen
Dear café, Given: instance Category C y :: forall r. C r (A - r) I am looking for the types of x and z such that: x . y :: forall r. C r r y . z :: forall r. C r r Can you help me find such types? I suspect only one of them exists. Less importantly, at least to me at this moment: how do I

[Haskell-cafe] Re: [Haskell] ANNOUNCE: usb-0.1

2009-10-01 Thread Martijn van Steenbergen
Bas van Dijk wrote: Comments and patches are highly welcome. I tried to install on my Mac but bindings-common choked on: cabal install bindings-common Resolving dependencies... cabal: Error: some packages failed to install: bindings-common-1.1 failed while unpacking the package. The

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: usb-0.1

2009-10-01 Thread Martijn van Steenbergen
Roel van Dijk wrote: Yes, that happens. I don't now the cause but the work-around is easy. Simply download the package manually from hackage, unpack and install using cabal. At least the following packages suffer from this problem: bindings-common bindings-libusb bindings-posix Perhaps

Re: [Haskell-cafe] type inference question

2009-10-08 Thread Martijn van Steenbergen
minh thu wrote: Also, I'd like to know why id id True is permitted but not (\f - f f True) id Because this requires rank-2 types: Prelude :set -XScopedTypeVariables Prelude :set -XRank2Types Prelude (\(f :: forall a. a - a) - f f True) id True HTH, Martijn.

Re: [Haskell-cafe] Any example of concurrent haskell application?

2009-10-09 Thread Martijn van Steenbergen
Daryoush Mehrtash wrote: I am trying to learn more about concurrent applications in Haskell by studying an existing a real application source code. I would very much appreciate if you can recommend an application that you feel has done a good job in implementing a real time application in

[Haskell-cafe] Non-traversable foldables

2009-10-09 Thread Martijn van Steenbergen
Hallo café, Can anyone think of datatypes that are Foldable but not Traversable? If not, what is the purpose of having a separate Foldable class? Thanks, Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Non-traversable foldables

2009-10-09 Thread Martijn van Steenbergen
Ross Paterson wrote: On Fri, Oct 09, 2009 at 04:41:05PM +0200, Martijn van Steenbergen wrote: Can anyone think of datatypes that are Foldable but not Traversable? Set Nice! Thank you all for your answers. Martijn. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] CBN, CBV, Lazy in the same final tagless framework

2009-10-09 Thread Martijn van Steenbergen
Felipe Lessa wrote: which unfortunately needs {-# LANGUAGE RecursiveDo #-} or some ugliness from mfix But mdo/mfix is awesome! :-( Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Parsec bug, or...?

2009-10-13 Thread Martijn van Steenbergen
Brandon S. Allbery KF8NH wrote: My fix would be to have myPrefixOf require the prefix be terminated in whatever way is appropriate (end of input, white space, operator?) instead of simply accepting as soon as it gets a prefix match regardless of what follows. Maybe you can use notFollowedBy

Re: [Haskell-cafe] MTL vs Transformers?

2009-10-13 Thread Martijn van Steenbergen
Erik de Castro Lopo wrote: However after reading the hackage descriptions of both Transformers and MTL, it seems that they share a very similar heritage. I therefore hacked the iteratee.cabal file and replaced the build-depends on transformers with one on mtl and the package built quite happily.

[Haskell-cafe] Monotype error

2009-10-14 Thread Martijn van Steenbergen
Dear café, {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ImpredicativeTypes #-} type Void = forall a. a newtype Mono a = Mono { runMono :: [Void] } beep :: Mono a - Mono a beep (Mono vs) = Mono (map undefined vs) Compiling this with GHC results in: Monotype.hs:9:28: Cannot match a

[Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
Hello café, I've never written an Alternative instance for a newtype yet that doesn't look like this: instance Alternative T where empty = T empty T x | T y = T (x | y) Why does newtype deriving not work for Alternative? (It works fine for Monoid.) Thanks, Martijn.

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
You guys are right. I was being silly. Thanks. :-) Ryan Ingram wrote: Works for me on GHC6.10.4: ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen
It doesn't work for this one: newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]} But my handwritten instance remains identical. Groetjes, Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] GHC devs

2009-10-16 Thread Martijn van Steenbergen
David Virebayre wrote: Taking the opportunity to thank very much both Simons and Ian for the work they do and the enthusiasm they show. You guys rock. I heartily second that! Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Test cases for type inference

2009-10-21 Thread Martijn van Steenbergen
Peter Verswyvelen wrote: For learning, I would like to develop my own implementation of type inference, based on the paper Typing Haskell in Haskell. At first sight, the source code of THIH contains a small number of tests, but I was wandering if a large test set exist? I'm pretty sure GHC

[Haskell-cafe] What's this pattern called?

2009-10-22 Thread Martijn van Steenbergen
Bonjour café, data ExprF r = Add r r | Sub r r | Mul r r | Div r r | Num Int This is a well-known pattern that for example allows nice notation of morphisms. But what is it called? I've heard fixed-point view, open datatypes and some others, but I'm curious where

Re: [Haskell-cafe] Is there in Haskell the eval function?

2009-10-22 Thread Martijn van Steenbergen
Waldemar Biernacki wrote: Is there the eval function like in imperative languages? You mean like in interpreted languages? I'd like to write an application which has to be compiled to exec file. It is neccessary to performe some additional procedures which are unknown at the moment of the

Re: [Haskell-cafe] why cannot i get the value of a IORef variable ?

2009-10-23 Thread Martijn van Steenbergen
Anton van Straaten wrote: On the plus side, this does make for a slogan with high market appeal: Haskell: Kittens inside Thanks. Now I have trouble getting this image of lambda-shaped bonsai kittens out of my head. ;-) Martijn. ___

Re: [Haskell-cafe] What's this pattern called?

2009-10-23 Thread Martijn van Steenbergen
Thanks for all the pointers, guys. You've been very helpful. I also found Type-indexed data types (Hinze et al) to be a good source. Much appreciated! Martijn. Martijn van Steenbergen wrote: data ExprF r ___ Haskell-Cafe mailing list Haskell

Re: [Haskell-cafe] Re: ANN: haskell-src-exts-1.2.0

2009-10-23 Thread Martijn van Steenbergen
Niklas Broberg wrote: Actually, it seems something went awry. I got a 500 Internal Server Error on my cabal upload, the package is there on hackage but it seems it was never added to the list of packages. This means cabal update doesn't know about it, nor is it listed on the What's New page.

[Haskell-cafe] ANN: HoleyMonoid-0.1

2009-10-26 Thread Martijn van Steenbergen
Hello! I'm happy to announce the first release of HoleyMonoid, a datatype that helps you build monoids with holes in them. The holes are filled in later using normal function application. For example: let holey = now x = . later show . now , y = .

Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2009-10-30 Thread Martijn van Steenbergen
Magnus Therning wrote: IIRC James Gosling once said that if he were to design Java today he would leave out classes. I suppose partly due to many of the issues with data inheritance. This sounds interesting. Can you link us to an article, please? Thanks, Martijn.

Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread Martijn van Steenbergen
Yusaku Hashimoto wrote: Hello cafe, Do you know any data-type which is Applicative but not Monad? The Except datatype defined in the Applicative paper. Some parsers are not monads, allowing for optimizations. Martijn. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] uu-parsinglib pKeyword

2009-10-30 Thread Martijn van Steenbergen
Hi Ozgur, Ozgur Akgun wrote: pKeyword_Int = ( \ _ _ _ - int ) $ pSym 'i' * pSym 'n' * pSym 't' pKeyword_Float = ( \ _ _ _ _ _ - float ) $ pSym 'f' * pSym 'l' * pSym 'o' * pSym 'a' * pSym 't' As you can see there is an obvious pattern if you try to capture a keyword. If there were a function

[Haskell-cafe] Fair diagonals

2009-11-03 Thread Martijn van Steenbergen
Dear café, I am looking for a function that does an N-dimensional diagonal traversal. I want the traversal to be fair: the sum of the indices of the produced combinations should be non-decreasing. Let me illustrate with an example. The type of a 2-dimensional traversal would look like this:

[Haskell-cafe] Re: Fair diagonals

2009-11-04 Thread Martijn van Steenbergen
Louis Wasserman wrote: +1 on Control.Monad.Omega. In point of fact, your diagN function is simply diagN = runOmega . mapM Omega You'll find it an interesting exercise to grok the source of Control.Monad.Omega, obviously, but essentially, you're replacing concatMap with a fair (diagonal)

Re: [Haskell-cafe] Fair diagonals

2009-11-06 Thread Martijn van Steenbergen
Henning Thielemann wrote: On Wed, 4 Nov 2009, Sjoerd Visscher wrote: On Nov 4, 2009, at 3:21 PM, Twan van Laarhoven wrote: I looked on hackage but I was surprised that I couldn't find this simple monad. The package level-monad does look very similar, only it uses a

Re: [Haskell-cafe] Working with multiple projects

2009-11-11 Thread Martijn van Steenbergen
Tony Morris wrote: I have two projects that I intend to put on hackage soon. One depends on the other. I have cabaled both. I am wondering how others work with this kind of set up where changes are made to both libraries as they work. You just update and re-upload the packages as necessary. It

[Haskell-cafe] Kind polymorphism

2009-11-23 Thread Martijn van Steenbergen
Hello, Are there currently any known problems that would hinder the implementation of kind polymorphism [1], e.g. unresolved inelegancies or technical limitations, or is it only a matter of finding the time to implement it? Thanks, Martijn. [1]

Re: [Haskell-cafe] Pointfree rank-2 typed function

2009-11-24 Thread Martijn van Steenbergen
Simon Peyton-Jones wrote: It used to be, because GHC used to implement so-called deep skolemisation. See Section 4.6.2 of http://research.microsoft.com/en-us/um/people/simonpj/papers/higher-rank/putting.pdf Deep skolemisation was an unfortunate casualty of the push to add impredicative

[Haskell-cafe] Type synonym family inside type class

2009-11-27 Thread Martijn van Steenbergen
Hello, I have a type family and a type class: type family ErrorAlg (f :: (* - *) - * - *) e ix :: * class MkErrorAlg f where mkErrorAlg :: ErrorAlg f e a - f (K0 a) ix - Either e a Instances for these two really go hand in hand, so I thought I would move the type family into the type

Re: [Haskell-cafe] namespaces for values, types, and classes

2009-11-27 Thread Martijn van Steenbergen
Sebastian Fischer wrote: Does anyone know why types and values are in separate namespaces but classes and types are not? Good question. I don't know the answer, but it is interesting to note that the report explicitly mentions this decision (but provides no reason): An identifier must not

Re: [Haskell-cafe] I really donot know how to use `newtype` ?

2009-11-27 Thread Martijn van Steenbergen
zaxis wrote: then how to use `X` ? Would you mind explaining the newtype X in detail ? You can just think of a newtype as a normal datatype: data X a = X (ReaderT XConf (StateT XState IO) a) I.e. construction and pattern matching work indentically. Every newtype you will find will have

Re: [Haskell-cafe] Type synonym family inside type class

2009-11-27 Thread Martijn van Steenbergen
Hi Sean, Sean Leather wrote: Perhaps this isn't answering your question, but you can turn the above into an associated type as follows. class MkErrorAlg f where type ErrorAlg (f :: (* - *) - * - *) :: * - * - * mkErrorAlg :: ErrorAlg f e a - f (K0 a) ix - Either e a That is

[Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Martijn van Steenbergen
So here's a totally wild idea Sjoerd and I came up with. What if newtypes were unwrapped implicitly? What advantages and disadvantages would it have? In what cases would this lead to ambiguous code? Thanks, Martijn. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Finding HP

2009-12-04 Thread Martijn van Steenbergen
Don Stewart wrote: vandijk.roel: On Wed, Dec 2, 2009 at 11:44 PM, Gregory Crosswhite gcr...@phys.washington.edu wrote: On a more serious note, Download Haskell /= Download Haskell Platform, so if I were glancing down the sidebar looking for a link to download the Haskell Platform then the

Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Martijn van Steenbergen
Luke Palmer wrote: On Fri, Dec 4, 2009 at 10:26 AM, Radek Micek radek.mi...@gmail.com wrote: Hello. I have two types for expression: data Expr = Add Expr Expr | Mul Expr Expr | Const Int data AExpr = AAdd AExpr AExpr | AConst Int The first one supports addition and multiplication and the

Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Martijn van Steenbergen
Hi Radek, Radek Micek wrote: I can write a function to simplify the first expression: simplify :: Expr - Expr simplify = {- replaces: a*1 and 1*a by a, a+0 and 0+a by a -} And I would like to use the function simplify for the second type AExpr. What can I do is to convert AExpr to Expr,

Re: [Haskell-cafe] Re: From function over expression (+, *) derive function over expression (+)

2009-12-05 Thread Martijn van Steenbergen
Radek Micek wrote: Hi, thank you for your reply but your MulExpr does not support expressions like (2*3)+5 Oh! You're right, how silly of me. Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-05 Thread Martijn van Steenbergen
Eugene Kirpichov wrote: Hello. Consider the type: (forall a . a) - String. On one hand, it is rank-2 polymorphic, because it abstracts over a rank-1 polymorphic type. On the other hand, it is monomorphic because it isn't actually quantified itself: in my intuitive view, a parametrically

Re: [Haskell-cafe] Children elements with HXT

2009-12-23 Thread Martijn van Steenbergen
Max Cantor wrote: That stuffed me up for a bit. I wrote some ugly template haskell a while back to automatically generate XmlPickler instances. can send to you if you want I recall typLAB writing about generic XML picklers: http://blog.typlab.com/2009/11/writing-a-generic-xml-pickler/

[Haskell-cafe] suffix or operands invalid for `push'

2009-12-29 Thread Martijn van Steenbergen
Hello, Above error is one of those that appear when using GHC on the 64-bit Snow Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32 -opta-m32 -optl-m32. However, the error still occurs when doing 'cabal haddock' in *some* packages. For example, a local project of mine builds

Re: [Haskell-cafe] suffix or operands invalid for `push'

2009-12-29 Thread Martijn van Steenbergen
Gregory Collins wrote: Martijn van Steenbergen mart...@van.steenbergen.nl writes: Hello, Above error is one of those that appear when using GHC on the 64-bit Snow Leopard. I've already patched my /usr/bin/ghc to mention -optc-m32 -opta-m32 -optl-m32. However, the error still occurs when doing

Re: [Haskell-cafe] mtl and transformers

2010-01-11 Thread Martijn van Steenbergen
Günther Schmidt wrote: Hi, when I cabal-installed the iteratee package, the transformers package was also installed as a dependency. Now when I run applications that import Control.Monad.Transformers I get this: Could not find module `Control.Monad.Trans': it was found in

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Martijn van Steenbergen
Niklas Broberg wrote: Haskell '98 apparently features 25 reserved words. (Not counting forall and mdo and so on, which AFAIK are not in Haskell '98.) 21 actually. case, class, data, default, deriving, do, else, if, import, in, infix, infixl, infixr, instance, let, module, newtype, of, then,

[Haskell-cafe] Visualizing function application

2010-01-15 Thread Martijn van Steenbergen
Dear café, I am deeply impressed with Vacuum[1][2], Ubigraph[3] and especially their combination[4]. I can trivially and beautifully visualize the ASTs that my parser produces. I can visualize zippers of the ASTs and confirm that sharing is optimal. Ubigraph is also able to animate graph

Re: [Haskell-cafe] Re: Declarative binary protocols

2010-01-19 Thread Martijn van Steenbergen
Antoine Latter wrote: getResponse = do require 256 x - getX len - getWord16be y - getY z - getZ require (fromIntegral len * 8) a - getA b - getB return $ Response x y z a b c This looks like code that could be written in applicative style, in which case you could analyze the

Re: [Haskell-cafe] functional references and HList?

2010-02-04 Thread Martijn van Steenbergen
Edward Kmett wrote: Functional references let you both read and write 'attributes' in a structure. These can be chained to access members of members. You can also use them to build bidirectional views on fields (and compose those again as well). Martijn.

Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread Martijn van Steenbergen
Ryan Ingram wrote: Unfortunately, this makes things like infinite_xs - sequence (repeat arbitrary) no longer work, since the state never comes out the other side. You're asking to execute an infinite number of monadic actions. How can this ever terminate at all? Martijn.

Re: [Haskell-cafe] Notes on migrating from uvector to vector

2010-02-16 Thread Martijn van Steenbergen
Ivan Miljenovic wrote: On 16 February 2010 08:35, Don Stewart d...@galois.com wrote: Enjoy the new decade of flexible, fusible, fast arrays for Haskell! /me points out that 2010 is actually the last year of the decade, and not the first year of a new decade... There certainly is /a/ decade

Re: [Haskell-cafe] Unused import warnings.

2010-08-10 Thread Martijn van Steenbergen
Are you saying that GHC complains about an unused import that is in fact used? Perhaps you've run into this bug: http://hackage.haskell.org/trac/ghc/ticket/1148 Are you using a recent version of GHC? Groetjes, Martijn. On 8/10/10 22:22, Lyndon Maydwell wrote: Hi Cafe. I have written some

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen
On 8/2/10 7:09, Ertugrul Soeylemez wrote: Given the definition of a Haskell function, Haskell is a pure language. The notion of a function in other languages is not: int randomNumber(); The result of this function is an integer. You can't replace the function call by its result without

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen
On 8/10/10 23:27, Felipe Lessa wrote: If we had in C: return (randomNumber(10, 15) + randomNumber(10, 15)) That would not be the same as: int x = randomNumber(10, 15) return (x + x) That's not fair. You're comparing C's '=' with Haskell's '='. But you should be comparing C's '='

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-10 Thread Martijn van Steenbergen
On 8/10/10 23:53, Felipe Lessa wrote: and the result is IO Int. When we replace the function call by its result, I think it is fair to replace the C function call by an int and the Haskell function call by an IO Int, because that is what those functions return. Fair enough. :-) Also, a

[Haskell-cafe] Re: [Hackathon] BelHac: A Hackaton in Belgium, 5-7 November

2010-09-27 Thread Martijn van Steenbergen
I have just booked 5 beds in Hostel 47 in Ghent for our group. We will be staying in a 6-bed room, so there is still one bed available. If anyone is still looking for a bed in Ghent and wants to share a room with fellow Haskellers, that one bed might be an interesting choice. I told them we

Re: [Haskell-cafe] trouble with HDBC-mysql on Mac OS X

2010-11-21 Thread Martijn van Steenbergen
Hi Mark, Chris, I had trouble as well but just found this pretty recent blog post by @freels which worked like a charm for me: http://matt.freels.name/2010/hdbc-mysql-os-x.html I hope it works for you as well! I've added Chris to the list of recipients because maybe he can incorporate the fix

[Haskell-cafe] Why does cabal unnecessarily reinstall dependencies?

2010-11-22 Thread Martijn van Steenbergen
Hello cafe, When I want to locally install my own package through cabal install it tries to reinstall dependencies convertible-1.0.9.1, HDBC-2.2.6.1 and HDBC-mysql-0.6.3 even though they are already installed (and work fine). Why does it do this? cabal-install version 0.8.2 using version

[Haskell-cafe] Build problems with HDBC-mysql on the Mac

2010-11-22 Thread Martijn van Steenbergen
Dear cafe, Following the instructions at http://matt.freels.name/2010/hdbc-mysql-os-x.html I successfully installed HDBC-mysql on my Mac! However when doing a cabal install in a local package which depends on HDBC-mysql, cabal proceeds to reinstall HDBC-mysql (is this a bug? see my other

Re: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-19 Thread Martijn van Steenbergen
Thomas Davie wrote: I've found user installs don't work at all on OS X, various people in #haskell were rather surprised to discover this, so apparently it's not the default behavior on other platforms. It really rather makes cabal install rather odd – because it doesn't actually install

Re: [Haskell-cafe] ANNOUNCE: Runge-Kutta library -- solve ODEs

2009-04-19 Thread Martijn van Steenbergen
Hi Uwe, Uwe Hollerbach wrote: I have so far only tested it with ghc 6.8.3 on MacOS 10.3.9 (powerPC), but I know of no reason why it wouldn't work with other versions and OSs. It works fine on 6.10.1 on Leopard Intel as well. I'm afraid I haven't messed with cabal much yet, so it's not

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-20 Thread Martijn van Steenbergen
David Leimbach wrote: Just refuse to use UHC until it conforms. One can refuse to use GHC libraries that use extensions as well for similar reasons. I always think twice when I see something that isn't Haskell 98 in my stack. Do you not use Hugs for the same reason?

Re: [Haskell-cafe] Comments from two weeks of using Leksah

2009-04-21 Thread Martijn van Steenbergen
Jeff Heard wrote: First of all, it's crashed only once, and the error was an actual segfault, so I'm not sure what went wrong there. All in all, I like the eyecandy and have left it on for everything I do, but I've noticed that arrows have an extra space after them, no matter which arrow. Also,

Re: [Haskell-cafe] ANN: list-tries-0.0 - first release

2009-04-21 Thread Martijn van Steenbergen
Matti Niemenmaa wrote: In order to run properly, list-tries needs a version of 'containers' that hasn't yet been released. I incorporated a little hack which makes it compile even with 0.2, but some calls will fail by calling 'error': 30 of my 1014 test cases do so. 1014 test cases?! Wow. :-)

[Haskell-cafe] Hac5 roundup

2009-04-23 Thread Martijn van Steenbergen
Dear Haskell Hackers, Many thanks to all those who attended Hac5! We had a spectacular number of participants: over 50 hackers showed up, representing several countries. Many thanks also to the organising committee and sponsors! Those bagels on Sunday were delicious. :-) Please check out

Re: [Haskell-cafe] GADT on the wiki: I'm lost

2009-04-23 Thread Martijn van Steenbergen
Hoi Peter, Peter Verswyvelen wrote: Sure I understand what a GADT is, but I'm looking for practical examples, and the ones on the wiki seem to show what you *cannot* do with them... I use GADTs for two things: 1) Type witnesses for families of data types. An example from the MultiRec

Re: [Haskell-cafe] Dynamically altering sort order

2009-04-24 Thread Martijn van Steenbergen
Hi Denis, Denis Bueno wrote: where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas? Here's a solution that is more symmetrical but not necessarily prettier: newtype Wrap =

Re: [Haskell-cafe] Dynamically altering sort order

2009-04-24 Thread Martijn van Steenbergen
Denis Bueno wrote: The problem here is that the order is fixed. Statically. I can't change it at runtime based on flags. (Right? Unless I'm missing something) That is right. It might or might not be a problem in your specific case. sortBy :: (a - a - Ord) - [a] - IO [a] sortBy cmp =

Re: [Haskell-cafe] Re: Converting IO [XmlTree] to [XmlTree]

2009-04-27 Thread Martijn van Steenbergen
Tillmann Rendel wrote: Achim Schneider wrote: In other words: 1) Explain Pointed 2) Explain Functor 3) Explain Applicative 4) Explain Monad Why Pointed first? Functor seems more useful and more basic. They are in order of power: every monad is an applicative; every applicative is a

Re: [Haskell-cafe] Can subclass override its super-class' default implementation of a function?

2009-04-27 Thread Martijn van Steenbergen
siki wrote: I'm not sure if this is possible at all. I'd like to do something like this: class A a where foo :: a - Double foo a = 5.0 class (A a) = B a where foo a = 7.0 This is currently not possible in Haskell. It's been proposed, though:

Re: [Haskell-cafe] Re: Converting IO [XmlTree] to [XmlTree]

2009-04-28 Thread Martijn van Steenbergen
Steffen Schuldenzucker wrote: Uhm, isn't it: class (Functor f) = Pointed f where pure :: a - f a -- singleton, return, unit etc. Got it from: The Typeclassopedia by Brent Yorgey (forgot the URL, sorry) Yes, but also: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/54685 So maybe

Re: [Haskell-cafe] gcd

2009-05-02 Thread Martijn van Steenbergen
Hi Steve, Steve wrote: Why is gcd 0 0 undefined? That's a good question. Can you submit an official proposal? http://www.haskell.org/haskellwiki/Library_submissions Thanks, Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Martijn van Steenbergen
Hi Nicolas, Nicolas Martyanoff wrote: So now I'd want to use it for a small project of mine, a simple multiplayer roguelike based on telnet. I wrote a minimal server in C, and it took me a few hours. Now I'm thinking about doing the same in Haskell, and I'm in trouble. I don't know if this is

Re: [Haskell-cafe] Getting WriterT log lazily

2009-05-04 Thread Martijn van Steenbergen
Magnus Therning wrote: Without the `seq` the call to sleep will simply be skipped (is there an easier way to force evaluation there?). Without `unsafePerformIO` all the sleeping is done up front, and all numbers are print at once at the end. The goal is of course to use code along the same

Re: [Haskell-cafe] Foldable for BNFC generated tree

2009-05-04 Thread Martijn van Steenbergen
Hi Deniz, Deniz Dogan wrote: So, basically I'd like some sort of folding functionality for these data types, without having to hack the lexer/parser myself (parameterising the data types), because as I said they're being generated by BNFC. What exactly do you mean by folding functionality?

[Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Martijn van Steenbergen
Hello, Mr. McBride and mr. Paterson define in their Applicative paper: data Except e a = OK a | Failed e instance Monoid e = Applicative (Except e) where ... Sometimes I'd still like to use = on Excepts but this feels wrong somehow, because it doesn't use monoids nicely like the Applicative

Re: [Haskell-cafe] Interesting Thread on OO Usefulness (scala mailing list)

2009-05-04 Thread Martijn van Steenbergen
Andrew Wagner wrote: [quote] Here's [a]language to to interpret (where postfix * means tupling): Variables: x Integer literals: i Terms: t = Lambda x*. t | Apply t t* | Var(x) | Num(i) Can someone explain to me how I should read this? It supposedly explains what the postfix

Re: [Haskell-cafe] Parsec - Custom Fail

2009-05-05 Thread Martijn van Steenbergen
mwin...@brocku.ca wrote: Hi, I am using parsec to parse a small programming language. The language is typed and I need to do some type checking, too. I have decided to do the parsing and type checking simultaneously in the my parsec parser. This approach avoids to keep source code positions

Re: [Haskell-cafe] Writing a compiler in Hakell

2009-05-06 Thread Martijn van Steenbergen
Rouan van Dalen wrote: Hi everyone. I am designing my own programming language. I would like to know what is the best way to go about writing my compiler in haskell. What are the tools available in haskell that can help with compiler construction? I know about Happy. Is that a good tool to

Re: [Haskell-cafe] List comprehension

2009-05-06 Thread Martijn van Steenbergen
por...@porg.es wrote: -- or with Data.Function.Predicate (shameless plug) http://hackage.haskell.org/packages/archive/predicates/0.1/doc/html/Data-Function-Predicate.html: Whoa, a function called isn't, why is this the first time I see that? :-) Martijn.

[Haskell-cafe] A small puzzle: inTwain as function of foldr

2009-06-04 Thread Martijn van Steenbergen
Bonjour café, A small puzzle: Consider the function inTwain that splits a list of even length evenly into two sublists: inTwain Hello world! (Hello ,world!) Is it possible to implement inTwain such that the recursion is done by one of the standard list folds? Is there a general way to

[Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread Martijn van Steenbergen
Hello, Suppose I have two projects: 1) one that defines a monad transformer and an accompanying type class that captures my monad-specific operations and 2) one that uses the other project, combining the monad transformer with, say, Parsec. Now while writing my Parsec parser I want to use

Re: [Haskell-cafe] Record initialise question

2009-06-05 Thread Martijn van Steenbergen
Hi John, John Ky wrote: full = do let myOrder = init -- [1] { item = Just init { itemId = Something } , operation = Just Buy } putStrLn $ show myOrder return () Where initOrder and initItem

Re: [Haskell-cafe] A small puzzle: inTwain as function of foldr

2009-06-05 Thread Martijn van Steenbergen
Thomas ten Cate wrote: Possible, yes. Efficient, not really. inTwain = foldr (\x (ls, rs) - if length ls == length rs then (x:ls, rs) else (x:(init ls), (last ls):rs)) ([], []) But this uses length and init and last all of which are recursive functions. I consider that cheating: only

Re: [Haskell-cafe] A small puzzle: inTwain as function of foldr

2009-06-05 Thread Martijn van Steenbergen
Geoffrey Marchant wrote: The linked paper appears to show the right style. This appears to satisfy the conditions, however: inTwain as = let (x,y,_) = foldr (\a (r,s,t) - case (t) of {b:(b':bs) - (r,a:s,bs); _ - (a:r,s,t)}) ([],[],as) as in (x,y) This one is very interesting. Thanks. :-) It

  1   2   3   >