Re: [Haskell-cafe] Difference lists and ShowS (Was: The Worker/Wrapper Transformation)

2008-01-03 Thread Tillmann Rendel
Henning Thielemann wrote: Sometimes I believed that I understand this reason, but then again I do not understand. I see that left-associative (++) like in ((a0 ++ a1) ++ a2) ++ a3 would cause quadratic time. But (++) is right-associative and 'concat' is 'foldr'. They should not scan the

Re: [Haskell-cafe] Knowledge

2007-12-20 Thread Tillmann Rendel
jlw501 wrote: I'm new to functional programming and Haskell and I love its expressive ability! I've been trying to formalize the following function for time. Given people and a piece of information, can all people know the same thing? Anyway, this is just a bit of fun... but can anyone help me

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Tillmann Rendel
david48 wrote: class Gadget g where fInit :: g - a - g data FString = FString !Int !String deriving Show instance Gadget FString where at this point fInit has this type: FString - a - FString fInit (FString n _) s = FString n (take n s) but your implementation has this type

Re: [Haskell-cafe] instance Monad Either?

2007-12-20 Thread Tillmann Rendel
Eric wrote: According to this http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? Try to import Control.Monad.Error to get a Monad instance for

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Tillmann Rendel
Felipe Lessa wrote: class Shape a where whatever class (Shape a, Shape b) = Intersectable a b where intersect :: a - b - Bool This looks nice at first sight, but is it usefull in practice? I can somehow express the type any shape wich is intersectable with a given other shape,

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Tillmann Rendel
insertjokehere wrote: --A parser for recognising binary operations parseBinaryOp :: String - String - [(Expr, Expr, String)] parseBinaryOp op str | (elem op binops) (notElem '(' (snd bm)) (notElem ')' (snd bm)) (elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)] You want (elem (nstr

Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tillmann Rendel
Hi Tommy, detab is one of the programs I do not like. I kept the direct translation approach up through that, but I think it really hides the simplicity there; detab copies its input to its output replacing tabs with 1-8 spaces, based on where the tab occurs in a line. The only interesting

Re: [Haskell-cafe] Hoogle works once more

2007-12-06 Thread Tillmann Rendel
Dougal Stanton wrote: Is there a way to search on module names? If I put in Data.Map then the one thing that doesn't come up is a link to the library page for Data.Map. That would be a really good short-cut. You can already search for unqualified module names:

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Tillmann Rendel
Andrew Coppin wrote: *thinks* Conjecture #1: All nontrivial properties of a computer program are undecidable in general. That is the well-known Rice's theorem. (A very handy one in exams about theoretical computer science, since you can smash so many questions with follows from Rice).

Re: [Haskell-cafe] Searched for mdo on haskell.org. Found nothing.

2007-11-22 Thread Tillmann Rendel
Hi Andrew, Andrew Coppin wrote: In general, I find *most* search functions to be fairly unhelpful. Google is the shining exception to this rule; it almost always seems to figure out what you're after. I guess doing text searching is just a fundamentally difficult problem, and the guys at

Re: [Haskell-cafe] newbie optimization question

2007-10-28 Thread Tillmann Rendel
= 0; for (int j = 1; j i; j++) if (i % j == 0) sum += i; if (sum == i) print(i); } Loops can be expressed with lazy lists in Haskell. Therefore, the presented Haskell program is perfectly equivalent to the obvious c program. Tillmann Rendel

Re: [Haskell-cafe] Re: [Off topic] Proving an impossibility

2007-09-04 Thread Tillmann Rendel
Vimal wrote: Ah, yes, it is possible in this case, but you have used an extra variable. It is okay, but our professor doesnt want to put emphasis on Computability here (or maybe I dont realize it), but the point is: Are such programming constructs really necessary in a programming language? i.e.

Re: [Haskell-cafe] Re: Explaining monads

2007-08-13 Thread Tillmann Rendel
David Roundy wrote: It's the *effect* of a monad, not the *side* effect. The type of = defines this dependency. And when you have a chain of dependencies, that is sometimes referred to as a sequence. True, it's not mystical, but it's still sequenced. How can a Haskell type define a data

Re: [Haskell-cafe] Explaining monads

2007-08-12 Thread Tillmann Rendel
Ronald Guida wrote: Here's a toy language, described by a regular expression: 0(10)*110 I want to read characters, one at a time, and eventually decide to Accept or Reject a string. Let me try to understand my options. * With a simple Arrow, I can create a fixed sequence of read

Re: [Haskell-cafe] where to put handy functions?

2007-08-10 Thread Tillmann Rendel
Chad Scherrer wrote: extract :: [Int] - [a] - [a] [...] This behaves roughly as extract ns xs == map (xs !!) ns extract sounds like removing the elements to be extracted from the original list. I would therefore expect it's type signature to be extract :: [Int] - [a] - ([a], [a]) with

Re: [Haskell-cafe] mutually recursive types

2007-08-08 Thread Tillmann Rendel
Rodrigo wrote: type Scenario = (String, String, [Step]) type Step = (String, Scenario, String, String, String) Recursive types are not supported by type-declarations. use data declarations instead: data Scenario = Scenario String String [Step] data Step = Step String Scenario String

Re: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread Tillmann Rendel
peterv wrote: I’m having difficulty to understand what phantom types are good for. I read the wiki, and it says this is useful if you want to increase the type-safety of your code, but the code below does not give a compiler error for the function test1, I get a runtime error, just like test2.

Re: [Haskell-cafe] Type classes: Missing language feature?

2007-08-07 Thread Tillmann Rendel
DavidA wrote: Now, what I'd like to do is have Lex and Glex, and any further monomial orderings I define later, automatically derive Show and Num instances from Monomial (because it seems like boilerplate to have to define Show and Num instances by hand). Something like the following (not

Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread Tillmann Rendel
peterv schrieb: In de book Modern C++ design, Andrei Alexandrescu writes that Haskell supports “multi-methods” http://books.google.com/books?id=aJ1av7UFBPwCpg=PA3ots=YPiJ_nWi6Ydq=moder n+C%2B%2Bsig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1 Chapter 11, Page 263 of this books: The C++ virtual

Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Tillmann Rendel
Stefan O'Rear wrote: Out of curiousity, what do you find objectionable about (legal): function argument argument2 | guard = body | guard = body as compared to (currently illegal): function argument argument2 | guard = body | guard = body I see the vertical strokes as visually lining up,

Re: [Haskell-cafe] Speedy parsing

2007-07-19 Thread Tillmann Rendel
Re, Joseph (IT) wrote: At this point I'm out of ideas, so I was hoping someone could identify something stupid I've done (I'm still novice of FP in general, let alone for high performance) or direct me to a guide,website,paper,library, or some other form of help. Two ideas about your

Re: [Haskell-cafe] Is this haskelly enough?

2007-07-18 Thread Tillmann Rendel
) guarding p x = guard (p x) return x If you want to decide in the mapped function how many elements to consume, you can use unfoldr directly. Tillmann Rendel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

Re: [Haskell-cafe] Evaluation of IO actions in record assignment

2007-07-09 Thread Tillmann Rendel
Adde wrote: signatureEntry - xmlGetWidget xml castToEntry signatureEntry passwordEntry - xmlGetWidget xml castToEntry passwordEntry repeatEntry - xmlGetWidget xml castToEntry repeatEntry return UserPanel {userPanelSignatureEntry = signatureEntry, userPanelPasswordEntry =

Re: [Haskell-cafe] Fun with ByteStrings [was: A very edgy language]

2007-07-08 Thread Tillmann Rendel
Andrew Coppin wrote: Now, as I understand it, a ByteString is a kind of unboxed array (= big RAM savings + big CPU time savings for not building it + big GC savings for not processing millions of list nodes + better cache performance). Or at least, a *strict* ByteString is; I'm very very

Re: [Haskell-cafe] A very nontrivial parser

2007-07-08 Thread Tillmann Rendel
Andrew Coppin wrote: Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But it would be nice to know what they *are*... :-S (Thus far, they just seem to be some incomprehensible syntax that makes the compiler stop complaining. In particular, I have no idea what the

Re: [Haskell-cafe] Re: Reinvention

2007-06-27 Thread Tillmann Rendel
Andrew Coppin wrote: But IIRC the Parsec library supports parsing of arbitrary tokens (although presumably they have to be in Eq?) so maybe I should revise that... They don't have be in Eq, because you supply your own token tests, using the token or tokenPrim functions. Tillmann

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Tillmann Rendel
Levi Stephen wrote: newtype Identifier = Identifier String newtype Literal = StringLiteral String -- to be extended later data Primary = PrimaryLiteral Literal | PrimaryIdentifier Identifier primary = do { i - identifier; return $ PrimaryIdentifier i; } | do { l -

Re: [Haskell-cafe] Collections

2007-06-21 Thread Tillmann Rendel
Andrew Coppin wrote: I don't even understand that... :-S Ok, I'll try to explain it: I represent sets by their characteristic function, wich returns True for members of the set, and False for other values. type Set a = a - Bool For example, the set of numbers containing only 42 is

Re: [Haskell-cafe] Collections

2007-06-20 Thread Tillmann Rendel
Andrew Coppin wrote: [...] type (a,b) [...] That's a rather special type; I haven't seen anything remotely like it in any other language. This type isn't that special in Haskell (apart from being syntax-sugared), it could be defined as data Pair a b = Pair a b The equivalent of this

Re: [Haskell-cafe] Re: Parsec problem

2007-06-06 Thread Tillmann Rendel
Neil Mitchell wrote: The code is at: http://www.cs.york.ac.uk/fp/darcs/hoogle/src/Hoogle/Query/Parser.hs My guess: names can never fail, so types is never tried, and eof fails. Tillmann ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Newbie Q: Monad 'fail' and 'error'

2007-06-06 Thread Tillmann Rendel
Dmitri O.Kondratiev wrote: Monad class contains declaration *fail* :: String - m a and provides default implementation for 'fail' as: fail s = error s On the other hand Prelude defines: * error* :: String - a which stops execution and displays an error message. Questions: 1) What value and

Re: [Haskell-cafe] I saw this... and thought of you

2007-06-06 Thread Tillmann Rendel
Andrew Coppin wrote: http://dis.4chan.org/read/prog/1180896798/ (It's been a while since I touched Java, and I must confess I can't even comprehend this code...) Look's like a bad done extension of the well-known function object pattern in oo design to allow currying. I would prefer the

Re: [Haskell-cafe] What puts False before True?

2007-06-05 Thread Tillmann Rendel
Tony Finch wrote: Another point worth noting is that the usual lambda calculus representations of false and zero are equivalent. (However true is not the same as one.) Looking at Church encoding, false = zero true = something else may be a point for false true, but true = curry fst

Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Tillmann Rendel
Hello, Phlex wrote: changePlanetAge universe galaxy planet age = ...lots of code, returning a new universe And the same code for all functions updating any of the properties of my planet ... And the same code for all functions updating properties of a country on this planet... In functional

Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Tillmann Rendel
Hello, Ketil Malde wrote: Makes me wonder whether one should have binary be the default? I'm a stranger in Windows-land, but are there cases where you want reading of a file to be terminated on ^Z? Seems pretty awful to me. The ghc docs state about openBinaryFile: Like openFile, but open

Re: [Haskell-cafe] Help with Programming in Haskell example

2007-05-18 Thread Tillmann Rendel
Hello, Andre Nathan schrieb: so I'm wondering what else I need to do for the do notation to work. import Prelude hiding ((=), return) You explicitly ask for the well-known and standard functions = and return to be hidden away, because you want to define your own versions. p :: Parser

Re: [Haskell-cafe] Newbie seeking advice regarding data structure for a tricky algorithm

2007-04-24 Thread Tillmann Rendel
Hi, Toby Hutton wrote: Say I want to put the words 'foo', 'bar' and 'baz' into a binary tree. The heuristic requires I split the words into letters and sort them: 'aabbfoorz'. The heuristic then may decide, based on the sorted letters, that 'bar' and 'foo' should go in the left child and

Re: [Haskell-cafe] How Albus Dumbledore would sell Haskell

2007-04-20 Thread Tillmann Rendel
Mirko Rahn wrote: More important: Correct me, if I'm wrong, but as far as I understand java, it is still impossible in your solution to evaluate the equivalent of head $ mirror $ rel [ (i,i) | i - [0..] ] in finite time, that is, your MirrorRel is not lazy in the elements. You have to build

<    1   2   3