Re: [Haskell-cafe] monadic DSL for compile-time parser generator, not possible?

2013-03-13 Thread Josef Svenningsson
Jeremy, The problem you're trying to solve might seem tricky but it is in fact quite solvable. In Feldspar[1] we use monads quite frequently and generate code from them, in a similar fashion to what you're trying to do. We've written a paper about how we do it[2] that I welcome you to read. If

[Haskell-cafe] Problems with code blocks in the description field in a .cabal file

2013-02-04 Thread Josef Svenningsson
Hi, I'm putting together a cabal package and I'd like to have some code examples in my description file. In particular I would like to have a code block containing markdown containing a code block of Haskell, like this: ~~~{ .haskell } module Main where main = putStrLn Hello World! ~~~

Re: [Haskell-cafe] Problems with code blocks in the description field in a .cabal file

2013-02-04 Thread Josef Svenningsson
://hackage.haskell.org/packages/archive/shpider/0.2.1.1/doc/html/Network-Shpider.html On 04/02/13 12:30, Josef Svenningsson wrote: Hi, I'm putting together a cabal package and I'd like to have some code examples in my description file. In particular I would like to have a code block

Re: [Haskell-cafe] Problems with code blocks in the description field in a .cabal file

2013-02-04 Thread Josef Svenningsson
should be fine if you follow Haddock formatting. For example: http://hackage.haskell.org/package/lens Is from the cabal file: http://hackage.haskell.org/packages/archive/lens/3.8.5/lens.cabal Ryan On Mon, Feb 4, 2013 at 7:30 AM, Josef Svenningsson josef.svennings...@gmail.com wrote: Hi

Re: [Haskell-cafe] Problems with code blocks in the description field in a .cabal file

2013-02-04 Thread Josef Svenningsson
documentation for now. Thank you very much! Josef Ryan On Mon, Feb 4, 2013 at 8:37 AM, Josef Svenningsson josef.svennings...@gmail.com wrote: Hi Ryan, As far as I can tell I'm following the Haddock formatting just fine. I'm using bird tracks for my code block and according to the Haddock

Re: [Haskell-cafe] smt solver bindings

2011-12-15 Thread Josef Svenningsson
On Thu, Dec 15, 2011 at 7:04 PM, Dimitrios Vytiniotis dimit...@microsoft.com wrote: I've a quick question: Are there Haskell wrappers for the Z3 C API around? I believe sbv recently got support for Z3 but I don't know if it uses the C API. Neither have I tried the Z3 backend, I only played

[Haskell-cafe] Mysterious complaint about .hi files

2011-06-07 Thread Josef Svenningsson
Hi cafe! I'm hitting a very strange problem when using haskell-src-exts and haskell-src-exts-qq. Consider the following module: \begin{code} {-# Language QuasiQuotes #-} module TestBug where import Language.Haskell.Exts import Language.Haskell.Exts.QQ unit = TyTuple Boxed [] ty = [dec| quux

Re: [Haskell-cafe] Wanted: composoable parsers from haskell-src-exts

2011-03-18 Thread Josef Svenningsson
On Thu, Mar 17, 2011 at 10:58 PM, Niklas Broberg niklas.brob...@gmail.comwrote: I already export a partial parser for top-of-file pragmas, I see. What I don't see is how such a parser would return the rest of input. Hmm. I see. And I see that you are correct in not seeing it, since it

Re: [Haskell-cafe] Safer common subexpression elimination

