Re: [Haskell-cafe] Working with the code For Typing Haskell In Haskell

2011-10-25 Thread Tom Pledger
Patrick LeBoutillier patrick.leboutillier at gmail.com writes: [...] exprt = Ap (Const mapt) (Const idt) test = runTI $ tiExpr initialEnv [] exprt When I execute the test function above in ghci I get: ([],TVar (Tyvar v3 Star)). I was expecting someting like below for the type

[Haskell-cafe] Re: Problems with threading?

2010-06-08 Thread Tom Pledger
Louis Wasserman wasserman.louis at gmail.com writes: While working on the Shootout, I noticed the following benchmarks: http://shootout.alioth.debian.org/u64/program.php?test=chameneosreduxlang=ghcid=3 http://shootout.alioth.debian.org/u64q/program.php?test=chameneosreduxlang=ghcid=3 [...]

[Haskell-cafe] Re: Need some help with an infinite list

2009-06-18 Thread Tom Pledger
Daniel Peebles pumpkingod at gmail.com writes: My solution attempted to exploit this using Numeric.showIntAtBase but failed because of the lack of 0 prefixes in the numbers. If you can find a simple way to fix it without duplicating the showIntAtBase code, I'd be interested! Another

[Haskell-cafe] Re: Need some help with an infinite list

2009-06-16 Thread Tom Pledger
GüŸnther Schmidt gue.schmidt at web.de writes: Hi guys, I'd like to generate an infinite list, like [a, b, c .. z, aa, ab, ac .. az, ba, bb, bc .. bz, ca ...] If you're happy to have a before the a, you can do this as a fairly cute one-liner in a similar style to this list of

[Haskell-cafe] Re: Typeclass question

2008-12-27 Thread Tom Pledger
Andrew Wagner wagner.andrew at gmail.com writes: I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this: data Foo = Bar a = Foo a Bool ... That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of

[Haskell-cafe] expension of fractions

2007-07-25 Thread Tom Pledger
Arie Groeneveld wrote: : | Looking at the result of my rewriting gives me the idea it isn't | Haskelly enough. | | Anyways, here's my interpretation: | | -- period m/n base = (period length, preperiod digits, period digits) | period :: Integer - Integer - Integer - (Int, ([Integer],

[Haskell-cafe] xkcd #287 NP-Complete

2007-07-15 Thread Tom Pledger
We've seen some nice concise solutions that can deal with the original problem: solve 1505 [215, 275, 335, 355, 420, 580] I'll be a nuisance and bring up this case: solve 150005 [2, 4, 150001] A more scalable solution is to use an explicit heap that brings together all the ways to

[Haskell-cafe] Construct all possible trees

2007-06-13 Thread Tom Pledger
*Andrew Coppin wrote: * | I'm trying to construct a function | | all_trees :: [Int] - [Tree] | | such that all_trees [1,2,3] will yield : If you write a helper function that takes an N element list, and returns all 2^N ways of dividing those elements into 2 lists, e.g. splits ab --

[Haskell-cafe] Switch optimization

2007-06-10 Thread Tom Pledger
Stefan O'Rear wrote: | On Mon, Jun 11, 2007 at 09:43:17AM +1000, Thomas Conway wrote: : | codeLen 127 = 0 | codeLen 128 = 1 | ... | codeLen 255 = 8 | | Now, compiling with ghc 6.6.1 and -O3, I see that it generates a long | chain of conditional branches. : That's deeply tied in

Re: [Haskell-cafe] The difference between ($) and application

2004-12-14 Thread Tom Pledger
[EMAIL PROTECTED] wrote: [...] However, if we try t2' = W $ id we get an error: /tmp/t1.hs:13: Inferred type is less polymorphic than expected Quantified type variable `a' escapes Expected type: (a - a) - b Inferred type: (forall a1. a1 - a1) - W In the first argument

Re: [Haskell-cafe] Is this a useful higher-order function, or should I RTFM?

2004-12-08 Thread Tom Pledger
Steven Huwig wrote: On Dec 6, 2004, at 11:05 PM, Tom Pledger wrote: import Data.Char(isSpace) import Data.List(groupBy) (op `on` f) x y = f x `op` f y wordsAndSpaces = groupBy ((==) `on` isSpace) `on` is a handy little function in this instance. Does it have a technical name

Re: [Haskell-cafe] ghc has problems with 'zipWith' ?

2004-12-08 Thread Tom Pledger
Daniel Fischer wrote: Hi, I have recently come across the curious phenomenon that ghci is sometimes much slower than hugs. [...] ms as = zipWith (+) (zipWith (*) as (1:ms as)) (0:1:ms as) Hugs has(**) a specific optimisation for the case where the left hand side of the declaration occurs as a

Re: [Haskell-cafe] Is this a useful higher-order function, or should I RTFM?

2004-12-06 Thread Tom Pledger
Steven Huwig wrote: [...] 1) Did I miss something in the Prelude or standard library that gives me this functionality, or something close to it? [...] 3) The 3-tuple output of unravel looks ugly to me, but I can't think of an alternative. For the case where there is an equal number of

