Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Alfonso Acosta
OK I'll include the module after I change the things mentioned. BTW, I finally have an initial version of the parameterized-data package: Darcs repository: http://code.haskell.org/parameterized-data Haddock documentation: http://code.haskell.org/~fons/parameterized-data/doc/ Any

Re: [Haskell-cafe] Doubting Haskell

2008-02-20 Thread Cale Gibbard
(I'm copying the list on this, since my reply contains a tutorial which might be of use to other beginners.) On 19/02/2008, Alan Carter [EMAIL PROTECTED] wrote: Hi Cale, On Feb 19, 2008 3:48 PM, Cale Gibbard [EMAIL PROTECTED] wrote: Just checking up, since you haven't replied on the list.

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Wolfgang Jeltsch
Am Mittwoch, 20. Februar 2008 09:20 schrieben Sie: OK I'll include the module after I change the things mentioned. BTW, I finally have an initial version of the parameterized-data package: Darcs repository: http://code.haskell.org/parameterized-data Haddock documentation:

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann
Now, to help solve this problem, I wrote ListLike[2], providing a set of typeclasses that make list operations generic. I also provided default instances of ListLike for: ListLike Data.ByteString.ByteString Word8 ListLike Data.ByteString.Lazy.ByteString Word8 ListLike [a] a (Integral i,

[Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
Hi folks, Before I started using Haskell, I used OCaml for a spell. One of my biggest annoyances with OCaml was that it had two list types: the default list (strict), and a lazy list (known as a stream). This led to all sorts of annoyances. Libraries were always written to work with one list

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Ross Paterson
On Wed, Feb 20, 2008 at 08:39:13AM -0600, John Goerzen wrote: I am concerned that the same thing is happening in Haskell. We now have three common list-like types: the regular list, strict ByteString, and lazy ByteString. This has created some annoying situations. For instance, a

Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Brent Yorgey
2008/2/19 Jeff φ [EMAIL PROTECTED]: instance SmartArraySelector UArray Bool where instance SmartArraySelector UArray Char where instance SmartArraySelector UArray Double where instance SmartArraySelector UArray Float where instance SmartArraySelector UArray Intwhere Well, I'm not

[Haskell-cafe] First Call for Papers -- GPCE'08

2008-02-20 Thread Emir Pasalic
Call for Papers Seventh International Conference on Generative Programming and Component Engineering (GPCE 2008) October 19-23, 2008 Nashville, Tennessee

Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Henning Thielemann
On Wed, 20 Feb 2008, Brent Yorgey wrote: 2008/2/19 Jeff ö [EMAIL PROTECTED]: instance SmartArraySelector UArray Bool where instance SmartArraySelector UArray Char where instance SmartArraySelector UArray Double where instance SmartArraySelector UArray Float where instance

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, Ross Paterson [EMAIL PROTECTED] wrote: conventions won't be usable in my ByteString code, for instance. [...] http://software.complete.org/listlike/static/doc/ListLike/Data-ListLike.html As Henning pointed out, multiple parameter type classes are problematic for core

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote: I notice that Data.Foldable does some similar things but does not use multi-parameter type classes. I seem to recall that I attempted to do this in the same manner, but got tripped up somewhere. I can't remember now exactly what the

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Neil Mitchell
Hi full - Maybe (item, full) Hrm, what exactly is the return data here? Is is the head and the tail if the list has = 1 item, or Nothing otherwise? Or...? Yes, its the projection onto another type: [] = Nothing (x:xs) = Just (x, xs) What is the problem with MPTC in base?

[Haskell-cafe] Problem with Python AST

2008-02-20 Thread Roel van Dijk
Hello everyone, I am trying to create an AST for Python. My approach is to create a data type for each syntactic construct. But I am stuck trying to statically enforce some constraints over my statements. A very short example to illustrate my problem: newtype Ident = Id String data BinOp = Add

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-20 Thread Alfonso Acosta
On Wed, Feb 20, 2008 at 11:26 AM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote: Hello Fons, why do you use the term vector? I'd say that this term is more or less wrong for what this type is about. The distinguishing property of vectors compared to lists is that there is addition and scalar

Re: [Haskell-cafe] Problem with Python AST

2008-02-20 Thread Daniel Gorín
Hi Something like this would do? if_ = Compound $ If [(IntLit 6, Suite [] [Break])] Nothing while_ = Compound $ While (IntLit 6) (Suite [] [if_]) Nothing f = Program [while_] -- this one fails -- f2 = Program [if_] newtype Ident = Id String data BinOp = Add | Sub data Exp =

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Jules Bean
John Goerzen wrote: On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote: I notice that Data.Foldable does some similar things but does not use multi-parameter type classes. I seem to recall that I attempted to do this in the same manner, but got tripped up somewhere. I can't remember now

Re: [Haskell-cafe] stream/bytestring questions

2008-02-20 Thread Chad Scherrer
On Feb 17, 2008 6:06 PM, Derek Elkins [EMAIL PROTECTED] wrote: It's -quite- possible that a coalgebraic perspective is much more natural for your code/problem. If that's the case, use it (the coalgebraic perspective that is). Obviously depending on the internals of the stream library is not

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
Henning Thielemann lemming at henning-thielemann.de writes: 4) We are missing one final useful type: a Word32-based ByteString. When working in the Unicode character set, a 32-bit character can indeed be useful, and I could see situations in which the performance benefit of a

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:48 PM, Chad Scherrer [EMAIL PROTECTED] wrote: StorableVector should fill this gap. http://code.haskell.org/~sjanssen/storablevector/ Yes, it could, but (1) it's way behind ByteString in terms of optimizations (== fusion) (2) there's (as far as I know) not a

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote: For anyone looking into it - the StorableVector fusion would have to be quite different from the current ByteString fusion framework. Maybe it would be enough to lay down a Stream fusion framework for StorableVectors. I must be

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote: Not directly, no. The point about Foldable, Functor, and Monad, is that they enforce the connection between container and contents. If the contents is of type a, the container is of type f a for a fixed type constructor 'f'. This works

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Antoine Latter
On Feb 20, 2008 12:59 PM, Chad Scherrer [EMAIL PROTECTED] wrote: On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote: For anyone looking into it - the StorableVector fusion would have to be quite different from the current ByteString fusion framework. Maybe it would be enough

Re: [Haskell-cafe] Doubting Haskell

2008-02-20 Thread Alan Carter
Cale, On Feb 20, 2008 10:58 AM, Cale Gibbard [EMAIL PROTECTED] wrote: (I'm copying the list on this, since my reply contains a tutorial which might be of use to other beginners.) Thank you so much for this - I've just started playing with it so few intelligent responses yet. I'm sure it will

[Haskell-cafe] Broken http://darcs.haskell.org/darcsweb/?

2008-02-20 Thread Dominic Steinitz
I'm getting errors when I click on any of the links. I'm not sure who administers the site. IOError Python 2.4.4: /usr/bin/python Wed Feb 20 11:41:13 2008 A problem occurred in a Python script. Here is the sequence of function calls leading up to the error, in the order they occurred.

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Chad Scherrer
Antoine Latter [EMAIL PROTECTED] wrote: From what I saw of Data.ByteString.Fusion, it relies on the assumption that the elements of the output array are of the same size and alignment as the elements of all of the arrays in the fused intermediate steps. That way, all of the intermediate

[Haskell-cafe] Re: Arrows: definition of pure arr

2008-02-20 Thread Ben Franksen
Wolfgang Jeltsch wrote: I’m also in the process of shortening the names for type variables since in conference papers you cannot use names that long (because otherwise you quickly overrun the available width) and I don’t want to have too many differences between papers and actual source code.

[Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
-- proposition data Prp a = Var a | Not (Prp a) | Or (Prp a) (Prp a) | And (Prp a) (Prp a) | Imp (Prp a) (Prp a) | Xor (Prp a) (Prp a) | Eqv (Prp a) (Prp a) | Cns Bool deriving (Show, Eq) -- Here are to

[Haskell-cafe] Re: a help for install

2008-02-20 Thread Ben Franksen
Wolfgang Jeltsch wrote: Am Montag, 18. Februar 2008 19:46 schrieb Carlos Gomez A.: hi, my name is carlos I need information for correct installor what are dependencies on ghc ? I have a Debian System. Always use your distribution’s packages until they aren’t any or there is good

Re: [Haskell-cafe] Exporting Haskell Libraries to C Programmers

2008-02-20 Thread Don Stewart
joseph.bruce: Hi, I have a Haskell library that I want to make available via FFI to C programmers on my project team. I read this thread (http://thread.gmane.org/gmane.comp.lang.haskell.cafe/21447) which had some interesting ideas, but they seemed unresolved. Or maybe it answers my

[Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Steve Lihn
I proudly announce a little toy that lists the frequency of modules being imported by other modules. Do you know Control.Monad is the most frequently imported module? I did not! Currently it only includes GHC 6.8 core library. If you have any idea how to parse through HackageDB code, please let

Re: [Haskell-cafe] Broken http://darcs.haskell.org/darcsweb/?

2008-02-20 Thread Ian Lynagh
On Wed, Feb 20, 2008 at 07:28:54PM +, Dominic Steinitz wrote: I'm getting errors when I click on any of the links. I've created /tmp/darcsweb-cache and made it writable, which seems to have made it work again. I'm not sure who administers the site. Neither am I, but it needs some tweaking

[Haskell-cafe] Re: Selecting Array type

2008-02-20 Thread Ben Franksen
Jeff φ wrote: However, my implementation of SmartArray requires me to create an instance of a selector class to tell the compiler whether the type is boxed or unboxed. I'm hoping to avoid creating instances of the selector class for every possible type. I'd be grateful for any suggestions.

[Haskell-cafe] Fwd: NW Functional Programming Interest Group

2008-02-20 Thread Greg Meredith
All, Apologies for multiple listings. This is just a friendly reminder that a small cadre of us are organizing a Northwest Functional Programming Interest Group. Our first official meeting is today at the The Seattle Public Library 1000 - 4th Ave. Seattle, WA 98104 Spiral 6 Conference Room

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Ben Franksen
John Goerzen wrote: On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote: Not directly, no. The point about Foldable, Functor, and Monad, is that they enforce the connection between container and contents. If the contents is of type a, the container is of type f a for a fixed type constructor

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Roundy
On Wed, Feb 20, 2008 at 11:18:51PM +0100, Ben Franksen wrote: John Goerzen wrote: On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote: Not directly, no. The point about Foldable, Functor, and Monad, is that they enforce the connection between container and contents. If the contents is

[Haskell-cafe] Re: Re: The Proliferation of List-Like Types

2008-02-20 Thread Ben Franksen
David Roundy wrote: On Wed, Feb 20, 2008 at 11:18:51PM +0100, Ben Franksen wrote: John Goerzen wrote: On 2008-02-20, Jules Bean [EMAIL PROTECTED] wrote: Not directly, no. The point about Foldable, Functor, and Monad, is that they enforce the connection between container and contents.

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On 2008-02-20, John Goerzen [EMAIL PROTECTED] wrote: On the other hand, if you mean using a dictionary to wrap just the ByteString types (or other similar ones), I am currently thinking of something along those lines. I'll post here if I come up with something clever (or not). Can't come up

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Duncan Coutts
On Wed, 2008-02-20 at 08:39 -0600, John Goerzen wrote: * The iconv library works only on lazy ByteStrings, and does not handle Strings or strict ByteStrings There is a very good reason for this. The right solution in this particular example is not to overload every internal string

Re: [Haskell-cafe] question about STM and IO

2008-02-20 Thread Bulat Ziganshin
Hello John, Tuesday, February 12, 2008, 9:28:22 PM, you wrote: I was recently looking at the STM library, and I have a question about the function unsafeIOToSTM. Can anyone explain to me what is unsafe about it, and what sort of use would be considered safe? STM operations can be repeated if

Re: [Haskell-cafe] Haddock documentation of Data.Array.* is confusing

2008-02-20 Thread Bulat Ziganshin
Hello Alfonso, Tuesday, February 12, 2008, 11:32:20 PM, you wrote: Excuse me for the subject, but IMHO is absolutely true. Anyhow, the of course, you are right, but for practical goals i may suggest just to read module sources instead of reading [had]docs. seeing the implementation is much

Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Wolfgang Jeltsch
Am Mittwoch, 20. Februar 2008 22:22 schrieb Steve Lihn: I proudly announce a little toy that lists the frequency of modules being imported by other modules. Do you know Control.Monad is the most frequently imported module? I did not! This doesn’t surprise me very much. What surprises me more

Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Ross Paterson
On Wed, Feb 20, 2008 at 09:22:58PM +, Steve Lihn wrote: I proudly announce a little toy that lists the frequency of modules being imported by other modules. Do you know Control.Monad is the most frequently imported module? I did not! Currently it only includes GHC 6.8 core library. If

Re: [Haskell-cafe] Where does ~ come from?

2008-02-20 Thread Steve Lihn
If ~ does not have any special meaning and it could be ### or xyz, then how does GHC know to print a ~ b, but not ~ a b a ### b, but not ### a b xyz a b, but not a `xyz` b Simply because xyz is alphanumeric? On Wed, Feb 20, 2008 at 12:34 AM, David Menendez [EMAIL PROTECTED] wrote: On Feb

Re: [Haskell-cafe] Where does ~ come from?

2008-02-20 Thread Stefan O'Rear
On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote: If ~ does not have any special meaning and it could be ### or xyz, then how does GHC know to print a ~ b, but not ~ a b a ### b, but not ### a b xyz a b, but not a `xyz` b Simply because xyz is alphanumeric? Yes. Stefan

Re: [Haskell-cafe] Haddock documentation of Data.Array.* is confusing

2008-02-20 Thread Alfonso Acosta
On Wed, Feb 20, 2008 at 10:17 PM, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Alfonso, Tuesday, February 12, 2008, 11:32:20 PM, you wrote: Excuse me for the subject, but IMHO is absolutely true. Anyhow, the of course, you are right, but for practical goals i may suggest just to

[Haskell-cafe] haddock as a markdown preprocessor

2008-02-20 Thread Conal Elliott
There was a chat today on #haskellhttp://tunes.org/%7Enef/logs/haskell/08.02.20 (15:08 to 16:10) about evolving haddock. I'd like to get comments. The goal is to get the full functionality of a general purpose, programmer-friendly markup language like markdown. One example is image embedding.

[Haskell-cafe] Re: Where does ~ come from?

2008-02-20 Thread Ben Franksen
Stefan O'Rear wrote: On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote: If ~ does not have any special meaning and it could be ### or xyz, then how does GHC know to print a ~ b, but not ~ a b a ### b, but not ### a b xyz a b, but not a `xyz` b Simply because xyz is

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On Wednesday 20 February 2008 5:13:34 pm Duncan Coutts wrote: On Wed, 2008-02-20 at 08:39 -0600, John Goerzen wrote: * The iconv library works only on lazy ByteStrings, and does not handle Strings or strict ByteStrings There is a very good reason for this. The right solution in this

Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Ryan Ingram
Oleg's done a lot of work here; there's a bunch of magic that can be done with TypeCast. I took my inspiration from here: http://okmij.org/ftp/Haskell/typecast.html#ambiguity-resolution Here are some tests in ghci (note that I specialized the index type in test to Int to make this shorter; doing

Re: [Haskell-cafe] stream/bytestring questions

2008-02-20 Thread Roman Leshchinskiy
Chad Scherrer wrote: Here's an example of the problem. Start with a function extract :: [Int] - [a] - [a] extract = f 0 where f !k nss@(n:ns) (x:xs) | n == k= x : f (k+1) ns xs | otherwise = f (k+1) nss xs f _ _ _ = [] If you want this to play nicely with stream

Re: [Haskell-cafe] question about STM and IO

2008-02-20 Thread Ryan Ingram
On 2/20/08, Bulat Ziganshin [EMAIL PROTECTED] wrote: STM operations can be repeated if first transaction was unsuccessful. so, you may se here only operations that may be safely repeated - say, reading/writing memory areas, or reading/writing files, or even sending network message as long as

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Roman Leshchinskiy
John Goerzen wrote: I am concerned that the same thing is happening in Haskell. We know have three common list-like types: the regular list, strict ByteString, and lazy ByteString. Why do you consider ByteString to be list-like but not arrays? 1) Does everyone agree with me that we have a

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Ryan Ingram
It depends what you mean by faster; more efficient (runtime) or less typing (programmer time!) For the former, you have basically the best implementation there is; you are basically encoding the continuation of (++) into the accumulating list of arguments to evs. You might want to consider

Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Benjamin L. Russell
Rewriting that script in Haskell could be an interesting exercise. Do you have the source code? Benjamin L. Russell --- Steve Lihn [EMAIL PROTECTED] wrote: I proudly announce a little toy that lists the frequency of modules being imported by other modules. Do you know Control.Monad is the

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb
G'day all. Quoting Cetin Sert [EMAIL PROTECTED]: -- proposition data Prp a = Var a | Not (Prp a) | Or (Prp a) (Prp a) | And (Prp a) (Prp a) | Imp (Prp a) (Prp a) | Xor (Prp a) (Prp a) | Eqv (Prp a) (Prp a) | Cns Bool

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread ajb
G'day all. Quoting Neil Mitchell [EMAIL PROTECTED]: Yes, its the projection onto another type: [] = Nothing (x:xs) = Just (x, xs) Also known as msplit: http://www.haskell.org/haskellwiki/New_monads/MonadSplit Cheers, Andrew Bromage ___

[Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann
On Wed, 20 Feb 2008, Chad Scherrer wrote: On Feb 20, 2008 10:57 AM, Antoine Latter [EMAIL PROTECTED] wrote: For anyone looking into it - the StorableVector fusion would have to be quite different from the current ByteString fusion framework. Maybe it would be enough to lay down a Stream

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread Henning Thielemann
On Thu, 21 Feb 2008, Roman Leshchinskiy wrote: John Goerzen wrote: 2) Would it make sense to make ListLike, or something like it, part of the Haskell core? I don't think ListLike is the right approach. It's basically a fairly arbitrary collection of functions. It would be preferable,

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
plong 0 = Var 0 plong n | even n= Or (Var n) (plong (n-1)) | otherwise = And (Var n) (plong (n-1)) main = do print ((length ∘ vars) (plong 1000)) real0m3.290s user0m3.152s sys 0m0.020s main = do print ((length ∘ vars_) (plong 1000)) real0m3.732s user

Re: [Haskell-cafe] question about STM and IO

2008-02-20 Thread John Lato
I take it that this follows from the lack of any mechanism to rollback IO? If so, I think that the following guidelines suffice for when it's acceptable to use unsafeIOtoSTM: 1. The IO action must be able to be safely repeated. 2. The IO action must be able to be safely performed with

Re: [Haskell-cafe] A little toy of Haskell Trivia

2008-02-20 Thread Henning Thielemann
On Thu, 21 Feb 2008, Wolfgang Jeltsch wrote: Am Mittwoch, 20. Februar 2008 22:22 schrieb Steve Lihn: I proudly announce a little toy that lists the frequency of modules being imported by other modules. Do you know Control.Monad is the most frequently imported module? I did not! This

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Derek Elkins
On Thu, 2008-02-21 at 05:10 +0100, Cetin Sert wrote: plong 0 = Var 0 plong n | even n= Or (Var n) (plong (n-1)) | otherwise = And (Var n) (plong (n-1)) compare the times again but with plong as follows: plong 0 = Var 0 plong n | even n = Or (plong (n-1)) (Var n) |

Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-20 Thread John Goerzen
On Wednesday 20 February 2008 8:42:56 pm Roman Leshchinskiy wrote: John Goerzen wrote: I am concerned that the same thing is happening in Haskell. We know have three common list-like types: the regular list, strict ByteString, and lazy ByteString. Why do you consider ByteString to be

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb
G'day all. Quoting Cetin Sert [EMAIL PROTECTED]: It is astonishing to see that your version actually performs the worst (at least on my machine). On your example, I'm not surprised: plong 0 = Var 0 plong n | even n= Or (Var n) (plong (n-1)) | otherwise = And (Var n) (plong

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert 101 real0m1.384s user0m1.148s sys 0m0.112s [EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage 101 real0m2.240s user0m1.972s sys 0m0.176s [EMAIL

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
I would expect my (well, I didn't invent it) to work better on something that didn't have this unique structure, such as: test 0 = Var 0 test n | even n= Or (Var n) (test (n-1)) | otherwise = And (test (n-1)) (Var n) for some reason this still does not perform as well as it should

Re: [Haskell-cafe] Selecting Array type

2008-02-20 Thread Jeff φ
On 2/19/08, Ryan Ingram [EMAIL PROTECTED] wrote: Oleg's done a lot of work here; there's a bunch of magic that can be done with TypeCast. I took my inspiration from here: http://okmij.org/ftp/Haskell/typecast.html#ambiguity-resolution . . . The trick is to represent whether a type is

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread David Menendez
On Wed, Feb 20, 2008 at 10:46 PM, [EMAIL PROTECTED] wrote: Quoting Neil Mitchell [EMAIL PROTECTED]: Yes, its the projection onto another type: [] = Nothing (x:xs) = Just (x, xs) Also known as msplit: http://www.haskell.org/haskellwiki/New_monads/MonadSplit Almost. The