2010-11-26 Thread Josef Svenningsson
On Thu, Nov 25, 2010 at 11:32 AM, Joachim Breitner m...@joachim-breitner.de wrote: Hi, although semantically it could, ghc does not do common subexpression elimination (CSE), at least not in every case. The canonical example where it would be bad is the function (with div to avoid numerical

Re: [Haskell-cafe] Compiling a DSL on the shoulders of GHC

2010-10-18 Thread Josef Svenningsson
Fiddling with GHC internals sounds like overkill for this project. Are you really sure you need a timeout to run the Haskell metaprogram? There are many implementations of EDSLs which take the approach that you want to take by using Haskell to create a syntax tree and the offshore it to some

Re: [Haskell-cafe] Higher-order algorithms

2010-08-24 Thread Josef Svenningsson
On Mon, Aug 23, 2010 at 6:10 PM, Max Rabkin max.rab...@gmail.com wrote: (Accidentally sent off-list, resending) On Mon, Aug 23, 2010 at 15:03, Eugene Kirpichov ekirpic...@gmail.com wrote: * Difference lists I mean that not only higher-order facilities are used, but the essence of the

Re: [Haskell-cafe] feasability of implementing an awk interpreter.

2010-08-20 Thread Josef Svenningsson
On Fri, Aug 20, 2010 at 6:05 AM, Jason Dagit da...@codersbase.com wrote: On Thu, Aug 19, 2010 at 8:05 PM, Michael Litchard mich...@schmong.orgwrote: I'd like the community to give me feedback on the difficulty level of implementing an awk interpreter. What language features would be

Re: [Haskell-cafe] derivable type classes

2010-03-23 Thread Josef Svenningsson
On Tue, Mar 23, 2010 at 11:52 AM, Ozgur Akgun ozgurak...@gmail.com wrote: Can a user define a derivable type class of her own? If yes, how? GHC has a feature which lets you define classes such that making an instance of them is as easy as deriving. It's called Generic classes. See GHC's

Re: [Haskell-cafe] ** for nested applicative functors?

2009-10-12 Thread Josef Svenningsson
On Mon, Oct 12, 2009 at 6:22 PM, Kim-Ee Yeoh a.biurvo...@asuhan.com wrote: Does anyone know if it's possible to write the following: ** :: (Applicative m, Applicative n) = m (n (a-b)) - m (n a) - m (n b) Clearly, if m and n were monads, it would be trivial. Rereading the original paper, I

Re: [Haskell-cafe] types and braces

2009-04-17 Thread Josef Svenningsson
Conor, I'd like to point out a few things that may help you on the way. On Wed, Apr 15, 2009 at 8:58 PM, Conor McBride co...@strictlypositive.org wrote: I don't immediately see what the clash in that context would be - I *think* what you propose should be doable. I'd be interested to know

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Josef Svenningsson
On Mon, Feb 16, 2009 at 2:30 AM, wren ng thornton w...@freegeek.org wrote: Louis Wasserman wrote: I follow. The primary issue, I'm sort of wildly inferring, is that use of STT -- despite being pretty much a State monad on the inside -- allows access to things like mutable references?

Re: [Haskell-cafe] Haskell project proposals reddit

2008-12-10 Thread Josef Svenningsson
On Wed, Dec 10, 2008 at 5:34 AM, Don Stewart [EMAIL PROTECTED] wrote: I'd like to echo Jason's remarks earlier. http://www.reddit.com/r/haskell_proposals/ We've tried for a couple of years now to efficiently track 'wanted libraries' for the community, but never with much success. In

Re: [Haskell-cafe] Philip Wadler video on Howard-Curry Correspondence ???

2008-11-27 Thread Josef Svenningsson
2008/11/27 Galchin, Vasili [EMAIL PROTECTED]: Hello, I am reading re-reading Prof. Wadler paper Proofs are Programs: 19th Century Logic and 21st Century Computing but also want to re-read watch his video on same subject. Is it this talk you're after?

Re: [Haskell-cafe] Compilers

2008-11-26 Thread Josef Svenningsson
On Wed, Nov 26, 2008 at 11:14 PM, David Menendez [EMAIL PROTECTED] wrote: How old is nhc? I've always thought of it as one of the big three, but I don't really know how far back it goes compared to ghc. The following page suggests that it was released mid 1994 but there could of course have

Re: [Haskell-cafe] a really juvenile question .. hehehehe ;^)

2008-10-06 Thread Josef Svenningsson
On Mon, Oct 6, 2008 at 2:58 PM, Cale Gibbard [EMAIL PROTECTED] wrote: 2008/10/6 Don Stewart [EMAIL PROTECTED]: dagit: data and newtype vary in one more subtle way, and that's how/when they evaluate to bottom. Most of the time they behave identically, but in the right cases they act

Re: [Haskell-cafe] Re: Red-Blue Stack