Re: [Haskell-cafe] Set of reals...?

2004-10-29 Thread Tom Pledger
Keith Wansbrough wrote: [...] Your data structure should be something like: data Interval = Interval { left :: Double, leftopen :: Bool, right :: Double, rightopen :: Bool } data Set = Set [Interval] If you want more efficiency, you probably want a bintree

Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

2004-10-09 Thread Tom Pledger
MR K P SCHUPKE wrote: [...] I dont see why you cannot change the implementation of lists without changing the interface... Good old lists will behave like good old lists - just the implementation would try and take advantage of blocking of the data wherever possible. Perhaps a pragma to change the

Re: Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

2004-10-09 Thread Tom Pledger
[EMAIL PROTECTED] wrote: [...] Actually we merely need to add a deconstructor. Also, we can leave the type of elements fully polymorphic. Something like this: class List l where nil :: l a cons :: a - l a - l a decon :: l a - w -- on empty - (a - l a - w)

Re: [Haskell-cafe] Haskell extension/improvement

2004-08-17 Thread Tom Pledger
Ron de Bruijn wrote: --- Martin_Sjögren [EMAIL PROTECTED] wrote: [...] mapM_ quickCheck [Test prop_revrev, Test prop_trivial, Test prop_something] Regards, Martin I didn't expect these replies (including one mentioning the HList idea(the enforced ordening is nice, though)), while I tried to be

Re: [Haskell-cafe] Control.Monad.Error with a custom error type

2004-08-14 Thread Tom Pledger
Brian Smith wrote: [...] instance MonadError (Either ReferenceError) Kind error: `Either ReferenceError' is not applied to enough type arguments When checking kinds in `MonadError (Either ReferenceError)' In the instance declaration for `MonadError (Either ReferenceError)' MonadError takes

Re: [Haskell-cafe] Question on Exercise from SOE

2004-07-03 Thread Tom Pledger
Nathan Weston wrote: I am learning haskell (and functional programming), from the School of Expression book. There's an exercise to rewrite the following function (for computing the area of a polygon) using map, fold, etc: data Shape = Polygon [Vertex] area (Polygon (v1:vs)) = polyArea vs

[Haskell-cafe] Modelling Java Interfaces with Existential data types

2004-06-08 Thread Tom Pledger
Hi. Another way is to take advantage of Haskell's laziness: class Foo a where foo :: a - Int data Oof1 = Oof1 Int instance Foo Oof1 where foo (Oof1 i) = i data Oof2 = Oof2 Int instance Foo Oof2 where foo (Oof2 i) = i list1 = [foo (Oof1 10), foo (Oof2 20)] That's all it takes. The applications

Re: [Haskell-cafe] operating on nested monads

2004-03-27 Thread Tom Pledger
Marco Righele wrote: Hello everyone, I have some operations that have to be done in sequence, with each one having the result of the previous as input. They can fail, so they have signature a - Maybe b Checking for error can be quite tedious so I use monadic operations: f :: a - Maybe b do

Re: [Haskell-cafe] Where's the error in this snippet of code?

2004-03-24 Thread Tom Pledger
Stefan Holdermans wrote: Alex, AG Ignore the layout AG I can't find the error, running it gives parse error during AG compile on pStack, it is not very descriptive and I don't AG what is wrong. Well, ignoring the layout is not a good thing here, since that's the one of the causes for your

Re: [Haskell-cafe] State Monad

2004-03-03 Thread Tom Pledger
Georg Martius wrote: [...] I could write: modifyT :: ((a, String) - (a, String)) - a - State String a modifyT trans a = do str - get let (a', str') = trans (a, str) put str' return a' f :: State String () f = do put hallo modify strTrans i -

Re: [Haskell-cafe] a rant from a stoned suicidal person

