Re: [Haskell-cafe] Re: Is a bug?

2009-07-26 Thread Dan Doel
On Sunday 26 July 2009 10:54:53 pm Linker wrote: Sorry.I defined a function : *GHCi, version 6.10.3: http://www.haskell.org/ghc/ :? for help* *Loading package ghc-prim ... linking ... done.* *Loading package integer ... linking ... done.* *Loading package base ... linking ... done.*

Re: Proposal: Deprecate ExistentialQuantification

2009-07-23 Thread Dan Doel
On Friday 10 July 2009 5:03:00 am Wolfgang Jeltsch wrote: Isn’t ExistentialQuantification more powerful than using GADTs for emulating existential quantification? To my knowledge, it is possible to use lazy patterns with existential types but not with GADTs. 6.10.4 doesn't allow you to use ~

Re: [Haskell-cafe] Re: Adding an ignore function to Control.Monad

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 3:35:27 am Jeff Wheeler wrote: On Fri, Jul 10, 2009 at 10:10 PM, Don Stewartd...@galois.com wrote: ## Control.Monad.void m a - m () Don Stewart Iavor Diatchki For whatever it's worth, I prefer void as well, for the exact reason Don said. Indeed, 'ignore'

Re: [Haskell-cafe] Type families and polymorphism

2009-07-11 Thread Dan Doel
On Saturday 11 July 2009 2:31:28 pm Jeremy Yallop wrote: Why does compiling the following program give an error? {-# LANGUAGE TypeFamilies, RankNTypes #-} type family TF a identity :: (forall a. TF a) - (forall a. TF a) identity x = x GHC 6.10.3 gives me: Couldn't match

Re: [Haskell-cafe] Alternative IO

2009-07-10 Thread Dan Doel
On Friday 10 July 2009 4:35:15 am Wolfgang Jeltsch wrote: I fear that this instance doesn’t satisfy required laws. As far as I know, the following equalities should hold: (*) = () f * empty = empty IO already fails at this law, because (f * empty) is not the same as empty, it is a

Re: [Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-06 Thread Dan Doel
On Thursday 02 July 2009 6:36:09 am Jon Fairbairn wrote: check :: (MonadPlus m) = (a - Bool) - a - m a check p a | p a = return a | otherwise = mzero I tried Hoogling for a function like check, but couldn't find it. Surely there's one in a library somewhere? It looks useful to me.

Re: [Haskell-cafe] How to read safely?

2009-06-24 Thread Dan Doel
On Wednesday 24 June 2009 5:40:28 am Magicloud Magiclouds wrote: Hi, Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no). At least, if its error could be catched, that'd be better. There was

Re: [Haskell-cafe] Getting my mind around UArray - STUArray conversion

2009-06-19 Thread Dan Doel
On Friday 19 June 2009 9:43:29 pm Scott Michel wrote: wombat :: (IArray UArray e, Ix ix, MArray (STUArray s) e (ST s)) = e - ix - UArray ix e - UArray ix e wombat val idx mem = (unsafeThaw mem :: ST s (STUArray s ix e)) = (\mmem - unsafeFreeze mmem) Based on the error message and dealing with

Re: [Haskell-cafe] Getting my mind around UArray - STUArray conversion

2009-06-19 Thread Dan Doel
Oops, I replied too hastily. What I wrote in my first mail is a problem, as witnessed by the ix and ix1 in the error message. However, it isn't the main error. The main error is that you have a monadic expression, with type something like: ST s (UArray ix e) but the return type of your

Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-14 Thread Dan Doel
On Thursday 14 May 2009 9:03:30 am Jan-Willem Maessen wrote: Hmm, I think neither of the data structures you name actually support both O(lg n) indexing and O(lg n) cons or append. That said, your point is well taken, so let's instead state it as a challenge: Data.Sequence has O(log n) index,

Re: [Haskell-cafe] Unfold fusion

2009-05-06 Thread Dan Doel
On Wednesday 06 May 2009 11:27:08 am Adrian Neumann wrote: Hello, I'm trying to prove the unfold fusion law, as given in the chapter Origami Programming in The Fun of Programming. unfold is defined like this: unfold p f g b = if p b then [] else (f b):unfold p f g (g b) And the law

Re: [Haskell-cafe] Unfold fusion

2009-05-06 Thread Dan Doel
On Wednesday 06 May 2009 4:26:15 pm Dan Doel wrote: unfortunately it looks like I'm doing something wrong in that coinductive hypothesis Sorry about the self-reply, but I realized where I went wrong. The principle of proof by coinduction for defining a function 'f' goes something like

Re: [Haskell-cafe] unsafeSTToIO and stToIO

2009-04-29 Thread Dan Doel
On Wednesday 29 April 2009 5:26:46 pm Xiao-Yong Jin wrote: Hi, Between the following two functions stToIO:: ST RealWorld a - IO a stToIO (ST m) = IO m unsafeSTToIO :: ST s a - IO a unsafeSTToIO (ST m) = IO (unsafeCoerce# m) All I can see is that the safe one uses RealWorld

Re: [Haskell-cafe] Functor and Haskell

2009-04-23 Thread Dan Doel
On Thursday 23 April 2009 2:44:48 pm Daryoush Mehrtash wrote: Thanks for this example I get the point now. (at least i think i do :) ) One more question This all being on the same category then the functor transformation can also be view as a simple morphism too. In this example the

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

2009-04-19 Thread Dan Doel
On Sunday 19 April 2009 4:56:29 pm wren ng thornton wrote: Bulat Ziganshin wrote: Hello R.A., Sunday, April 19, 2009, 11:46:53 PM, you wrote: Does anybody know if there are any plans to incorporate some of these extensions into GHC - specifically the existential typing ? it is

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

2009-04-19 Thread Dan Doel
On Sunday 19 April 2009 7:11:51 pm wren ng thornton wrote: Yes, however, because consumers (e.g. @f@) demand that their arguments remain polymorphic, anything which reduces the polymorphism of @a@ in @x@ will make it ineligible for being passed to consumers. Maybe not precise, but it works.

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

2009-04-19 Thread Dan Doel
On Sunday 19 April 2009 9:31:27 pm Derek Elkins wrote: simply because this is essentially a function with type (forall a. F a) - (exists a. F a) and you can do that by instantiating the argument to any type, and then hiding it in an existential), You can do this by using undefined,