2008-09-26 Thread Josef Svenningsson
On Fri, Sep 26, 2008 at 7:18 PM, Stephan Friedrichs [EMAIL PROTECTED] wrote: apfelmus wrote: [..] Persistent data structures are harder to come up with than ephemeral ones, [...] Yes, in some cases it's quite hard to find a persistent solution for a data structure that is rather trivial

Re: [Haskell-cafe] Re: Call Graph Tool?

2008-06-27 Thread Josef Svenningsson
On Fri, Jun 27, 2008 at 12:39 PM, Claus Reinke [EMAIL PROTECTED] wrote: Assuming I get it included, is there any features in particular you'd want to see in there? Note that if I do have it produce visualisations, they'll be static images as part of an analysis report rather than being

Re: [Haskell-cafe] Re: ghc on Ubuntu Linux?

2008-05-18 Thread Josef Svenningsson
be the cause of this. Hopefully someone with a bit more cabal knowledge can help out. Good luck, Josef On Sat, May 17, 2008 at 11:02 AM, Josef Svenningsson [EMAIL PROTECTED] wrote: On Sat, May 17, 2008 at 1:00 PM, Galchin, Vasili [EMAIL PROTECTED] wrote: Josef, E.g. [EMAIL PROTECTED

Re: [Haskell-cafe] Re: ghc on Ubuntu Linux?

2008-05-17 Thread Josef Svenningsson
Vasili, I have pretty much exactly the same set up as you seem to have. I haven't had a single problem with running configure using cabal. In what sense does it stop working? Cheers, Josef 2008/5/17 Galchin, Vasili [EMAIL PROTECTED]: PS I have always installed ghc first via the Ubuntu package

Re: [Haskell-cafe] STM example code

2008-03-17 Thread Josef Svenningsson
2008/3/9 Galchin Vasili [EMAIL PROTECTED]: I am playing around with the STM API. I would like to see examples of STM other than the Santa.hs as I am having problems with STM vs IO. Here's my implementation of the Dining Philosophers in STM:

Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Josef Svenningsson
On Feb 6, 2008 3:06 PM, Miguel Mitrofanov [EMAIL PROTECTED] wrote: On 6 Feb 2008, at 16:32, Peter Padawitz wrote: Can anybody give me a simple explanation why the second definition of a palindrome checker does not terminate, although the first one does? pal :: Eq a = [a] - Bool pal

Re: [Haskell-cafe] Missing join and split

2008-01-01 Thread Josef Svenningsson
On Dec 28, 2007 11:40 PM, Mitar [EMAIL PROTECTED] wrote: Would not it be interesting and useful (but not really efficient) to have patterns something like: foo :: Eq a = a - ... foo (_{4}'b') = ... which would match a list with four elements ending with an element 'b'. Or: foo

Re: [Haskell-cafe] Graph theory analysis of Haskell code

2007-12-06 Thread Josef Svenningsson
This sounds like a fun project and it is certainly feasible to do. I thought I'd give you some pointers to fun stuff that people have been doing in the past. Thomas Reps have been doing program analysis since the dawn of time, but one paper that seems particularly related to what you try to do is

Re: [Haskell-cafe] -O2 bug in GHC 6.8.1?

2007-11-20 Thread Josef Svenningsson
On Nov 20, 2007 4:32 PM, Ian Lynagh [EMAIL PROTECTED] wrote: Hi Brad, On Tue, Nov 20, 2007 at 09:50:02PM +1000, Brad Clow wrote: $ ./test 23 24 I can't reproduce this. Can you please tell us what platform you are on (e.g. x86_64 Linux) and what gcc --version says? Also, where did

Re: Re[2]: [Haskell-cafe] Fusing foldr's

2007-10-30 Thread Josef Svenningsson
On 10/29/07, Bulat Ziganshin [EMAIL PROTECTED] wrote: you may also look at these data: 1,225,416 bytes allocated in the heap 152,984 bytes copied during GC (scavenged) 8,448 bytes copied during GC (not scavenged) 86,808 bytes maximum residency (1 sample(s)) 3

Re: [Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-10-30 Thread Josef Svenningsson
On 10/30/07, Henning Thielemann [EMAIL PROTECTED] wrote: When following the description on http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck then darcs will run the QuickCheck tests on each 'darcs record', but the new patch is also

Re: [Haskell-cafe] Fusing foldr's

2007-10-29 Thread Josef Svenningsson
On 10/28/07, Isaac Dupree [EMAIL PROTECTED] wrote: Josef Svenningsson wrote: Less bogus timing: avg4: 18.0s avgS: 2.2s avgP: 17.4s OK, so these figures make an even stronger case for my conclusion :-) Single traversal can be much faster than multiple traversals *when done right

Re: [Haskell-cafe] Fusing foldr's

2007-10-29 Thread Josef Svenningsson
On 10/29/07, Josef Svenningsson [EMAIL PROTECTED] wrote: But using those flags yielded a very interesting result: avgP: 4.3s Superlinear speedup!? As you say, I would have expected something slightly larger than 9s. I think what happens here is that for avg4 the entire list has to be kept

Re: [Haskell-cafe] Fusing foldr's

2007-10-27 Thread Josef Svenningsson
On 10/26/07, Dan Weston [EMAIL PROTECTED] wrote: Thanks for letting me know about the Data.Strict library on Hackage. I will definitely make use of that! BTW, you left out an import Data.List(foldl') in your example. Yes, Data.Strict can be pretty handy for getting the right strictness. Sorry

Re: [Haskell-cafe] Fusing foldr's

2007-10-26 Thread Josef Svenningsson
Sorry for reacting so late on this mail. I'm digging through some old mails... On 10/12/07, Dan Weston [EMAIL PROTECTED] wrote: Always check optimizations to make sure they are not pessimizations! Actually, traversing the list twice is very cheap compared to space leakage, and accumulating

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Josef Svenningsson
On 10/24/07, Neil Mitchell [EMAIL PROTECTED] wrote: Hi Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal? No, though it is an interesting idea. You can get pretty close with existing Haskell though: (bin 100010011)

Re: [Haskell-cafe] Re: Mutable but boxed arrays?

2007-09-06 Thread Josef Svenningsson
On 9/6/07, Simon Marlow [EMAIL PROTECTED] wrote: Ketil Malde wrote: I, on the other hand, have always wondered why the strict arrays are called unboxed, rather than, well, strict? Strictness seems to be their observable property, while unboxing is just an (admittedly important)

Re: [Haskell-cafe] Small question

2007-08-10 Thread Josef Svenningsson
On 8/10/07, John Meacham [EMAIL PROTECTED] wrote: On Thu, Aug 09, 2007 at 06:37:32PM +0100, Andrew Coppin wrote: Which of these is likely to go faster? type Quad = (Bool,Bool) ... data Quad = BL | BR | TL | TR ... I'm hoping that the latter one will more more strict / use less space.

Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Josef Svenningsson
On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote: Neil Mitchell [EMAIL PROTECTED] wrote: I'm not convinced either, a nice concrete example would let people ponder this a bit more. I tried to provide something in my response to Simon. Here it is again: One could sugar: do tax -

Re: [Haskell-cafe] Polymorphic variants

2007-07-25 Thread Josef Svenningsson
On 7/26/07, Jon Harrop [EMAIL PROTECTED] wrote: Does Haskell have anything similar to OCaml's polymorphic variants? No as such, but it's possible to simulate them. As always Oleg was the one to demonstrate how: http://okmij.org/ftp/Haskell/generics.html Cheers, Josef

Re: [Haskell-cafe] Practical Haskell question.

2007-07-22 Thread Josef Svenningsson
Michael, I think what you're trying to do is perfectly doable in Haskell and I think the right tool for it is arrows, as Tomasz Zielonka mentioned before. I suggest you take a look at the following paper which uses arrows to enforce security levels in the code:

Re: [Haskell-cafe] reimplementing break (incorrectly) quickcheck p list gives me feedback that it breaks on list, but not what predicate test caused the breakage

2007-07-06 Thread Josef Svenningsson
On 7/6/07, Thomas Hartman [EMAIL PROTECTED] wrote: I am a total quickcheck noob. Is there a way to find out what predicate test function is, below? The trick that I know of to do that is to not generate a function in the first place, but a data type which can represent various functions of

Re: [Haskell-cafe] Abstraction leak

2007-07-01 Thread Josef Svenningsson
On 6/30/07, Jon Cast [EMAIL PROTECTED] wrote: On Friday 29 June 2007, Jon Cast wrote: Here's my solution (drawn from a library I'll be posting Real Soon Now): snip solution I forgot to point out that this is 75-90% drawn from a library called Fudgets[1], which is probably the most extended

Re: [Haskell-cafe] Functional Data Structures

2007-06-21 Thread Josef Svenningsson
On 6/21/07, Michael T. Richter [EMAIL PROTECTED] wrote: Is there a good book or web site outlining decent pure-lazy-functional data structures, with or without code samples? Chris Okasaki's publication page is a goldmine when it comes to functional data structures, lazy and otherwise.

Re: [Haskell-cafe] Higher order types via the Curry-Howard correspondence

2007-05-13 Thread Josef Svenningsson
I think both Benja's and David's answers are terrific. Let me just add a reference. The person who's given these issues most thought is probably Per Martin-Löf. If you want to know more about the meaning of local connectives you should read his On the Meanings of the Logical Constants and the

Re: [Haskell-cafe] Bloom Filter

2007-05-01 Thread Josef Svenningsson
Hi, Just a small comment on one of the comments. On 5/1/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Also, rather than this: add :: Bloom a - a - Bloom a a better argument order is this: insert :: a - Bloom a - Bloom a That way, you can use it with foldr. Hmmm. If you want to

Re: [Haskell-cafe] Is Template Haskell a suitable macro language?

2007-04-24 Thread Josef Svenningsson
On 4/24/07, Jacques Carette [EMAIL PROTECTED] wrote: In Ocaml, you can frequently use polymorphic variants to get the same effect. Which means that if you are willing to do enough type-class-hackery, it should, in principle, be possible to do the same in Haskell. But it sure isn't as

Re: [Haskell-cafe] Re: [C2hs] anyone interested in developing a Language.C library?

2007-04-21 Thread Josef Svenningsson
On 4/21/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: chak: Duncan Coutts wrote: If anyone is interested in developing a Language.C library, I've just completed a full C parser which we're using in c2hs. It covers all of C99 and all of the GNU C extensions that I have found used in

Re: [Haskell-cafe] First order Haskell without Data

2007-04-19 Thread Josef Svenningsson
Hi, Just a comment or two on the implications of converting higher-order functions to data. The paper you reference about this uses the method of defunctionalization. This is a whole program transformation and might therefore not be suitable in a compiler such as GHC or YHC. On the other hand,

Re: [Haskell-cafe] idea for avoiding temporaries

2007-03-09 Thread Josef Svenningsson
On 3/8/07, John Meacham [EMAIL PROTECTED] wrote: it seems we can almost do this now without adding any new API calls, just have 'thawArray' and 'freezeArray' perform the check, and behave like 'unsafeThawArray' or 'unsafeFreezeArray' when they are the only reference. The compiler may even be

Re: [Haskell-cafe] seq (was: Article review: Category Theory)

2007-01-19 Thread Josef Svenningsson
On 1/20/07, Brian Hulley [EMAIL PROTECTED] wrote: Neil Mitchell wrote: Hi Brian, Is there any solution that would allow excess laziness to be removed from a Haskell program such that Hask would be a category? class Seq a where seq :: a - b - b Then you have a different seq based on

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Josef Svenningsson
On 1/11/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Josef Svenningsson wrote: Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful. I wrote: Are those really needed

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Josef Svenningsson
Yitzchak, I agree with you that both lazy and strict monads are important and that we should have both options in a monad library. But the fun doesn't end there. There are other strictness properties to consider. Take the state monad for example. Should it be strict or lazy in the state that it

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Josef Svenningsson
On 1/10/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Hi Josef, Josef Svenningsson wrote: ...the fun doesn't end there. There are other strictness properties to consider. Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need

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

2006-09-19 Thread Josef Svenningsson
On 9/19/06, Jan-Willem Maessen [EMAIL PROTECTED] wrote: On Sep 18, 2006, at 4:47 AM, Einar Karttunen wrote: 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

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

2006-09-17 Thread Josef Svenningsson
On 9/17/06, Jan-Willem Maessen [EMAIL PROTECTED] wrote: On Sep 13, 2006, at 3:37 AM, 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,

Re: [Haskell-cafe] Variants of a recursive data structure

2006-08-03 Thread Josef Svenningsson
Klaus, You've gotten many fine answers to your question. I have yet another one which is believe is closest to what you had in mind. The key to the solution is to add an extra type parameter to Labelled like so: data Labelled f a = L String (f a) Now you can use it to form new recursive type

Re: [Haskell-cafe] Code review: efficiency question

2006-05-03 Thread Josef Svenningsson
Brian, You might also want to take a look at the list fusion functionality in GHC which often can help optimize your programs when programming with lists. http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.html#id3153234 It doesn't help in your particular program but it might

Re: [Haskell-cafe] show for functional types

2006-04-05 Thread Josef Svenningsson
On 4/5/06, Robert Dockins [EMAIL PROTECTED] wrote: Hey, if we wanted a private conversation, we'd take it off-list. :-) :-) Do you have any reference to the fact that there is any diagreement about the term? I know it has been used sloppily at times but I think it is pretty well defined.

Re: [Haskell-cafe] multiple computations, same input

2006-03-27 Thread Josef Svenningsson
On 3/28/06, Neil Mitchell [EMAIL PROTECTED] wrote: This feels like a situation Parsec users would find themselves in all the time. When you have a bunch of parsers in a 'choice', does the start of the input stream linger until the last parser is executed? No, as soon as one token is

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

2006-03-18 Thread Josef Svenningsson
Sorry for the slow reply,On 3/8/06, Einar Karttunen ekarttun@cs.helsinki.fi wrote: Does anyone have an efficient tree implemented in STM thatsupports concurrent updates in an efficient fashion? Thisseems suprisingly hard to implement - a normal binarytree with links as TVar is very slow and does

Re: [Haskell-cafe] Expanding do notation

2006-01-07 Thread Josef Svenningsson
On 1/7/06, Chris Kuklewicz [EMAIL PROTECTED] wrote: When you put print (head p) at then end, it keeps a reference to thewhole list p which is your space leak.If you want to store the headof p, this *should* work: main = do n - getArgs = return . read . head let p = permutations [1..n] headOfP -

Re: [Haskell-cafe] Papers from the 2005 Haskell Workshop (Tallinn)?

2005-10-11 Thread Josef Svenningsson
On 10/12/05, John Meacham [EMAIL PROTECTED] wrote: I certainly think we should somehow centralize an index to papers onhaskell. I have found it extremely difficult to track down papers forauthors that have since moved out of academia or have passed on anddon't have their personal homepages with

Re: [Haskell-cafe] A Tool To Show Functions Relationship?

2005-06-09 Thread Josef Svenningsson
On 6/6/05, Dimitry Golubovsky [EMAIL PROTECTED] wrote: Does there exist a tool which given a Haskell source, shows functions that are mutually recursive (i. e. call each other, even via calling third, etc. functions)? Knowledge of that would help to split the module into smaller modules

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-15 Thread Josef Svenningsson
On Mon, 14 Feb 2005 19:01:53 -0500, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I was thinking more along the lines of Ralf Hinze's nondeterminism transformer monad: http://haskell.org/hawiki/NonDeterminism The relevant instance is this: instance (Monad m) = MonadPlus (NondetT m)

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-14 Thread Josef Svenningsson
On Sun, 13 Feb 2005 19:08:26 -0500, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Quoting Josef Svenningsson [EMAIL PROTECTED]: I think it's unfair to the monad transformers to simply say that they don't obey the law. The interesting thing is whether they *preserve* the law. A monad

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-14 Thread Josef Svenningsson
On Mon, 14 Feb 2005 10:07:41 -0500, Jacques Carette [EMAIL PROTECTED] wrote: Josef Svenningsson [EMAIL PROTECTED] wrote: You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread Josef Svenningsson
On Sun, 13 Feb 2005 17:59:57 -0500, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: G'day all. Quoting Remi Turk [EMAIL PROTECTED]: According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m mzero === mzero, which IO

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Josef Svenningsson
On Thu, 09 Dec 2004 10:18:12 -0500, Robert Dockins [EMAIL PROTECTED] wrote: And I thought that most programmers used zipWith, which has to be prefix. Is this true? Can you not use backticks on a partially applied function? If so, it seems like such a thing would be pretty useful

Re: [Haskell-cafe] Re: not possible with monad transformers ?

2004-12-01 Thread Josef Svenningsson
On Tue, 30 Nov 2004 18:36:46 + (UTC), Pavel Zolnikov [EMAIL PROTECTED] wrote: [..] type M2 a = OuptutMonadT Maybe String a whenError:: M2 a - M2 a - M2 a 1 foo a b = do 2 output before 3 let r = liftM2 (+) a b 4 `whenError` $ reportError error 5 return r

[Haskell-cafe] RE: [Haskell] Lexically scoped type variables

2004-11-25 Thread Josef Svenningsson
Let me just begin by sharing my experience with scoped type variables. I've found them very useful in a project were I was to generalize a substantial code base. Many of the functions had local definitions whose type were simply not expressible without scoped type variables. During this work I

[Haskell-cafe] Interview with David Roundy on darcs and Haskell

2004-11-25 Thread Josef Svenningsson
Hi all, At osdir there is a nice interview with David Roundy about darcs, the revision control system written in Haskell. He has a few comments about Haskell as well. Read it here: http://osdir.com/Article2571.phtml This was also covered on /. (which is where I found it). /Josef

RE: [Haskell-cafe] empty Array?

2004-10-11 Thread Josef Svenningsson
It is, of course, trivial to implement this for lists. I've run into a snag, however, when trying to implement this for Arrays (as in Data.Array) - I can't seem to find a way to represent an empty array, which makes implementing 'empty' and 'null' impossible. Suggestions? Empty arrays can

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-07 Thread Josef Svenningsson
Andre, I very much enjoyed reading your blog entry. I would like to make a few comments. First of all I heartly agree with what you call the main problem. I quote: The main problem I see with all this is that its just too hard for an average Haskell programmer to get good performance out of

Re: [Haskell-cafe] dimension of arrays

2004-03-29 Thread Josef Svenningsson
On Mon, 29 Mar 2004, Fred Nicolier wrote: Is there a way to get the number of dimension of an array ? i.e. something like : dims :: (Ix a) = Array a b - Int dims = ... a = listArray (1,10) [1,2..] b = listArray ((1,1),(10,10)) [1,2..] dims a -- should be equal to 1 dims b -- should

Re: [Haskell-cafe] Sat solver

2004-02-05 Thread Josef Svenningsson
Hi, On Thu, 5 Feb 2004, Ron de Bruijn wrote: Hi there, I need a complete 3-CNF-Sat solver that can solve sentences of about length 20 (or shorter). Now I use simple model checking, but that's a bit slow , you understand :) I have seen some algorithms on the web and some code-sniplets

Monad @ Microsoft

2003-10-31 Thread Josef Svenningsson
OK, this one is just too good not to post about it. Microsoft has developed a now command line interface. Guess what they call it? Read it here: http://slashdot.org/articles/03/10/31/1346201.shtml?tid=185tid=190tid=201 Well, it seems Simoj PJ is doing a good job introducting functional

Re: fixed point

2003-10-28 Thread Josef Svenningsson
Sorry about replying to my own mail. On Mon, 27 Oct 2003, Josef Svenningsson wrote: On Mon, 27 Oct 2003, Paul Hudak wrote: Thomas L. Bevan wrote: Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix. Suppose you

Re: fixed point

2003-10-27 Thread Josef Svenningsson
On Mon, 27 Oct 2003, Paul Hudak wrote: Thomas L. Bevan wrote: Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix. Suppose you have a LET expression with a set of (possibly mutually recursive) equations such as: let f1

Re: can a lazy language give fast code?

2002-07-30 Thread Josef Svenningsson
Hi, On Mon, 29 Jul 2002, Scott J. wrote: Can one write withthe Haskell compliler faster code than in the examples of http://www.bagley.org/~doug/shootout/ where GHC (old Haskell 98?) seems to be much slower than Ocaml or Mlton both strict functional languages. Can one expect any

Re: Haskell problem

2002-02-21 Thread Josef Svenningsson
On Thu, 21 Feb 2002, Mark Wotton wrote: Hi, I'm trying out some combinatorial parsers, and I ran into a slightly inelegant construction. To parse a sequence of things, we have a function like pThen3 :: (a-b-c-d) - Parser a - Parser b - Parser c - Parser d pThen3 combine p1 p2 p3 toks =