2004-03-03 Thread Tom Pledger
There are a lot of hoaxes on the internet, but just in case you're for real, here's an idea... Step 1: Take 20 minutes to get some fresh air. Step 2: When you get back to your computer, take 5 minutes to read Desiderata (http://shell.world-net.co.nz/~unikorn/desiderata.htm), especially the

Re: Partially ordered collections (revisited)

2003-11-20 Thread Tom Pledger
Graham Klyne writes: : | Ah, yes. I've grown a little wary of foldl, but I see it's | appropriate in this case. As it's part of the standard prelude, I | personally have no qualms about depending upon it ... or should I? (Hope you don't mind my returning this to haskell-cafe.) Most of

Subsumption in partially ordered sets

2003-11-17 Thread Tom Pledger
Graham Klyne writes: : | Below is some code I have written, which works, but I'm not sure | that it's especially efficient or elegant. Are there any published | Haskell libraries that contain something like this? Hi. Partially ordered sets are in cahoots with lattices, so you may be

Using field selectors in a type constructor

2003-10-14 Thread Tom Pledger
Graham Klyne writes: : | What I'd really like to do is assign it to field vbMap, and reference that | from the definition of vbEnum, but I can't figure out if there's a way | to do so. Writing this: | [[ | joinVarBindings vb1 vb2 | | vbNull vb1 = vb2 | | vbNull vb2 = vb1 |

Database interface - would like advice on oracle library binding

2003-09-23 Thread Tom Pledger
Bayley, Alistair writes: : | Still making slow progress on an Oracle database binding... now I'm trying | to fit the API I have into some sort of abstract interface (like the one(s) | discussed previously: | http://haskell.org/pipermail/haskell-cafe/2003-August/004957.html ). | | | 1.

Poll result: How to respond to homework questions

2003-09-02 Thread Tom Pledger
Hi. The stream of votes has dried up, and the ICFP people and monthly digest people have had an opportunity, so here's the collated result. 22 people voted. (A) Give a perfect answer. (B) Give a subtly flawed answer. (C) Give an obfuscated answer. (D) Give a critique of what the questioner has

Poll: How to respond to homework questions

2003-08-27 Thread Tom Pledger
Hi. I'm curious about what the people on this list consider appropriate, as responses to homework questions. Even if there isn't a consensus, it may be interesting to see how opinion is divided. Please consider the following. (A) Give a perfect answer. (B) Give a subtly flawed answer. (C) Give

Re: No safety in numbers

2003-08-21 Thread Tom Pledger
Konrad Hinsen writes: | On Thursday 21 August 2003 23:23, Jon Cast wrote: | I can make such a declaration, but it still gets converted to Double. | | How are you doing this? I'm not seeing the behavior you describe. | | module Foo where | x = 0.5 :: Fractional a = a Try x ::

RE: Database interface

2003-08-21 Thread Tom Pledger
Tim Docker writes: : | Is it normal or common to support multiple simultaneous queries on | a single DB connection? In transaction processing, yes. There's an idiom where you use one query to select all the (financial) transactions in a batch, but there's so much variation in how you need to

RE: Database interface

2003-08-20 Thread Tom Pledger
Tim Docker writes: : | The list being folded over | is implied by the DB query, is accessible through the IO monad. | Hence a parameter is not required. It would really be: | | doquery :: Process - String - b - (b - IO (b,Bool)) - IO b : | One thing that I am unsure about is whether the

RE: Database interface

2003-08-14 Thread Tom Pledger
Tim Docker writes: | Tom Pledger writes: | | This is a pretty good way to stop those nasty vague SQL row types at | the Haskell border and turn them into something respectable. Perhaps | it would even be worth constraining the extracted type to be in | DeepSeq | | doquery

Database interface

2003-08-14 Thread Tom Pledger
Thomas L. Bevan writes: | Does anyone know if there is work being done on a standard Haskell | database interface. I suspect that there isn't. The pattern seems to be that someone gets an interface working well enough for some purposes, and perhaps shares it, but is too modest and/or busy to

callbacks in Haskell

2003-06-25 Thread Tom Pledger
Robert Vollmert writes: | Hello, | | I've been having a little trouble writing a module that waits for and | handles IO events, e.g. by reading from a pipe. It seemed natural to | use some form of callbacks here, though that may very well be the | wrong approach. I'd be happy to hear of

Re: How to search for a string sequence in a file a rewrite it???

2003-03-13 Thread Tom Pledger
(moving to haskell-cafe) Alexandre Weffort Thenorio writes: | Ooops a small error before but here is the right one. | | Great. I got almost everything. My problem now is: | | I got a function called findstr where | | findstr z [,xxxxxx] = | [z,xxxzxxx]