Re: [Haskell-cafe] understanding typeable

2009-04-12 Thread Dan Doel
On Monday 13 April 2009 1:18:40 am Anatoly Yakovenko wrote: ah, Int vs Integer, i didn't see that at all. Thats kind of weird, i thought 1 could be either one. It can, but typeOf has to pick one instance to use. The default for Num is Integer, so that's what it chooses without any annotation

Re: [Haskell-cafe] Questions about slow GC with STArray

2009-04-06 Thread Dan Doel
On Monday 06 April 2009 4:10:43 am Bulat Ziganshin wrote: one way to solve this problem is to make one `modified` bit per each 256 elements rather than entire array so GC will have to scan only modified chunks For reference, I constructed a benchmark that takes advantage of GHC's tagging of

Re: [Haskell-cafe] ZipList monad, anyone?

2009-04-01 Thread Dan Doel
On Wednesday 01 April 2009 6:44:35 am Patai Gergely wrote: Does ZipList have any useful monad instance? The thought came up while thinking about higher order dataflows and an ArrowApply interface for Yampa. As a ZipList can be thought of as a function with a discrete domain, I figured its

Re: [Haskell-cafe] least fixed points above something

2009-03-20 Thread Dan Doel
On Friday 20 March 2009 2:43:49 am Martijn van Steenbergen wrote: Luke Palmer wrote: Well, it's probably not what you're looking for, but to remain true to the domain-theoretical roots of fix, the least fixed point above can be implemented as: fixAbove f x = fix f `lub` x How can this

Re: [Haskell-cafe] least fixed points above something

2009-03-20 Thread Dan Doel
On Friday 20 March 2009 5:23:37 am Ryan Ingram wrote: On Fri, Mar 20, 2009 at 1:01 AM, Dan Doel dan.d...@gmail.com wrote: However, to answer Luke's wonder, I don't think fixAbove always finds fixed points, even when its preconditions are met. Consider: f [] = [] f (x:xs) = x:x:xs

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Dan Doel
On Tuesday 17 March 2009 7:36:21 pm ben wrote: I am trying to understand the definition of (co)inductive types in Haskell. After reading the beginning of Vene's thesis [1] I was happy, because I understood the definition of the least fixpoint: newtype Mu f = In (f (Mu f)). But this

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Dan Doel
On Wednesday 18 March 2009 5:28:35 am Duncan Coutts wrote: You can explain it to yourself (not a proof) by writing out the example for lists and co-lists along with fold for the list and unfold function for the co-list. Then write conversion functions between them. You can go from lists to

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Dan Doel
On Wednesday 18 March 2009 5:15:32 am Ryan Ingram wrote: There's something from Wadler's draft that doesn't make sense to me. He says: This introduces a new type, T = Lfix X. F X, satisfying the isomorphism T ~ F T. Note that it is an isomorphism, not an equality: the type comes

Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-16 Thread Dan Doel
On Monday 16 March 2009 2:11:10 pm Ryan Ingram wrote: However, I disagree with your description of what unsafe should be used for. unsafe calls out the need for the programmer to prove that what they are doing is safe semantically, instead of the compiler providing those proofs for you.