Re: Time library underspecified

2002-11-14 Thread Tom Pledger
John Meacham writes: : | another useful thing would be | endOfTime and beginningOfTime constants, representing the minimum and | maximum values representable by ClockTime. : | ___ | Haskell mailing list | [EMAIL PROTECTED] |

Odd Performance

2002-10-22 Thread Tom Pledger
Tim Otten writes: : | Can anyone suggest why the tighter algorithm exhibits significantly | worse performance? Is takeWhile significicantly more expensive than | take? No. | Is the \z lambda expression expensive? No. | The intsqrt isn't recalculated each time takeWhile evalutes a |

Odd Performance

2002-10-22 Thread Tom Pledger
Tom Pledger writes: | Tim Otten writes: | : | | Can anyone suggest why the tighter algorithm exhibits significantly | | worse performance? Is takeWhile significicantly more expensive than | | take? | | No. Correction (before anyone else pounces on it): Only if the predicate function

Re: mutable records

2002-09-05 Thread Tom Pledger
Scott J. writes: : | Sill I want to make objects packed with their objects and | functions. Doesn't mean that I have to use existential data types? Sometimes you can avoid using existentials by making all your object-updating functions return the post-update object explicitly. For example:

Modification of State Transformer

2002-08-08 Thread Tom Pledger
Shawn P. Garbett writes: : | What I want is something like this, so that the state transformer has a | generic state type: | | newtype St a s = MkSt (s - (a, s)) | | apply :: St a s - s - (a, s) | apply (MkSt f) s = f s | | instance Monad St where | return x = MkSt

typeclass versioning

2002-06-12 Thread Tom Pledger
From: Cagdas Ozgenc [EMAIL PROTECTED] | Greetings. | | What happens if a type is made an instance of a typeclass in two | different modules with different implementations? That's OK, provided that the two instance declarations are never in scope together, i.e. neither of the modules imports

Is there a name for this structure?

2002-03-26 Thread Tom Pledger
Joe English writes: : | Suppose you have two morphisms f : A - B and g : B - A | such that neither (f . g) nor (g . f) is the identity, | but satisfying (f . g . f) = f. Is there a conventional name | for this? Is it equivalent to saying that (f . g) is the identity on the range of f?

typeclasses

2002-03-24 Thread Tom Pledger
Cagdas Ozgenc writes: | Greetings. | | How can I make all types that belong to class A and instance of | class B, if the implementations of functions in class B can be | realized by only using the functions in class A? | | Thanks for taking time. Something like this, you mean?

Question about something in Hudak's book

2002-03-12 Thread Tom Pledger
Ludovic Kuty writes: : | Is it an idiom or some sort of optimization ? It's more to do with the particular algorithm for finding the area of a convex polygon. Try working through the calculation of the area of this kite. Polygon [(0, 0), (1, 0), (2, 2), (0, 1)] I think the two versions

Lazy Evaluation

2002-03-03 Thread Tom Pledger
Nguyen Phan Dung writes: : | mylist :: [Integer] | mylist = [1..10] | | In Hugs, I type mylist to print out all the elements inside. However, | after printing about 22000 elements, the system crashs outputs: | Garbage collection fails to reclaim sufficient memory The declaration

higher-kind deriving ... or not

2002-02-26 Thread Tom Pledger
C T McBride writes: : | A little more tinkering, and it looks like it might be | | show :: Show (f (Wonky f)) = Wonky f - String | | Is this really the type of show? That looks correct to me. | If so, no wonder there's a problem. Yes, there's a vicious circle in context reduction,

higher-kind deriving ... or not

2002-02-26 Thread Tom Pledger
Tom Pledger writes: | C T McBride writes: | : | | A little more tinkering, and it looks like it might be | | | | show :: Show (f (Wonky f)) = Wonky f - String | | | | Is this really the type of show? | | That looks correct to me. Well, after the first context reduction

Haskell problem

2002-02-20 Thread Tom Pledger
Mark Wotton writes: | 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 = |

Why is there a space leak here?