Re: [Haskell-cafe] Microsoft PhD Scholarship at Strathclyde

2009-03-14 Thread Dan Doel
On Saturday 14 March 2009 8:12:09 am Conor McBride wrote: Rome wasn't burnt in a day. Of course I want more than just numerical indexing (and I even have a plan) but numeric constraints are so useful and have so much of their own peculiar structure that they're worth studying in their own

Re: [Haskell-cafe] Microsoft PhD Scholarship at Strathclyde

2009-03-14 Thread Dan Doel
On Saturday 14 March 2009 1:07:01 pm Conor McBride wrote: But this... 2) A family of singleton types int(n) parameterized by the static type. For instance, int(5) is the type that contains only the run-time value 5. 3) An existential around the above family for representing

Re: [Haskell-cafe] Pointless functors

2009-03-13 Thread Dan Doel
On Thursday 12 March 2009 10:30:47 pm Robin Green wrote: For most functors, that is equivalent to point x = undefined But by that logic, everything is a member of every typeclass... There are some cases where expected laws will prevent that. For instance, If you try to make a monad like:

Re: [Haskell-cafe] Does anybody dislike implicit params as much as I do?

2009-03-12 Thread Dan Doel
On Thursday 12 March 2009 4:36:28 pm Thomas Hartman wrote: http://blog.patch-tag.com/2009/03/09/implicitparams-are-evil-thoughts-on-ad apting-gitit/ I understand there are arguments for using IPs, but after this experience, the ImplicitParams extension is a code smell for me. Implicit

Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Dan Doel
On Wednesday 11 March 2009 2:24:55 pm R J wrote: foldl and foldr are defined as follows: foldr:: (a - b - b) - b - [a] - b foldr f e [] = e foldr f e (x : xs) = f x (foldr f e xs) foldl:: (b - a - b) - b - [a] - b foldl f e [] =

Re: Type functions and ambiguity

2009-03-09 Thread Dan Doel
On Monday 09 March 2009 11:56:14 am Simon Peyton-Jones wrote: For what it's worth, here's why. Suppose we have type family N a :: * f :: forall a. N a - Int f = blah g :: forall b. N b - Int g x = 1 + f x The defn of 'g' fails with a very similar

Re: [Haskell] Definitions of purity and Lazy IO

2009-03-06 Thread Dan Doel
On Thursday 05 March 2009 11:48:33 pm Jonathan Cast wrote: That is, for any program context C[] such that C[f1] is well-typed, the program C[f2] must too be well-typed, and if one can observe the result of C[f1] and of C[f2], the two observations must be identical. Every time? For every

Deep fmap with GADTs and type families.

2009-03-05 Thread Dan Doel
Greetings, Someone on comp.lang.functional was asking how to map through arbitrary nestings of lists, so I thought I'd demonstrate how his non-working ML function could actually be typed in GHC, like so: --- snip --- {-# LANGUAGE TypeFamilies, GADTs, EmptyDataDecls, Rank2Types,

Re: [Haskell] Lazy IO breaks purity

2009-03-04 Thread Dan Doel
On Wednesday 04 March 2009 9:12:20 pm o...@okmij.org wrote: We demonstrate how lazy IO breaks referential transparency. A pure function of the type Int-Int-Int gives different integers depending on the order of evaluation of its arguments. Our Haskell98 code uses nothing but the standard

Re: [Haskell-cafe] speed: ghc vs gcc

2009-02-20 Thread Dan Doel
Test.hs import Prelude hiding (sum, enumFromTo) import Data.List.Stream (sum, unfoldr) enumFromTo m n = unfoldr f m where f k | k = n= Just (k,k+1) | otherwise = Nothing main = print . sum $ enumFromTo 1 (10^9 :: Int) snip do...@zeke % time ./Test

Re: [Haskell-cafe] speed: ghc vs gcc

2009-02-20 Thread Dan Doel
Sorry for replying to myself, but I got suspicious about the 6ms runtime of the 64-bit C++ code on my machine. So I looked at the assembly and found this: .LCFI1: movabsq

Re: [Haskell-cafe] speed: ghc vs gcc

2009-02-20 Thread Dan Doel
On Friday 20 February 2009 10:52:03 am David Leimbach wrote: The GCC optimizer must know that you can't return a value to user space of that large as a return result. In Haskell you're printing it... why not print it in C++? I actually changed my local copy to print out the result (since I

Re: [Haskell-cafe] forall ST monad

2009-02-19 Thread Dan Doel
On Thursday 19 February 2009 7:22:48 am Kim-Ee Yeoh wrote: Jonathan Cast-2 wrote: Summary: Existential types are not enough for ST. You need the rank 2 type, to guarantee that *each* application of runST may (potentially) work with a different class of references. (A different state

Re: [Haskell-cafe] Re: forall ST monad

2009-02-17 Thread Dan Doel
On Tuesday 17 February 2009 7:28:18 am Heinrich Apfelmus wrote: Wolfgang Jeltsch wrote: First, I thought so too but I changed my mind. To my knowledge a type (forall a. T[a]) - T' is equivalent to the type exists a. (T[a] - T'). It’s the same as in predicate logic – Curry-Howard in action.

Re: [Haskell-cafe] Re: forall ST monad

2009-02-17 Thread Dan Doel
On Tuesday 17 February 2009 5:27:45 pm Ryan Ingram wrote: On Tue, Feb 17, 2009 at 5:22 AM, Dan Doel dan.d...@gmail.com wrote: -- fail: inferred type less polymorphic than expected -- This seems like it could perhaps work, since E'' -- re-hides the 'a' but it doesn't, probably because

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

2009-02-16 Thread Dan Doel
On Monday 16 February 2009 8:44:21 am Josef Svenningsson wrote: 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

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

2009-02-15 Thread Dan Doel
On Sunday 15 February 2009 9:44:42 pm Louis Wasserman wrote: Hello all, I just uploaded stateful-mtl and pqueue-mtl 1.0.1. The ST monad transformer and array transformer have been removed -- I've convinced myself that a heap transformer backed by an ST array cannot be referentially

Re: [Haskell-cafe] Moggi :: CT - Hask

2009-02-07 Thread Dan Doel
On Saturday 07 February 2009 12:11:29 pm Gregg Reynolds wrote: I had a monadic revelation at about 3 am. The answer to the question what is an IO value, really? is who cares? I just posted a blog entry discussing how CT found it's way from Moggi into Haskell at http://syntax.wikidot.com/blog

Re: [Haskell-cafe] type metaphysics

2009-02-03 Thread Dan Doel
On Tuesday 03 February 2009 9:05:08 pm wren ng thornton wrote: Extending things to GADTs, this is also the reason why functions are called exponential and denoted as such in category theory: |N - M| = |M| ^ |N| That's the number of functions that exist in that type. Not all of these are

Re: [Haskell-cafe] mapM_ - Monoid.Monad.map

2009-01-24 Thread Dan Doel
On Friday 23 January 2009 4:39:02 pm George Pollard wrote: with your proposed mapM_ will leave a thunk equivalent to () `mappend` () `mappend` () `mappend`... in memory until the mapM_ has completely finished, where each () is actually an unevalutated thunk that still has a reference

Re: [Haskell-cafe] Fold that quits early?

2009-01-24 Thread Dan Doel
On Saturday 24 January 2009 11:39:13 am Andrew Wagner wrote: This is almost a fold, but seemingly not quite? I know I've seem some talk of folds that potentially quit early. but not sure where I saw that, or if it fits. f xs [] = False f xs (y:ys) | any c ys' = True | otherwise

Re: [Haskell-cafe] Re: Laws and partial values

2009-01-24 Thread Dan Doel
On Saturday 24 January 2009 3:12:30 pm Thomas Davie wrote: On 24 Jan 2009, at 20:28, Jake McArthur wrote: Thomas Davie wrote: But, as there is only one value in the Unit type, all values we have no information about must surely be that value The flaw in your logic is your assumption

Re: [Haskell-cafe] Fold that quits early?

2009-01-24 Thread Dan Doel
On Saturday 24 January 2009 10:26:48 pm Andrew Wagner wrote: There's at least one thing; I won't call it a flaw in your logic, but it's not true of my usage. Your definition always produces a non-null list. The particular g in my mind will eventually produce a null list, somewhere down the

Re: [Haskell-cafe] mapM_ - Monoid.Monad.map

2009-01-23 Thread Dan Doel
On Friday 23 January 2009 3:50:18 pm Henning Thielemann wrote: I always considered the monad functions with names ending on '_' a concession to the IO monad. Would you need them for any other monad than IO? For self-written monads you would certainly use a monoid instead of monadic action,

Re: [Haskell-cafe] Functors [Comments from OCaml Hacker Brian Hurt]

2009-01-17 Thread Dan Doel
On Saturday 17 January 2009 8:28:05 am Bulat Ziganshin wrote: Hello Luke, Saturday, January 17, 2009, 3:16:06 PM, you wrote:   fmap id = id   fmap (f . g) = fmap f . fmap g  The first property is how we write preserving underlying structure, but this has a precise, well-defined

Re: [Haskell-cafe] Open unqualified imports

2009-01-16 Thread Dan Doel
On Friday 16 January 2009 9:42:46 am eyal.lo...@gmail.com wrote: I think currently many modules are designed to be imported unqualified, and this is unfortunate. Haskell' libraries can fix this. For example, the various Monadic counterparts such as mapM, replicateM, etc could do without the M

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-15 Thread Dan Doel
On Thursday 15 January 2009 6:21:28 pm David Menendez wrote: On Thu, Jan 15, 2009 at 5:32 PM, Andrew Coppin andrewcop...@btinternet.com wrote: As an aside, the integers form two different monoids. Haskell can't [easily] handle that. Does anybody know of a language that can? Some of the

Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Dan Doel
On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote: On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham news...@lava.net wrote: I have seen several libraries where all functions of a monad have the monadic result (), e.g. Binary.Put and other writing functions. This is a clear indicator,

Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Dan Doel
On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote: When GHC starts optimizing (Writer Builder) as well as it optimizes PutM, then that will be a cogent argument. Until then, one might argue that it misses the whole point of Put. Well it can still serve as an optimization over

Re: type families and overlapping

2008-12-17 Thread Dan Doel
On Wednesday 17 December 2008 1:25:26 pm Jorge Marques Pelizzoni wrote: Hi, While playing with type families in GHC 6.10.1, I guess I bumped into the no-overlap restriction. As I couldn't find any examples on that, I include the following (non-compiling) code so as to check with you if

[Haskell] ANNOUNCE: uvector-algorithms 0.1

2008-12-14 Thread Dan Doel
Hello, I've been sitting on this for a while, waiting for some changes to uvector to go in, but finally decided I should just release it, and fix it up if and when said changes go in. So, I'm announcing the first release of uvector- algorithms. What it is is a library of algorithms (mostly

[Haskell-cafe] ANNOUNCE: uvector-algorithms 0.1

2008-12-14 Thread Dan Doel
Hello, I've been sitting on this for a while, waiting for some changes to uvector to go in, but finally decided I should just release it, and fix it up if and when said changes go in. So, I'm announcing the first release of uvector- algorithms. What it is is a library of algorithms (mostly

Re: [Haskell-cafe] The Knight's Tour: solutions please

2008-12-01 Thread Dan Doel
On Monday 01 December 2008 1:39:13 pm Bertram Felgenhauer wrote: As one of the posters there points out, for n=100 the program doesn't actually backtrack if the 'loneliest neighbour' heuristic is used. Do any of our programs finish quickly for n=99? The Python one doesn't. Nothing I tried

Re: [Haskell-cafe] Re: Go Haskell! - array libraries

2008-11-30 Thread Dan Doel
On Sunday 30 November 2008 6:28:29 am Roman Leshchinskiy wrote: On 30/11/2008, at 11:36, Don Stewart wrote: Should mutable arrays have list-like APIs? All the usual operations, just in-place and destructive where appropriate? I don't know. To be honest, I don't think that the term mutable

Re: [Haskell-cafe] The Knight's Tour: solutions please

2008-11-30 Thread Dan Doel
Here's a clean-up of my code (it even fits within the line-length limit of my mail client :)). Note that it's pretty much exactly the Python algorithm. When the Python program finds a solution, it prints the board and exits. Since that's evil IO type stuff, we noble functional folk instead set

Re: [Haskell-cafe] varargs zip

2008-11-21 Thread Dan Doel
On Friday 21 November 2008 9:40:14 am Jason Dusek wrote: It came up on IRC last night that there is no generic zip in Haskell. I decided to write one as an example, but it only half works. When the argument lists are all definitely of one type, instance selection works as expected;

Re: Lazy minimum

2008-11-19 Thread Dan Doel
On Wednesday 19 November 2008 11:38:07 pm David Menendez wrote: One possibility would be to add minimum and maximum to Ord with the appropriate default definitions, similar to Monoid's mconcat. This is probably the most sensible way. However, first seeing this, I wanted to see if I could do it

Re: [Haskell-cafe] Proof that Haskell is RT

2008-11-13 Thread Dan Doel
On Wednesday 12 November 2008 7:05:02 pm Jonathan Cast wrote: I think the point is that randomIO is non-deterministic (technically, pseudo-random) but causal --- the result is completely determined by events that precede its completion. unsafeInterleaveIO, by contrast, is arguably (sometimes)

Re: [Haskell-cafe] Proof that Haskell is RT

2008-11-12 Thread Dan Doel
On Wednesday 12 November 2008 6:18:38 pm David MacIver wrote: To put it a different way, in the absence of unsafeInterleaveIO the IO monad has the property that if f and g are observably equal up to termination then x = f and x = g are equivalent in the IO monad (actually this may not be true

Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelementInt/Int map?

2008-10-19 Thread Dan Doel
On Sunday 19 October 2008 10:32:08 am Claus Reinke wrote: (hint to ghc hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be useful!-), I can't figure out what that means though. Strictness is not a property of types or of values, it is a property of functions. [!] is not a

Re: [Haskell-cafe] Haskell Weekly News: Issue 85 - September 13, 2008

2008-09-14 Thread Dan Doel
On Sunday 14 September 2008 6:59:06 am Rafael Almeida wrote: One thing have always bugged me: how do you prove that you have correctly proven something? I mean, when I write a code I'm formaly stating what I want to happen and bugs happen. If I try to prove some part of the code I write more

Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-08-28 Thread Dan Doel
On Thursday 28 August 2008 12:26:27 pm Adrian Hey wrote: As I've pointed out several times already you can find simple examples in the standard haskell libs. So far nobody has accepted my challenge to re-implement any of these competantly (I.E. avoiding the use of global variables). Why

Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-08-28 Thread Dan Doel
On Thursday 28 August 2008 2:28:35 pm David Roundy wrote: On Thu, Aug 28, 2008 at 01:17:29PM -0400, Dan Doel wrote: On Thursday 28 August 2008 12:26:27 pm Adrian Hey wrote: As I've pointed out several times already you can find simple examples in the standard haskell libs. So far nobody

Re: [Haskell-cafe] ansi2html - one program, several issues

2008-07-20 Thread Dan Doel
On Sunday 20 July 2008, John Meacham wrote: I do not believe that is the case, since the return type of runParser Either ParseError a means that before you can extract the result of the parse from the 'Right' branch, it must evaluate whether the result is 'Left' or 'Right' meaning it needs to

Re: [Haskell-cafe] Existential quantification problem

2008-07-10 Thread Dan Doel
On Thursday 10 July 2008, Marco Túlio Gontijo e Silva wrote: Hello, how do I unbox a existential quantificated data type? {-# LANGUAGE ExistentialQuantification #-} data L a = forall l. L (l a) unboxL (L l) = l is giving me, in GHC: Inferred type is less polymorphic than expected

Re: [Haskell-cafe] type classes

2008-07-02 Thread Dan Doel
On Wednesday 02 July 2008, Cotton Seed wrote: Hi everyone, I'm working on a computational algebra program and I've run into a problem. In my program, I have types for instances of algebraic objects, e.g. ZModN for modular integers, and types for the objects themselves, e.g. ZModNTy for the

Re: [Haskell-cafe] Learning GADT types to simulate dependent types

2008-06-28 Thread Dan Doel
On Saturday 28 June 2008, Paul Johnson wrote: I'm trying to understand how to use GADT types to simulate dependent types. I'm trying to write a version of list that uses Peano numbers in the types to keep track of how many elements are in the list. Like this: {-# OPTIONS -fglasgow-exts

Re: [Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-27 Thread Dan Doel
On Friday 27 June 2008, Anatoly Yakovenko wrote: $ cat htestdot.hs {-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields -fglasgow-exts -fbang-patterns -lcblas#-} module Main where import Data.Vector.Dense.IO import Control.Monad main = do let size = 10 let times =

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-23 Thread Dan Doel
On Monday 23 June 2008, Isaac Dupree wrote: there's no chance for the lower-level near code generation to reverse-SAT to eliminate the heap usage? (which would obviously be a different optimization that might be useful in other ways too, if it could be made to work) (did someone say that

Re: [Haskell-cafe] Safe way to parse arguments?

2008-06-21 Thread Dan Doel
On Saturday 21 June 2008, Don Stewart wrote: maybeRead :: Read a = String - Maybe a maybeRead s = case reads s of [(x, )] - Just x _ - Nothing Note, if you want to match the behavior of read, you'll probably want something like: maybeRead :: Read

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-20 Thread Dan Doel
On Friday 30 May 2008, Duncan Coutts wrote: This is for two reasons. One is because your second foldl' is directly recursive so does not get inlined. The static argument transformation it what you're doing manually to turn the latter into the former. The SAT is implemented in ghc 6.9 (though

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-20 Thread Dan Doel
On Friday 20 June 2008, Max Bolingbroke wrote: Of course, if you have any suggestions for good heuristics based on your benchmarking experience then we would like to hear them! There was some discussion of this in the original ticket, http://hackage.haskell.org/trac/ghc/ticket/888, but when

Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Doel
On Friday 20 June 2008, Pieter Laeremans wrote: type Id = String class Catalog a where listItems :: a - IO [String] getItem :: a - Id - IO (Maybe String) class Item a where getCatalog :: Catalog catalog = a - catalog data Catalog c = Content c = Content {auteur :: String,

Re: Low-level array performance

2008-06-18 Thread Dan Doel
On Wednesday 18 June 2008, Daniel Fischer wrote: Am Dienstag, 17. Juni 2008 22:37 schrieb Dan Doel: I'll attach new, hopefully bug-free versions of the benchmark to this message. With -O2 -fvia-C -optc-O3, the difference is small (less than 1%), but today, ByteArr is faster more often

Re: Low-level array performance

2008-06-17 Thread Dan Doel
On Tuesday 17 June 2008, Simon Marlow wrote: So I tried your examples and the Addr# version looks slower than the MBA# version: Hmm... I tried with 6.8.2 and 6.8.3, using -O2 in both cases. I tried the Ptr version with and without -fvia-C -optc-O2, no difference. I had forgotten about the

Re: Low-level array performance

2008-06-17 Thread Dan Doel
On Tuesday 17 June 2008, Daniel Fischer wrote: I've experimented a bit and found that Ptr is faster for small arrays (only very slightly so if compiled with -fvia-C -optc-O3), but ByteArr performs much better for larger arrays ... The GC time for the Addr# version is frightening I had an

Re: Low-level array performance

2008-06-17 Thread Dan Doel
On Tuesday 17 June 2008, [EMAIL PROTECTED] wrote: I see that Dan Doel's post favoring Ptr/Addr# has the same allocation amounts (from +RTS -sstderr) for Ptr/Addr# and the MutableByteArray# Everyone else sees more allocation for Ptr/Addr# than MBA# and see MBA# as faster in these cases. I

Low-level array performance

2008-06-16 Thread Dan Doel
Greetings, Recently, due to scattered complaints I'd seen on the internet, I set about to rewrite the fannkuch [1] benchmark on the Great Computer Language Shootout. The current entry uses Ptr/Addr#, malloc, etc. so it's not particularly representative of code one would actually write in

Re: [Haskell-cafe] 1/0

2008-06-16 Thread Dan Doel
On Monday 16 June 2008, Evan Laforge wrote: So, I know this has been discussed before, but: 1/0 Infinity 0/0 NaN ... so I see from the archives that Infinity is mandated by ieee754 even though my intuition says both should be NaN. Every other language throws an exception, even C

Re: [Haskell-cafe] Design your modules for qualified import

2008-06-07 Thread Dan Doel
On Friday 06 June 2008, Andrew Coppin wrote: It's really quite frustrating that it is 100% impossible to write a single function that will process lists, arrays, sets, maps, byte strings, etc. You have to write several different versions. OK, so some functions really don't make sense for a set

Re: [Haskell-cafe] Teaching Monads

2008-06-07 Thread Dan Doel
On Saturday 07 June 2008, Ronald Guida wrote: 3. These closures are extremely similar to the closures that arise when desugaring let-syntax. let x1 = f1 inf1 -$ (\x1 - Where: let x2 = f2 in f2 -$ (\x2 - (-$) :: a - (a - b) - b let x3 = f3 in

Re: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-05-29 Thread Dan Doel
On Thursday 29 May 2008, Tyson Whitehead wrote: I thought this was interesting. Is it to be expected? Am I right in interpreting this to mean it was just too much for the strictness analyzer. I believe the first ultimately produces significantly superior code, so should one always write

Re: [Haskell-cafe] reordering pure bindings in monads

2008-05-29 Thread Dan Doel
On Thursday 29 May 2008, Tim Newsham wrote: Intuitively it seems like the applicative expression: (++) $ getLine * getLine should represent the same thing as the more traditional liftM2 expressions: do { x - getLine; y - getLine; return ((++) x y) } but it seems to me that you cant

Re: [Haskell-cafe] one-way monads

2008-05-20 Thread Dan Doel
On Tuesday 20 May 2008, [EMAIL PROTECTED] wrote: Actually, it's true less than 50% of the time. In particular, it's not true of any monad transformer. Sure it is. Any particular transformer t typically comes with some particular way of writing a function of type t m a - m a (you may have to

Re: [Haskell-cafe] GHC predictability

2008-05-13 Thread Dan Doel
On Tuesday 13 May 2008, Jeff Polakow wrote: Is this the code you mean? meanNat = go 0 0 where go s n [] = s / n go s n (x:xs) = go (s+x) (n+1) xs If so, bang patterns are still required bang patterns in ghc-6.8.2 to run in constant memory: meanNat = go 0 0 where

[Haskell] ANNOUNCE: category-extras 0.2

2008-04-27 Thread Dan Doel
Hello, all. After quite a bit of collaboration with Edward Kmett over the past few days, I've rolled up a new release of category-extras. Perhaps the most significant addition is the generalized hylomorphism he first blogged about here:

[Haskell-cafe] ANNOUNCE: category-extras 0.2

2008-04-27 Thread Dan Doel
Hello, all. After quite a bit of collaboration with Edward Kmett over the past few days, I've rolled up a new release of category-extras. Perhaps the most significant addition is the generalized hylomorphism he first blogged about here:

Re: Suggestion regarding (.) and map

2008-04-24 Thread Dan Doel
On Thursday 24 April 2008, Wolfgang Jeltsch wrote: I don’t think that this is reasonable. (.) corresponds to the little circle in math which is a composition. So (.) = () would be far better. Were I building a library, this might be the direction I'd take things. They're two incompatible

Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread Dan Doel
On Wednesday 23 April 2008, Bulat Ziganshin wrote: Hello Dan, Wednesday, April 23, 2008, 1:42:20 PM, you wrote: This wouldn't work, you'd have to rewrite it as: withSomeResource foo . withSomeOtherThing bar . yetAnotherBlockStructured thing $ ... it is very

Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread Dan Doel
On Wednesday 23 April 2008, Bulat Ziganshin wrote: it's not refactoring! it's just adding more features - exception handler, progress indicator, memory pool and so on. actually, code blocks used as a sort of RAII for Haskell. are you wanna change all those ';' when you add new variable to your

Re: Meta-point: backward compatibility

2008-04-23 Thread Dan Doel
On Wednesday 23 April 2008, Chris Smith wrote: I don't think I agree that fail in the Monad typeclass is a good example here, or necessarily that there is a good example. We should remember that there is a cohesive community of Haskell programmers; not a bunch of unrelated individuals who

Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-22 Thread Dan Doel
On Tuesday 22 April 2008, Simon Marlow wrote: I'm hoping someone will supply some. There seemed to be strong opinion on #haskell that this change should be made, but it might just have been a very vocal minority. These are the arguments off the top of my head: 1) Anything of the form: f

Re: [Haskell-cafe] Re: Type families and GADTs in 6.9

2008-04-12 Thread Dan Doel
On Saturday 12 April 2008, ChrisK wrote: The length calculation looked complicated. So I reformulated it as a comparison using HasIndex. But ghc-6.8.2 was not inferring the recursive constraint on proj, so I split proj into proj_unsafe without the constraint and proj with the constraint

[Haskell-cafe] Type families and GADTs in 6.9

2008-04-11 Thread Dan Doel
Hello, I've been playing around with type families off and on in 6.8, but, what with the implementation therein being reportedly incomplete, it's hard to know what I'm getting right and wrong, or what should work but doesn't and so on. So, I finally decided to take the plunge and install 6.9

<    1   2   3   4   >