2001-05-28 Thread Tom Pledger
David Bakin writes: : | I have been puzzling over this for nearly a full day (getting this | reduced version from my own code which wasn't working). In | general, how can I either a) analyze code looking for a space leak | or b) experiment (e.g., using Hugs) to find a space leak? Thanks!

Re: Why is there a space leak here?

2001-05-28 Thread Tom Pledger
Michal Gajda writes: | On Tue, 29 May 2001, Tom Pledger wrote: : | When you consume the (3N)th cell of v, you can't yet garbage collect | the Nth cell because it will be needed for generating the (3N+1)th, | (3N+2)th and (3N+3)th. | | So, as you proceed along the list, about two

RE: Functional programming in Python

2001-05-24 Thread Tom Pledger
Peter Douglass writes: : | but in ( foo ( bar (baz x) ) ) | | You would want the following I think. | | foo . bar . baz x | | which does have the parens omitted, but requires the composition | operator. Almost. To preserve the meaning, the composition syntax would need to be

Things and limitations...

2001-05-14 Thread Tom Pledger
Juan Carlos Arevalo Baeza writes: : | First, about classes of heavily parametric types. Can't be done, I | believe. At least, I haven't been able to. What I was trying to do (as an | exercise to myself) was reconverting Graham Hutton and Erik Meijer's | monadic parser library into a

Novice question

2001-04-22 Thread Tom Pledger
Mark Carroll writes: | Is this a good place for novice questions? Yes, either here or on http://haskell.org/wiki/wiki | greaterthan 0 _ _ = False | greaterthan _ (x:xs) (y:ys) = x y : | Main greaterthan 0 [] [] | ERROR: Unresolved overloading | *** Type : Ord a = Bool | ***

Question about typing

2001-04-05 Thread Tom Pledger
Toby Watson writes: | Intuitively the following scenarios seem to be related, can anyone | point my in the direction of formal work on this, or give me the | formal terms I need to search around? | | 1. Adding two integers together: Int - Int - Int | | 2. Adding two lists of Integers

making a Set

2001-02-22 Thread Tom Pledger
(moved to haskell-cafe) G Murali writes: | hi there, | | I'm tryng to get my concepts right here.. can you please help in | defining a funtion like | | makeSet :: (a-Bool)-Set a | | I understand that we need a new type Set like | data Set a = Set (a-Bool) what puzzles me is how to

need help w/ monad comprehension syntax

2001-02-15 Thread Tom Pledger
Konst Sushenko writes: | what am i missing? : | --g :: State String Char | g = [ x | x - return 'a' ] Hi. The comprehension syntax used to be for monads in general (in Haskell 1.4-ish), but is now (Haskell 98) back to being specific to lists. Does it help if you use do-notation instead?

Re: Revamping the numeric classes

2001-02-11 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: | Fri, 9 Feb 2001 17:29:09 +1300, Tom Pledger [EMAIL PROTECTED] pisze: | | (x + y) + z | | we know from the explicit type signature (in your question that I was | responding to) that x,y::Int and z::Double. Type inference does not | need

Re: A sample revised prelude for numeric classes

2001-02-11 Thread Tom Pledger
Brian Boutel writes: : | Having Units as types, with the idea of preventing adding Apples to | Oranges, or Dollars to Roubles, is a venerable idea, but is not in | widespread use in actual programming languages. Why not? There was a pointer to some good papers on this in a previous

Re: Revamping the numeric classes

2001-02-08 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: | On Thu, 8 Feb 2001, Tom Pledger wrote: | | nice answer: give the numeric literal 10 the range type 10..10, which | is defined implicitly and is a subtype of both -128..127 (Int8) and | 0..255 (Word8). | | What are the inferred types for | f

Re: Revamping the numeric classes

2001-02-07 Thread Tom Pledger
Dylan Thurston writes: : | (A question in the above context is whether the literal '0' should | be interpreted as 'fromInteger (0::Integer)' or as 'zero'. | Opinions?) Opinions? Be careful what you wish for. ;-) In a similar discussion last year, I was making wistful noises about

Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Tom Pledger
Ashley Yakeley writes: At 2001-01-16 13:18, Magnus Carlsson wrote: f1 = Just 3 f2 = f3 = f4 = Nothing So I've declared b = d, but 'theValue b' and 'theValue d' are different because theValue is looking at the static type of its argument? What's to stop 'instance TheValue

Re: combinator parsers and XSLT

2000-10-01 Thread Tom Pledger
Manuel M. T. Chakravarty writes: Lars Henrik Mathiesen [EMAIL PROTECTED] wrote, From: "Manuel M. T. Chakravarty" [EMAIL PROTECTED] Date: Fri, 29 Sep 2000 10:17:56 +1100 I agree that usually the predicates as proposed by you would be better. The problem is that a scanner