[Haskell-cafe] A voyage of undiscovery
2009/7/17 Andrew Coppin andrewcop...@btinternet.com: I've been working hard this week, and I'm stumbled upon something which is probably of absolutely no surprise to anybody but me. Consider the following expression: (foo True, foo 'x') Is this expression well-typed? Astonishingly, the answer depends on where foo is defined. If foo is a local variable, then the above expression is guaranteed to be ill-typed. However, if we have (for example) foo :: x - x as a top-level function, then the above expression becomes well-typed. Some useful reading material: Section 22.7 of the book Types and Programming Languages by Benjamin Pierce. The classic paper Basic Polymorphic Typechecking by Luca Cardelli: http://lucacardelli.name/Papers/BasicTypechecking.pdf Both of these are very readable introductions to the let-style polymorphism found in the Hindley/Milner type system. Haskell's type system is essentially an elaboration of that idea. Pierce's book shows how to achieve let-polymorphism by inlining non-recursive let bindings during type checking/inference, which is a nice way to understand what is going on. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Parallellizing array-based function
Is it possible to parallelize array-based functions such as in-place quicksort in Haskell? If so, does anyone have a working implementation? -- Dr Jon Harrop, Flying Frog Consultancy Ltd. http://www.ffconsultancy.com/?e ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] PEPM'10 - Call for Papers (Deadline: 6 Oct 09) - Invited Speakers announced
=== CALL FOR PAPERS ACM SIGPLAN 2010 Workshop on Partial Evaluation and Program Manipulation (PEPM'10) Madrid, January 18-19, 2010 (Affiliated with POPL'10) http://www.program-transformation.org/PEPM10 === INVITED SPEAKERS: * Lennart Augustsson (Standard Chartered Bank, UK) * Jeremy Siek (University of Colorado at Boulder, USA) IMPORTANT DATES: * Paper submission:Tue, October 6, 2009, 23:59, Apia time * Author notification: Thu, October 29, 2009 * Camera-ready papers: Mon, November 9, 2009 To facilitate smooth organization of the review process, authors are asked to submit a short abstract by October 1, 2009. SUBMISSION CATEGORIES: * Regular research papers (max. 10 pages in ACM Proceedings style) * Tool demonstration papers (max. 4 pages plus max. 6 pages appendix) TRAVEL SUPPORT: Students and other attendants in need can apply for a SIGPLAN PAC grant to help cover expenses. For details, see http://www.sigplan.org/PAC.htm. SCOPE: The PEPM Symposium/Workshop series aims to bring together researchers and practitioners working in the areas of program manipulation, partial evaluation, and program generation. PEPM focuses on techniques, theories, tools, and applications of analysis and manipulation of programs. The 2010 PEPM workshop will be based on a broad interpretation of semantics-based program manipulation in a continued effort to expand the scope of PEPM significantly beyond the traditionally covered areas of partial evaluation and specialization and include practical applications of program transformations such as refactoring tools, and practical implementation techniques such as rule-based transformation systems. In addition, it covers manipulation and transformations of program and system representations such as structural and semantic models that occur in the context of model-driven development. In order to reach out to practitioners, there is a separate category of tool demonstration papers. Topics of interest for PEPM'10 include, but are not limited to: * Program and model manipulation techniques such as transformations driven by rules, patterns, or analyses, partial evaluation, specialization, program inversion, program composition, slicing, symbolic execution, refactoring, aspect weaving, decompilation, and obfuscation. * Program analysis techniques that are used to drive program/model manipulation such as abstract interpretation, static analysis, binding-time analysis, dynamic analysis, constraint solving, type systems, automated testing and test case generation. * Analysis and transformation for programs/models with advanced features such as objects, generics, ownership types, aspects, reflection, XML type systems, component frameworks, and middleware. * Techniques that treat programs/models as data objects including meta-programming, generative programming, deep embedded domain-specific languages, program synthesis by sketching and inductive programming, staged computation, and model-driven program generation and transformation. * Application of the above techniques including experimental studies, engineering needed for scalability, and benchmarking. Examples of application domains include legacy program understanding and transformation, DSL implementations, visual languages and end-user programming, scientific computing, middleware frameworks and infrastructure needed for distributed and web-based applications, resource-limited computation, and security. We especially encourage papers that break new ground including descriptions of how program/model manipulation tools can be integrated into realistic software development processes, descriptions of robust tools capable of effectively handling realistic applications, and new areas of application such as rapidly evolving systems, distributed and web-based programming including middleware manipulation, model-driven development, and on-the-fly program adaptation driven by run-time or statistical analysis. PROCEEDINGS: There will be formal proceedings published by ACM Press. In addition to printed proceedings, accepted papers will be included in the ACM Digital Library. Selected papers may later on be invited for a journal special issue dedicated to PEPM'10. SUBMISSION GUIDELINES: Papers should be submitted electronically via the workshop web site. Regular research papers must not exceed 10 pages in ACM Proceedings style. Tool demonstration papers must not exceed 4 pages in ACM Proceedings style, and authors will be expected to present a live demonstration of the described tool at the workshop (tool papers should include an additional appendix of up to 6 extra pages giving the outline, screenshots, examples, etc. to indicate the content of the proposed live demo at
Re: [Haskell-cafe] Parsec for C or C++
There is a C++ parser in C++, it may be of help : http://42ndart.org/scalpel/ It's a quite advanced WIP. On Fri, Jul 17, 2009 at 3:58 AM, Sterling Clover s.clo...@gmail.com wrote: A parser for JavaScript (admittedly a much simpler beast) is part of Brown's WebBits: http://hackage.haskell.org/packages/archive/WebBits/0.15/doc/html/ BrownPLT-JavaScript-Parser.html Cheers, Sterl. On Jul 16, 2009, at 1:40 PM, Roy Lowrance wrote: Turns out that Language.C uses alex and happy. I'm looking to use Parsec. So back to the original question: Does anyone know of a C or java parser written using Parsec? - Roy On Thu, Jul 16, 2009 at 12:43 PM, Roy Lowranceroy.lowra...@gmail.com wrote: Thanks Rick. A perfect tip! - Roy On Thu, Jul 16, 2009 at 12:29 PM, Rick Rrick.richard...@gmail.com wrote: There is language.c http://www.sivity.net/projects/language.c/ http://hackage.haskell.org/package/language-c From a parsing standpoint, C++ is a massive departure from C. Good luck though. On Thu, Jul 16, 2009 at 12:25 PM, Roy Lowrance roy.lowra...@gmail.com wrote: I am working on a research language that is a variant of C. I'd like to use Parsec as the parser. Is there an existing Parsec parser for C or C++ (or Java) that could serve as a starting point? Thanks, Roy ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- The greatest obstacle to discovering the shape of the earth, the continents, and the oceans was not ignorance but the illusion of knowledge. - Daniel J. Boorstin -- Roy Lowrance home: 212 674 9777 mobile: 347 255 2544 -- Roy Lowrance home: 212 674 9777 mobile: 347 255 2544 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Alp Mestan http://blog.mestan.fr/ http://alp.developpez.com/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
on haskell reddit today powerSet = filterM (const [True, False]) is said to be beautiful / mind blowing. I just don't get it. I can play with transformations until I get powerSet [] = [[]] powerSet (x:xs) = let pxs = powerSet xs in map (x:) pxs ++ pxs which is understandable to me, but no matter how long I look at the original filterM definition it just doesn't click. Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense? If anybody agrees with me, care to throw out other examples of obfuscated haskell considered harmful? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
On Fri, Jul 17, 2009 at 1:35 AM, Thomas Hartman tphya...@gmail.com wrote: on haskell reddit today powerSet = filterM (const [True, False]) The M is the list, i.e. *nondeterminism* monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False). Basically, regular filter says that for each element in the list, we need to make a choice as to whether it occurs in the result. Here we use nondeterminism to make both choices. Luke is said to be beautiful / mind blowing. I just don't get it. I can play with transformations until I get powerSet [] = [[]] powerSet (x:xs) = let pxs = powerSet xs in map (x:) pxs ++ pxs which is understandable to me, but no matter how long I look at the original filterM definition it just doesn't click. Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense? If anybody agrees with me, care to throw out other examples of obfuscated haskell considered harmful? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
For each item, we ignore what the item actually is (hence `const`), and say that we both want it (True) and don't want it (False) in the output. Since we are using the list monad we are allowed to say this, and the filter function gives us a list of lists. I think there's probably a more intuitive name for `filterM`... ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
Thomas Hartman wrote: on haskell reddit today powerSet = filterM (const [True, False]) Does it help if we inline the 'const' function and rewrite [True, False] in monadic notation as (return True `mplus` return False)? powerSet = filterM (\x - return True `mplus` return False). You can see that 'x' is ignored, both True and False are returned, hence x is preserved in one answer and not preserved in another. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Python vs Haskell in tying the knot
Thank you all for your answers and sorry for the delay I'm writing this message but before replying, I wanted to be sure to understand your arguments! Now, I'm starting to get into this tying the knot thing and understand why the Haskell version of fib ties the knot while my Python version does not. It seems all related to the thunk thing, i.e. in the Haskell version the subsequent calls to fib are not actual calls because they all refers to the same thunk, which is evaluated on demand. Now, to confirm my hypothesis, I wrote a slight different version of fib, like follows: fib' n = 1:1:(fib' n) `plus` (tail $ fib' n) where plus = zipWith (+) i.e. I inserted a fictious argument n in the definition of fib'. Now, if I try take 30 $ fib' 100, it takes significntly longer than take 30 fib: specifically, the latter is instantaneous, while the former takes about 5 seconds to complete on my MacBook Pro. Is this an evidence that the tying the knot process is going on in the first version? More, I've read that a fully lazy language would memoize all functions by default: in this case, even fib' would have been tying the knot. But this is not the case of Haskell. Am I wrong? Thank you, Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Python vs Haskell in tying the knot
On 17 Jul 2009, at 12:41, Cristiano Paris wrote: Thank you all for your answers and sorry for the delay I'm writing this message but before replying, I wanted to be sure to understand your arguments! Now, I'm starting to get into this tying the knot thing and understand why the Haskell version of fib ties the knot while my Python version does not. It seems all related to the thunk thing, i.e. in the Haskell version the subsequent calls to fib are not actual calls because they all refers to the same thunk, which is evaluated on demand. Now, to confirm my hypothesis, I wrote a slight different version of fib, like follows: fib' n = 1:1:(fib' n) `plus` (tail $ fib' n) where plus = zipWith (+) i.e. I inserted a fictious argument n in the definition of fib'. Now, if I try take 30 $ fib' 100, it takes significntly longer than take 30 fib: specifically, the latter is instantaneous, while the former takes about 5 seconds to complete on my MacBook Pro. Is this an evidence that the tying the knot process is going on in the first version? That's correct More, I've read that a fully lazy language would memoize all functions by default: in this case, even fib' would have been tying the knot. But this is not the case of Haskell. Am I wrong? Memoization is not a feature of lazyness. If you can do it in such a way that you don't waste significant amount of RAM, then it may be a nice optimisation, and an alternative evaluation strategy, but it would not be lazy. Bob ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
On Jul 17, 2009 1:40pm, Thomas Hartman wrote: my question to all 3 (so far) respondants is, how does your explanation explain that the result is the power set? I guess you forgot to reply to the cafe. Well, to me the modified definition I posted looks like the essence of powerset, the set of all subsets. Every element x of the input list divides the powerset in 2 halves, the first one contains x, the second one doesn't. Filtering on the non-deterministic predicate (\x - return True `mplus` return False) in the List monad does exactly that. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] laziness blowup exercise
On Thu, Jul 16, 2009 at 9:57 PM, Ryan Ingramryani.s...@gmail.com wrote: On Thu, Jul 16, 2009 at 8:22 PM, Thomas Hartmantphya...@gmail.com wrote: Is this being worked on? On Thu, Jul 16, 2009 at 12:35 PM, Bas van Dijkv.dijk@gmail.com wrote: I have no idea. Yes. Bolingbroke, Peyton-Jones. Types are calling conventions http://lambda-the-ultimate.org/node/3319 Thanks for the pointer to this interesting paper! However I dont't think that the type system explained in that paper is powerful enough to differentiate between these different iterates: iterate1, iterate2, iterate3, iterate4 :: (a - a) - a - [a] iterate1 f x = x : let nxt = f x in iterate1 f nxt iterate2 f x = let nxt = f x in nxt `seq` x : iterate2 f nxt iterate3 f x = x `seq` x : let nxt = f x in iterate3 f nxt iterate4 f x = x : let nxt = f x in nxt `seq` iterate4 f nxt The type system somehow has to express the growing and shrinking of the stack so that it can statically disallow: iterate1 (+ 1) 0 !! (10^6) :: Int fits in my stack and allow: iterate4 (+ 1) 0 !! (10^6) :: Int fits in my stack Bas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why is there no Zippable class? Would this work?
Job Vranish wrote: I was needing a way to zip generic data structures together today and was very annoyed to find that there is no Zippable class, or variant there of. Notice that you can always do this if the LHS is traversable and the RHS is Foldable (as a special case the RHS is the same as the LHS, since all foldables are traversable) : http://www.haskell.org/haskellwiki/Foldable_and_Traversable#Generalising_zipWith ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Python vs Haskell in tying the knot
On Fri, Jul 17, 2009 at 12:46 PM, Thomas Davietom.da...@gmail.com wrote: Memoization is not a feature of lazyness. If you can do it in such a way that you don't waste significant amount of RAM, then it may be a nice optimisation, and an alternative evaluation strategy, but it would not be lazy. Thank you for pointing out. I'd like to share this link to a useful article about circular programming, which helped me a lot: http://www.csse.monash.edu.au/~lloyd/tildeFP/1989SPE/ Thank you again. Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
2009/7/17 Gleb Alexeyev gleb.alex...@gmail.com: On Jul 17, 2009 1:40pm, Thomas Hartman wrote: my question to all 3 (so far) respondants is, how does your explanation explain that the result is the power set? Because powerset(s) = 2^s? I was going to make some nice code but I ended up with this monster :D {-# LANGUAGE ScopedTypeVariables #-} import Control.Monad -- a more generic if gif p t f | p == maxBound = t | otherwise = f -- this is filterM, but with the generic if collect _ [] = return [] collect p (x:xs) = do flg - p x ys - collect p xs return (gif flg (x:ys) ys) -- just changed if - gif -- list exponentiation -- first parameter is fake, just to get an 'a' expSet :: forall a b. (Bounded a, Enum a, Eq a) = a - [b] - [[b]] expSet _a = collect (\_- values :: [a]) values :: (Bounded a, Enum a) = [a] values = enumFromTo minBound maxBound data Trool = Un | Deux | Trois deriving (Bounded, Enum, Eq, Show) trool = undefined :: Trool bool = undefined :: Bool powerset = expSet bool I feel dirty :P signature.asc Description: OpenPGP digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Python vs Haskell in tying the knot
On Fri, Jul 17, 2009 at 12:41 PM, Cristiano Parisfr...@theshire.org wrote: ... Now, to confirm my hypothesis, I wrote a slight different version of fib, like follows: fib' n = 1:1:(fib' n) `plus` (tail $ fib' n) where plus = zipWith (+) i.e. I inserted a fictious argument n in the definition of fib'. Now, if I try take 30 $ fib' 100, it takes significntly longer than take 30 fib: specifically, the latter is instantaneous, while the former takes about 5 seconds to complete on my MacBook Pro. Is this an evidence that the tying the knot process is going on in the first version? BTW, after a -O2 compilation, fib' is apparently as fast a fib. Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
Thomas Hartman wrote: on haskell reddit today powerSet = filterM (const [True, False]) is said to be beautiful / mind blowing. Is this a uniquely haskell obfu, or is there a way of reading this definition that makes sense? To me, these are more obvious: powerSet = map catMaybes . mapM ((mzero:).return.return) powerSet = map concat . mapM ((mzero:).return.return) They work by pretty much the same principle. Perhaps they seem simpler to me only because I use mapM a lot more than I use filterM. Regards, Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Line drawing algorithm
Hi All, I am working on a diagraming utility in Haskell. I started with line drawing. I am doing the basic stuff using the y = mx + c formula to draw a line between (x1,y1) and (x2,y2) Here's what I need to do - if dx dy where dx = (x2 - x1) and dy = (y2 - y1) then I need to vary x between x1 and x2 and find the various y's however if dy dx then I need to vary y beteen y1 and y2 and get various x's In the code below, I've only taken care of the situation where dx dy - I was thinking if there was a better way to do it that takes care of the other condition as well without repeating the code. type Point = (Integer,Integer) line :: Point - Point - [Point] -- get all the points in the line line p1@(x1,y1) p2@(x2,y2) = line' start end start slope where (start,end) = reorderPoints p1 p2 slope = ((fromIntegral (y2-y1)) / (fromIntegral (x2-x1))) reorderPoints (px1,py1) (px2,py2) | px1 px2 = (p1,p2) | otherwise = (p2,p1) line' :: Point - Point - Point - Double - [Point] line' start@(x1,y1) end@(x2,y2) point@(x3,y3) slope | x3 == x2 = [end] | otherwise = [point] ++ line' start end (newX,newY) slope where newX = x3 + 1 newY = y1 + round (slope * (fromIntegral (newX - x1))) hello = line (1,1) (10,10) Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Line drawing algorithm
CK Kashyap wrote: Hi All, I am working on a diagraming utility in Haskell. I started with line drawing. I am doing the basic stuff using the y = mx + c formula to draw a line between (x1,y1) and (x2,y2) Hi, Are you doing this to learn Haskell, learn about drawing lines, or to just get it implemented? If either of the latter two, when drawing a straight line you shouldn't need to do floating point operations such as this: newY = y1 + round (slope * (fromIntegral (newX - x1))) Bresenham's algorithm (or similar variants) allows you to draw a line without needing floating point. A Haskell implementation is here: http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell Although it may not be too understandable! Wikipedia has an explanation of the general algorithm: http://en.wikipedia.org/wiki/Bresenham%27s_line_algorithm As to how to cope with the dy dx case in your code given the dx dy case, you could just swap the x and y coords at the start, then swap back the x and y coords of all the output points afterwards. Odd, but effective :-) Thanks, Neil. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Line drawing algorithm
Thanks Neil ... Are you doing this to learn Haskell, learn about drawing lines, or to just get it implemented? If either of the latter two, when drawing a straight line you shouldn't need to do floating point operations such as this: Actually, my reasons are first and third. newY = y1 + round (slope * (fromIntegral (newX - x1))) http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell Thanks for the link. As to how to cope with the dy dx case in your code given the dx dy case, you could just swap the x and y coords at the start, then swap back the x and y coords of all the output points afterwards. Odd, but effective :-) Slope would differ right for both case right? Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Python vs Haskell in tying the knot
BTW, after a -O2 compilation, fib' is apparently as fast a fib. The compiler is your friend. :o) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Alternative IO
Am Freitag, 10. Juli 2009 23:41 schrieben Sie: On Jul 10, 2009, at 4:35 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 empty | g = g This implies the following: (f empty) | g = g But this wouldn’t hold with your instance. (f empty) | g would cause the side effects of f and of g, while g would (obviously) only cause the side effects of g. I think the third equality you provide is too strong (which isn't to say that it might not be the law that people have documented and expect). Lots of useful alternative instances fail it, not least any parser combinator library (such as Parsec) without automatic backtracking. Really? The third equality is required since Alternative instances have to be monoids with empty as the neutral element and (|) as composition. […] Additionally, the second equality you provide is just wrong. f * empty = empty is no more true than f * g = g, I don’t understand this. The equation f * g = g is much more general than f * empty = empty. (|) usually denotes non-determinism and empty should be the neutral element of non-determinism, which is failing. This leads me to f * empty = empty. […] Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Alternative IO
Am Samstag, 11. Juli 2009 00:16 schrieben Sie: 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, Huh? There was no Applicative instance for IO. This was the reason for Cristiano to define one, and my mail pointed out a problem in his definition. Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK
Am Dienstag, 7. Juli 2009 14:42 schrieb Robin Green: On Fri, 10 Jul 2009 10:44:51 +0200 Wolfgang Jeltsch g9ks1...@acme.softbase.org wrote: PASCAL uses “program”, not “programme”, The word program (as in computer program) is spelled program in both British and American English. Probably just because British English took it from American English. It’s similar to the “German” word “Computer”. It’s not native. Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK
Am Mittwoch, 15. Juli 2009 05:27 schrieben Sie: On Jul 10, 2009, at 8:44 PM, Wolfgang Jeltsch wrote: Why do we use English for identifiers? Because English is the language of computer science. What English should we use? It’s tempting to say, we should use the original English, which is British English. But we should ask again what is the language of computer science. And the language of computer science is American English. It was possible to adopt such an attitude in the 20th century. But this is the 21st century. We have globalisation, internationalisation, localisation. We have Unicode, so that people are no longer limited to the set of characters that technicians from the USA found tolerable back in 1967. So I should upload a package with German identifiers to Hackage? Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What's the status with unicode characters on haddock ?
Am Freitag, 10. Juli 2009 09:54 schrieb david48: Hello all, I made a small program for my factory and I wanted to try to document it using haddock. The thing is, the comments are in French and the resulting html pages are unreadable because the accentuated letters are mangled. It's not acceptable to use HTML entities, as I'd like the comments to remain readable when/if I edit the code. Anyone has had the same problem ? Found a workaround ? Thanks, David. To my knowledge, Haddock only supports ASCII as input encoding. If you want to have characters outside ASCII, you have to escape them using something like #xA0;. Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What's the status with unicode characters on haddock ?
On Fri, Jul 17, 2009 at 4:37 PM, Wolfgang Jeltschg9ks1...@acme.softbase.org wrote: To my knowledge, Haddock only supports ASCII as input encoding. If you want to have characters outside ASCII, you have to escape them using something like #xA0;. Which would mean, while editing the code I'd have to read comments like that : -- | s#xA0;lection de l'#xA0;tat Which becomes totally unreadable. :( David ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Alternative IO
On Fri, Jul 17, 2009 at 10:21 AM, Wolfgang Jeltschg9ks1...@acme.softbase.org wrote: Am Freitag, 10. Juli 2009 23:41 schrieben Sie: Additionally, the second equality you provide is just wrong. f * empty = empty is no more true than f * g = g, I don’t understand this. The equation f * g = g is much more general than f * empty = empty. (|) usually denotes non-determinism and empty should be the neutral element of non-determinism, which is failing. This leads me to f * empty = empty. That's too strong, unless you want to restrict Alternative to applicative functors with reversible side-effects. It's generally accepted that LogicT IO is an instance of MonadPlus, but liftIO (putStrLn effects!) mzero /= mzero I would expect LogicT IO to be an instance of Alternative as well. -- Dave Menendez d...@zednenem.com http://www.eyrie.org/~zednenem/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Jane Street
If one of you knows something about working at Jane Street, I'd be happy to have exchange some mails. I am considering applying there. Thanks! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: cabal: : openFile: does not exist (No such file or directory)
cabal -v3 update will give you a more verbose version of what is going wrong. cabal --help regrettably, cabal --help doesn't tell you this but there is always the man page I suppose. 2009/7/16 Tony Hannan tonyhann...@gmail.com: Hello, I'm on Ubuntu 8.10. I installed ghc 6.10.4 (from binary package: ghc-6.10.4-i386-unknown-linux-n.tar.bz2). I installed haskell-platform-2009.2.0.1 (from source package: haskell-platform-2009.2.0.1.tar.gz). It contains cabal-install-0.6.2. Then when I run cabal update, I get the following error: cabal: : openFile: does not exist (No such file or directory) Any ideas? Thanks, Tony ___ Libraries mailing list librar...@haskell.org http://www.haskell.org/mailman/listinfo/libraries ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] laziness blowup exercise
Thomas, if you did no know, where to look for `lazy-memory-hole', say in your first example, how would you go about solving that puzzle systematically with a Profiler (or other tools)? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What's the status with unicode characters on haddock ?
Am Freitag, 17. Juli 2009 16:43 schrieben Sie: On Fri, Jul 17, 2009 at 4:37 PM, Wolfgang Jeltschg9ks1...@acme.softbase.org wrote: To my knowledge, Haddock only supports ASCII as input encoding. If you want to have characters outside ASCII, you have to escape them using something like #xA0;. Which would mean, while editing the code I'd have to read comments like that : -- | s#xA0;lection de l'#xA0;tat Which becomes totally unreadable. :( Yes, it’s a pity. For me, it’s not such a big problem since I don’t write my Haddock comments in my native language (German) but in English. I only experience this problem because I use nice typography, i.e., “ ” – instead of -. GHC supports UTF-8 input, and Haddock uses GHC nowadays. So, in my opinion, Haddock should also support UTF-8 input. Do you want to file a feature request? Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] laziness blowup exercise
I don't have a good answer to that, and I unable to reliably solve this type of problem, which is one reason I am posting around on haskell cafe hoping to accumulate wisdom. Here for instance I think I did t = last . take (10^6) $ repeat $ S.empty which doesn't blow up, and by process of elimination figured the process must be in iterate. I then looked at iterate by writing myiterate (could have also copied from hackage prelude) and thought about it until the answer (well, an answer, maybe not the best one) came myiterate f x = x : myiterate f (f x) In general, I feel like I don't do very well solving these types of problems. Am 17. Juli 2009 08:47 schrieb Matthias Görgens matthias.goerg...@googlemail.com: Thomas, if you did no know, where to look for `lazy-memory-hole', say in your first example, how would you go about solving that puzzle systematically with a Profiler (or other tools)? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What's the status with unicode characters on haddock ?
On Fri, Jul 17, 2009 at 4:05 PM, Wolfgang Jeltschg9ks1...@acme.softbase.org wrote: Yes, it’s a pity. For me, it’s not such a big problem since I don’t write my Haddock comments in my native language (German) but in English. I only experience this problem because I use nice typography, i.e., “ ” – instead of -. I would write the comments in English, but as it is, it's a little piece of code for our factory that's never going to be released. Still, I wanted to document it properly, and my boss can't read English. GHC supports UTF-8 input, and Haddock uses GHC nowadays. So, in my opinion, Haddock should also support UTF-8 input. Do you want to file a feature request? Sure. I'm registering to haddock trac site and will search the tickets. David. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What's the status with unicode characters on haddock ?
On Fri, Jul 17, 2009 at 4:15 PM, david48dav.vire+hask...@gmail.com wrote: On Fri, Jul 17, 2009 at 4:05 PM, Wolfgang GHC supports UTF-8 input, and Haddock uses GHC nowadays. So, in my opinion, Haddock should also support UTF-8 input. Do you want to file a feature request? Sure. I'm registering to haddock trac site and will search the tickets. There are two tickets already about unicode or character handling: #20 and #116. It doesn't look like it's a hot issue :( David. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Plot data reconstruction reading pixel colors from image files
Hi, How can I open and read colors of specific pixels of an image file in Haskell? Which packages, functions do you recommend? You can have a look at the quoted conversation for an idea on what I would like to automate. Best Regards, Cetin Sert Hi dear *^o^*, Here are the points from Figure 37 [SEE ATTACHED PNG] Cisse Goni Kodougou Nouna normals log10s normals log10s normals log10s normals log10s 0.7998 0.5249 0.4248 0.375 0.412499964 0.4248 0.8501 1.575 1.5999 1.325 1.0498 6.30957344480193 3.3496543915782757 2.6607250597988084 2.371373705661655 2.5852348395621885 2.6607250597988084 7.07945784384138 37.583740428844415 39.81071705534971 21.134890398366466 11.220184543019629 -0.5625 -0.3252 0.162499964 0.3374 0.5 0.8501 1.48749998 2.1375 2.2625 1.875 1.0 0.27384196342643613 0.4731512589614803 1.4537843856076607 2.1752040340195222 3.1622776601683795 7.07945784384138 30.725573652674456 137.24609610075626 183.02061063110568 74.98942093324558 10.0 0.7251 0.34964 0.3374 0.5 0.625 0.63749997 0.76249997 1.2249 1.5125 1.2125 0.625 5.30882309884 2.2387211385683377 2.1752040340195222 3.1622776601683795 4.216965034285822 4.340102636447436 5.787619883491203 16.788040181225597 32.546178349804585 16.31172909227838 4.216965034285822 0.3374 0.137499973 0.375 0.6499 0.5747 0.47464 0.98749998 1.825 2.025 1.4749 0.76249997 2.1752040340195222 1.372460961007561 2.371373705661655 4.46683592150963 3.7583740428844394 2.9853826189179573 9.716279515771058 66.83439175686145 105.92537251772886 29.853826189179586 5.787619883491203 Top to Bottom in the table is Left to Right in the figure. Lots of love, CS ;-) P/S: Sorry it took a bit longer than expected but it was lots of fun! --- module Main where import Control.Monad f x = 3 - (x / 80) -- 80: number of pixels d x = x - 2 -- pixel offset cisse, goni, kodou, nouna :: [Double] cisse = [178,200,208,212,209,208,174,116,114,136,158] goni = [287,268,229,215,202,174,123,71 ,61 ,92 ,162] kodou = [184,214,215,202,192,191,181,144,121,145,192] nouna = [215,231,212,190,196,204,163,96 ,80 ,124,181] disp :: (String, [Double]) → IO () disp (town,pixels) = do putStrLn$ town putStrLn$ normals mapM_ print $ points putStrLn$ log10s mapM_ print $ log10s putStrLn$ --- where points = map (f . d) pixels log10s = map (10 **) points main :: IO () main = do mapM_ disp [(Cisse, cisse),(Goni, goni),(Kodougou, kodou),(Nouna, nouna)] Cisse normals 0.7998 0.5249 0.4248 0.375 0.412499964 0.4248 0.8501 1.575 1.5999 1.325 1.0498 log10s 6.30957344480193 3.3496543915782757 2.6607250597988084 2.371373705661655 2.5852348395621885 2.6607250597988084 7.07945784384138 37.583740428844415 39.81071705534971 21.134890398366466 11.220184543019629 --- Goni normals -0.5625 -0.3252 0.162499964 0.3374 0.5 0.8501 1.48749998 2.1375 2.2625 1.875 1.0 log10s 0.27384196342643613 0.4731512589614803 1.4537843856076607 2.1752040340195222 3.1622776601683795 7.07945784384138 30.725573652674456 137.24609610075626 183.02061063110568 74.98942093324558 10.0 --- Kodougou normals 0.7251 0.34964 0.3374 0.5 0.625 0.63749997 0.76249997 1.2249 1.5125 1.2125 0.625 log10s 5.30882309884 2.2387211385683377 2.1752040340195222 3.1622776601683795 4.216965034285822 4.340102636447436 5.787619883491203 16.788040181225597 32.546178349804585 16.31172909227838 4.216965034285822 --- Nouna normals 0.3374 0.137499973 0.375 0.6499 0.5747 0.47464 0.98749998 1.825 2.025 1.4749 0.76249997 log10s 2.1752040340195222 1.372460961007561 2.371373705661655 4.46683592150963 3.7583740428844394 2.9853826189179573 9.716279515771058 66.83439175686145 105.92537251772886 29.853826189179586 5.787619883491203 --- attachment: fig37-points.png___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] laziness blowup exercise
I tried using your original code and stuffing it into a profiler. But all I get is a triangle of linearly increasing resource usage, and then it breaks for lack of stack. I guess I am just to ignorant about retainer profiling and such stuff. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A voyage of undiscovery
Derek Elkins wrote: The answer to your questions are on the back of this T-shirt. http://www.cafepress.com/skicalc.6225368 Oh... dear God. o_O ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A voyage of undiscovery
John Meacham wrote: actually, the rules are pretty straightforward. It doesn't matter where something is bound, just _how_ it is bound. Let-bound names (which includes 'where' and top-level definitions) can be polymorphic. lambda-bound or case-bound names (names bound as an argument to a function or that appear in a pattern) can only be monomorphic. And that's all there is to it. (the monomorphism restriction complicates it a little, but we don't need to worry about that for now) That seems simple enough (although problematic to implement). However, the Report seems to say that it matters whether or not the bindings are muturally recursive [but I'm not sure precisely *how* it matters...] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Plot data reconstruction reading pixel colors from image files
If you don't find anything more specific, I suggest taking a look at Data.Binary and reading a simple format like BMP or so. (You can convert your file to BMP with an external program before.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Plot data reconstruction reading pixel colors from image files
On Fri, Jul 17, 2009 at 06:31:20PM +0200, Cetin Sert wrote: How can I open and read colors of specific pixels of an image file in Haskell? Which packages, functions do you recommend? You could try DevIL, SDL-image or Gtk, I guess. -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Oops in Haskell
Hi, Can someone please send me a working example based on the contents posted in the URL below? http://yi-editor.blogspot.com/2008/12/prototypes-encoding-oo-style.html Thanks, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Oops in Haskell
Kashyap, Can someone please send me a working example based on the contents posted in the URL below? There's a small typo in the post: the definition of Proto should read data Proto = Proto {a :: A, b :: B, c :: C} The rest seems fine to me. (See below for an excerpt). Cheers, Stefan --- import Data.Function (fix) data A = A B C ; fa = A data B = B A C ; fb = B data C = C A B ; fc = C userFunction = C data Proto = Proto {a :: A, b :: B, c :: C} proto = \self - Proto { a = fa (b self) (c self), b = fb (a self) (c self), c = fc (a self) (b self) } customizedProto = \self - proto self { c = userFunction (a self) (b self) } customizedABC = fix customizedProto ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A voyage of undiscovery
Andrew, That seems simple enough (although problematic to implement). However, the Report seems to say that it matters whether or not the bindings are muturally recursive [but I'm not sure precisely *how* it matters...] It means that functions can only be used monomorphically within their own binding group. (That includes the definition of the function itself: functions cannot be polymorphically recursive. Of course, these restrictions do not apply in case of explicit type signatures. Even if this doesn't all make sense, immediately, it should give you something to google for. ;-)) Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Pattern matching with where free variables can be used more than once
Wouldn't it be great if pattern variables could be used more than once in a pattern? Like so: foo [x,x,_,x] = The values are the same! foo _ = They're not the same! where this could be rewritten to: foo [x,y,_,z] | x == y x == z = The values are the same! foo _ = They're not the same! It seems like a straight-forward translation and there wouldn't be a speed hit for normal patterns because it would only be triggered in compilation where the same free variable appears twice. Implications are: 1. in ``foo [x,y] = ...'', x has type a 1. in ``foo [x,x] = ...'', x has type Eq a = a Was this ever considered? Is it a bad idea for some reason I'm not aware of? On a mildly irrelevant note, I have observed newbies to the language wonder why on earth it's not already like this. Cheers ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Pattern matching with where free variables can be used more than once
Christopher, Wouldn't it be great if pattern variables could be used more than once in a pattern? Like so: foo [x,x,_,x] = The values are the same! foo _ = They're not the same! These are called nonlinear patterns. I think Miranda (a precursor of Haskell, sort of) used to have them. Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] excercise - a completely lazy sorting algorithm
Hi all, I apologize that I didn't react to your posts, I was on a vacation. (BTW, if you ever come to Slovakia, I strongly recommend visiting Mala (Lesser) Fatra mountains. IMHO it's more beautiful than more-known Tatra mountains.) Thanks for your interest and many intriguing ideas. Especially, I like cata-/ana-/hylo-morphisms, it looks to me as a very useful concept to learn. I hope I'll manage to create my own version of the sorting algorithm based on your advices. Maybe I'll also try to do some real benchmarks, if I have time. -Petr On Tue, Jul 07, 2009 at 02:49:08AM +0200, Matthias Görgens wrote: The sorted array of bags of unsorted input is a nice idea. However, you have to use the data structure in a single-threaded [1] fashion to obtain the claimed bounds. Here's a pure solution that uses amortization and laziness. import qualified Data.Sequence as S import Data.Sequence (()) import Data.Foldable import Data.Monoid Suppose we have a function to find the the median of a list, and partition it into three sublists: Smaller than the median, equal to the media, larger than the median. That function should run in linear time. partitionOnMedian :: forall a. (Ord a) = (S.Seq a) - BTreeRaw a (S.Seq a) where the following data structure holds the sublists and some bookkeeping information: data BTreeRaw a m = Leaf | Node {cmp::(a-Ordering) , lN :: Int , less::m , eq :: (S.Seq a) , gN :: Int , greater::m } where 'lN' and 'gN' are the length of 'less' and 'greater'. We can make BTreeRaw a functor: instance Functor (BTreeRaw a) where fmap f Leaf = Leaf fmap f (Node c lN l e gN g) = Node c lN (f l) e gN (f g) Now using a fixed-point construction we can bootstrap a sorting algorithm from partitionOnMedian: data Fix m = Fix {unfix :: (m (Fix m))} type BTree a = Fix (BTreeRaw a) treeSort :: forall a. (Ord a) = S.Seq a - BTree a treeSort = Fix . helper . partitionOnMedian where helper = fmap (Fix . helper . partitionOnMedian) Now treeSort produces the thunk of a balanced binary search tree. Of course we can get a sorted list out of it (forcing the whole structure): flatten :: BTree a - S.Seq a flatten (Fix Leaf) = S.empty flatten (Fix (Node _ lN l e gN g)) = flatten l e flatten g mySort = flatten . treeSort But we can also get elements efficently, forcing only a linear amount of comparisions in the worst case: index :: BTree a - Int - a index (Fix Leaf) _ = error tried to get an element of Leaf index (Fix (Node lN l e gN g)) i | i lN = index l i | i - lN S.length e = S.index e (i-lN) | i - lN - S.length e gN = index g (i - lN - S.length e) | i - lN - S.length e - gN = 0 = error index out of bounds Although we do have to force comparisions only once every time we touch the same element in the tree, we do still have to traverse the tree (in logarithmic time). If you want linear time access on first touch of an element and constant time access afterwards us toArray: toArray :: (IA.IArray a t) = Fix (BTreeRaw t) - a Int t toArray tree = IA.listArray (0,maxI) (map (index tree) [0..maxI]) where size (Fix Leaf) = 0 size (Fix (Node lN _ e gN _)) = lN + S.length e + gN maxI = size tree - 1 [1] Single-Threaded in the sense of Okasaki's use of the word. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] What is the point of the 'What the bleep' names in haskell?
Why do Haskell programmers (and libraries) name their function like @ or ###?Why not use a more descriptive label for functions? Daryoush ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What is the point of the 'What the bleep' names in haskell?
On Jul 17, 2009, at 15:06 , Daryoush Mehrtash wrote: Why do Haskell programmers (and libraries) name their function like @ or ###?Why not use a more descriptive label for functions? Because symbols can be used as infix functions directly, whereas alphanumerics have to be wrapped in `` for infix. And infix is often easier to read. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon universityKF8NH PGP.sig Description: This is a digitally signed message part ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] an instance in other than the last type parameters
Hi, I have probably a very simple question, but I wasn't able to figure it out myself. Consider a two-parameter data type: data X a b = X a b If I want to make it a functor in the last type variable (b), I can just define instance Functor (X a) where fmap f (X a b) = X a (f b) But how do I write it if I want X to be a functor in its first type variable? Is that possible at all? Something like: instance Functor ??? where fmap f (X a b) = X (f a) b Thanks in advance, Petr ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What is the point of the 'What the bleep' names in haskell?
dmehrtash: Why do Haskell programmers (and libraries) name their function like @ or # ##?Why not use a more descriptive label for functions? Where are those functions defined?? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] an instance in other than the last type parameters
Petr, If I want to make it a functor in the last type variable (b), I can just define instance Functor (X a) where fmap f (X a b) = X a (f b) But how do I write it if I want X to be a functor in its first type variable? Short answer: you can't. Easiest way to workaround is to define a newtype wrapper around your original datatype: newtype X' b a = X' {unX' :: X a b} instance Functor (X' b) where fmap g (X' (X a b)) = X' (X b (g a)) Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What is the point of the 'What the bleep' names in haskell?
System.Console.Curses? Sorry couldn't resist ... On Fri, Jul 17, 2009 at 12:18 PM, Don Stewartd...@galois.com wrote: dmehrtash: Why do Haskell programmers (and libraries) name their function like @ or # ##? Why not use a more descriptive label for functions? Where are those functions defined?? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] an instance in other than the last type parameters
Petr, Short answer: you can't. Easiest way to workaround is to define a newtype wrapper around your original datatype: newtype X' b a = X' {unX' :: X a b} instance Functor (X' b) where fmap g (X' (X a b)) = X' (X b (g a)) Err fmap g (X' (X a b)) = X' (X (g a) b) Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] an instance in other than the last type parameters
data X a b = X a b instance Functor (X a) where fmap f (X a b) = X a (f b) Yeah, that works just fine. On Fri, Jul 17, 2009 at 1:14 PM, Petr Pudlak d...@pudlak.name wrote: Hi, I have probably a very simple question, but I wasn't able to figure it out myself. Consider a two-parameter data type: data X a b = X a b If I want to make it a functor in the last type variable (b), I can just define instance Functor (X a) where fmap f (X a b) = X a (f b) But how do I write it if I want X to be a functor in its first type variable? Is that possible at all? Something like: instance Functor ??? where fmap f (X a b) = X (f a) b Thanks in advance, Petr ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Pattern matching with where free variables can be used more than once
Am Freitag, 17. Juli 2009 20:38 schrieb Stefan Holdermans: Christopher, Wouldn't it be great if pattern variables could be used more than once in a pattern? Like so: foo [x,x,_,x] = The values are the same! foo _ = They're not the same! These are called nonlinear patterns. I think Miranda (a precursor of Haskell, sort of) used to have them. Yes, Miranda had them. I see the following problem with them: Patterns are about the structure of data. So using the same variable twice in the same pattern should mean that the values that match the variable must have the same structure. This would break data abstraction. For example, matching a pair of sets against the pattern (x,x) would succeed if both sets were represented by the same tree internally, but not succeed if both sets were equal but represented differently. Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What is the point of the 'What the bleep' names in haskell?
Am Freitag, 17. Juli 2009 21:06 schrieb Daryoush Mehrtash: Why do Haskell programmers (and libraries) name their function like @ or ###?Why not use a more descriptive label for functions? It’s for the same reason that mathematicians say 2 + 3 instead of plus(2,3): it’s more readable at times. :-) Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] uncommon IMO problem - toilet management
In the last two days I was invigilator at the International Mathematic Olympics 2009 in Bremen, Germany. There we got a problem different from the official math problems. :-) Eventually I solved it using Haskell. Read the detailed description at http://hackage.haskell.org/package/toilet-0.0.1 I think the problem is simple enough to be used in education of programming. (I also think it would have been better to avoid monads and use lazy list processing.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: first Grapefruit release
Am Montag, 16. Februar 2009 15:27 schrieben Sie: On Mon, 16 Feb 2009, Wolfgang Jeltsch wrote: [redirecting to haskell-cafe] Am Sonntag, 15. Februar 2009 00:25 schrieben Sie: Hi Wolfgang, I was wondering if I can use FLTK as GUI backend for Grapefruit? This should be possible in principal. It just could be that my assumptions about how widgets are created and composed were too tight so that Grapefruit’s general interface doesn’t fit FLTK. In this case, please just tell me and I will try to make the interface more general. Ok, great I ll have to use them then I will see and know what improvement is needed. I believe for this to make it happen, I would have to output FLTK's C++ into C then create bindings for Haskell (via FFI). Is that doable or an quite tall order? Recently, a student of mine has written a program which generates a Haskell Qt binding fully automatically from Qt header files. The generated binding consists of three layers. The first layer is C++ code which reexports Qt’s functionality as a pure C interface. The C interface is ugly for humans and not type safe (because C doesn’t know classes). The second layer consists of a couple of FFI declarations. The third layer is Haskell code which provides a nice interface similar to the original C++ interface. I still have to get the source code of the binding generator from that student but I hope this will happen soon. I want to publish it then on the web. It hope that it is possible to reuse this binding generator for other C++ libraries. That would be very helpful, I ll be looking forward. Hello Jamie, it’s been quite some time that we had this discussion about writing a FLTK-based GUI backend for Grapefruit. I’m sorry that I have to tell you that the above-mentioned student never managed to send me a final version of this Qt binding generator. At least, I was able to make him send me the current state of his code. I don’t think he will improve this code anymore. If you want to have a look at the code, please visit http://haskell.org/haskellwiki/HQK and follow the link to the code and have a look at the building tips. In case you would like to improve the binding generator, I’d be happy to receive patches. :-) Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: first Grapefruit release
Hello Jeff, it’s been some time that we had the conversation below and I have to tell you the same thing I told Jamie in a haskell-cafe mail sent a few minutes ago: The student who wrote the Qt binding generator never managed to send me a final version of his code. At least, I was able to make him send me the current state. I don’t think he will improve this code anymore. If you want to have a look at the code, please visit http://haskell.org/haskellwiki/HQK and follow the link to the code and have a look at the building tips. In case you would like to improve the binding generator, I’d be happy to receive patches. :-) Sorry for these bad news. Best wishes, Wolfgang Am Mittwoch, 18. Februar 2009 15:42 schrieb Jeff Heard: When he gives you the code, could you let me know? I would really love to bind Open Scene Graph, but it's entirely C++ and that makes for a lot more difficult coding to say the least. On Wed, Feb 18, 2009 at 4:17 AM, Wolfgang Jeltsch g9ks1...@acme.softbase.org wrote: Am Dienstag, 17. Februar 2009 19:36 schrieben Sie: If you have problems with Gtk2Hs on Windows, it might be better to write a Win32-based backend for Grapefruit instead of a wxWidgets-based one. What do you think about that? Win32-based backend would make more sense as it is one less layer to deal with. But how? Same thing with Mac. A student of mine wrote a fully automatic binding generator for C++ libraries which also supports Qt extensions (signals and slots). (However, this guy still has to give me the code. :-/ ) One could do a similar thing for generating Win32 and Cocoa bindings. Then one could write Grapefruit UI backends based on these bindings. Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: [Haskell] ANN: data-ordlist-0.0.1 and NumberSieves-0.0
Leon Smith schrieb: Two new packages have been uploaded to Hackage, one that implements bag (multiset) and set operations on ordered lists, and another that offers three different number theoretic sieves. http://hackage.haskell.org/package/data-ordlist Data.OrdList offers many of the same kinds of operations as Data.Set, although Data.Set is likely to often be a better choice. However, this library is not intended to be used as an abstract datatype for sets and multisets, rather it is intended to be a convenient way for efficiently dealing with lists that you happen to know are ordered. You could also implement that in terms of Map a Int. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK
Wolfgang Jeltsch schrieb: Am Mittwoch, 15. Juli 2009 05:27 schrieben Sie: On Jul 10, 2009, at 8:44 PM, Wolfgang Jeltsch wrote: Why do we use English for identifiers? Because English is the language of computer science. What English should we use? It’s tempting to say, we should use the original English, which is British English. But we should ask again what is the language of computer science. And the language of computer science is American English. It was possible to adopt such an attitude in the 20th century. But this is the 21st century. We have globalisation, internationalisation, localisation. We have Unicode, so that people are no longer limited to the set of characters that technicians from the USA found tolerable back in 1967. So I should upload a package with German identifiers to Hackage? I most like identifiers like getZahl. :-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Debugging methods for haskell
On Thu, 16 Jul 2009, Fernan Bolando wrote: Hi all I recently used 2 hours of work looking for a bug that was causing Program error: Prelude.!!: index too large A good way to avoid such problems is to avoid partial functions at all. (!!) is also inefficient. Is it possible to define the function in terms of foldl? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] can there be (hash-table using) O(n) version of this (I think currently) n log n algo?
The code below is, I think, n log n, a few seconds on a million + element list. I wonder if it's possible to get this down to O(N) by using a hashtable implemementation, or other better data structure. Further, is there a hashtable implementation for haskell that doesn't live in IO? Maybe in ST or something? import Data.HashTable import qualified Data.Set as S import Data.List (foldl') testdata = [1,4,8,9,20,11,20,14,2,15] ++ [1..(10^6)] wantedsum = 29 -- set data structure -- findsums locates pairs of integers in a list that add up to a wanted sum. findsums :: [Int] - Int - S.Set (Int,Int) findsums xs wanted = snd . foldl' f (S.empty,S.empty) $ xs where f (candidates,successes) next = if S.member (wanted-next) candidates then (candidates, S.insert (next,wanted-next) successes) else (S.insert next candidates,successes) -- hashtable data structure -- result: t -- fromList [(15,14),(16,13),(17,12),(18,11),(19,10),(20,9),(21,8),(22,7),(23,6),(24,5),(25,4),(26,3),(27,2),(28,1)] -- probably O(n log n) complexity since using tree based Data.Set (a few seconds on million+ element list) t = findsums testdata wantedsum ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Plot data reconstruction reading pixel colors from image files
Felipe Lessa schrieb: On Fri, Jul 17, 2009 at 06:31:20PM +0200, Cetin Sert wrote: How can I open and read colors of specific pixels of an image file in Haskell? Which packages, functions do you recommend? You could try DevIL, SDL-image or Gtk, I guess. Perhaps http://hackage.haskell.org/package/pgm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] is closing a class this easy?
Friends Is closing a class this easy? -- module Moo ( Public(..) ) where class Private x = Public x where blah :: ... class Private x where instance Private A where instance Public A where blah = ... instance Private B where instance Public B where blah = ... -- Modules importing Moo get Public and its instances, but cannot add new ones: any such instances must be accompanied by Private instances, and Private is out of scope. Does this work? If not, why not? If so, is this well known? It seems to be just what I need for a job I have in mind. I want a class with nothing but hypothetical instances. It seems like I could write -- module Noo ( Public(..) , public ) where class Private x = Public x where blah :: ... blah = ... class Private x where public :: (forall x. Public x = x - y) - y public f = f Pike data Pike = Pike instance Private Pike instance Public Pike -- But if I don't tell 'em Pike, I've ensured that blah can only be used in the argument to public. Or is there a hole? Cures youriously Conor ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] FFI to double constants, printf
When we printf doubles from C (like when using hsc2hs to bind to a constant) we can get something that's not valid Haskell. See these 2 examples: 3.40282347e+38F inf Do you know some way to printf a double using printf (or any other standard function) that's always going to give me valid Haskell text, even in special cases? Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] generalize RecordPuns and RecordWildCards to work with qualified names?
Record punning is not all that useful with qualified module names. If I write '(M.Record { M.rec_x })' it says Qualified variable in pattern and if I write '(M.Record { rec_x })' it says 'Not in scope: `rec_x''. Could it be this extension be further extended slightly so that 'f (M.Record { M.rec_x })' will desugar to 'f (M.Record { M.rec_x = rec_x })'? Similarly, RecordWildCards could support this too. It seems simple and useful to me... am I missing anything fatally problematic about this? Would anyone else use it? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] FFI to double constants, printf
You probably want something like printf(%.10Lg,d);. Here's a shot C example and its output: #include stdio.h int main(int argc, char * argv[]) { long double d = 0.123456789; printf(%.30Lf\n, d); printf(%.20Lg\n, d); printf(%.20Le\n, d); } /* 0.1234567887336054491370 0.123456788734 1.234567887336e-01 */ On Fri, Jul 17, 2009 at 6:41 PM, Mauríciobriqueabra...@yahoo.com wrote: When we printf doubles from C (like when using hsc2hs to bind to a constant) we can get something that's not valid Haskell. See these 2 examples: 3.40282347e+38F inf Do you know some way to printf a double using printf (or any other standard function) that's always going to give me valid Haskell text, even in special cases? Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] is closing a class this easy?
I've used a similar approach for a while, for instance in http://comonad.com/haskell/type-int/src/Data/Type/Boolean.hs http://comonad.com/haskell/type-int/src/Data/Type/Boolean.hs But I think your approach is cleaner than mine, because it doesn't need my seemingly superfluous closure term or fundep. -Edward Kmett On Fri, Jul 17, 2009 at 11:38 AM, Conor McBride co...@strictlypositive.orgwrote: Friends Is closing a class this easy? -- module Moo ( Public(..) ) where class Private x = Public x where blah :: ... class Private x where instance Private A where instance Public A where blah = ... instance Private B where instance Public B where blah = ... -- Modules importing Moo get Public and its instances, but cannot add new ones: any such instances must be accompanied by Private instances, and Private is out of scope. Does this work? If not, why not? If so, is this well known? It seems to be just what I need for a job I have in mind. I want a class with nothing but hypothetical instances. It seems like I could write -- module Noo ( Public(..) , public ) where class Private x = Public x where blah :: ... blah = ... class Private x where public :: (forall x. Public x = x - y) - y public f = f Pike data Pike = Pike instance Private Pike instance Public Pike -- But if I don't tell 'em Pike, I've ensured that blah can only be used in the argument to public. Or is there a hole? Cures youriously Conor ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why is there no Zippable class? Would this work?
There is a Zip class in category-extras 's Control.Functor.Zip on hackage that covers this use-case. http://hackage.haskell.org/packages/archive/category-extras/latest/doc/html/Control-Functor-Zip.html It can basically be viewed as the ap of an Applicative functor chosen to be the left inverse of a genericly definable 'unzip'. Though, a Zippable functor isn't necessarily Applicative, because there is no reason it needs to support pure -- a lot of zippable functors are comonads after all. I wrote a short blog post on this: http://comonad.com/reader/2008/zipping-and-unzipping-functors/ and one on the less powerful dual operations (less powerful because while every Haskell Functor is strong, much fewer are costrong): http://comonad.com/reader/2008/cozipping/ -Edward Kmett On Thu, Jul 16, 2009 at 5:56 PM, Job Vranish jvran...@gmail.com wrote: I was needing a way to zip generic data structures together today and was very annoyed to find that there is no Zippable class, or variant there of. So I made my own: class (Foldable f, Functor f) = Zippable f where fmaps :: (Foldable g) = g (a - b) - f a - f b fmaps' :: [a - b] - f a - f b -- to save a step on instance implementation zipWith :: (a - b - c) - f a - f b - f c zip :: f a - f b - f (a, b) unzip :: f (a, b) - (f a, f b) fmaps fs a = fmaps' (toList fs) a fmaps' fs a = fmaps fs a zipWith f a b = fmaps (fmap f a) b zip = zipWith (,) unzip a = (fmap fst a, fmap snd a) instance Zippable [] where fmaps' (fx:fs) (x:xs) = fx x : fmaps' fs xs fmaps' _ _ = [] --The fmaps function is also quite handy as a replacment for zipWith3, zipWith4, etc... --For example: x = [1, 3, 5, 7, 3] y = [6, 9, 3, 1, 4] z = [2, 4, 0, 8, 2] test = fmap (,,) x `fmaps` y `fmaps` z -- [(1,6,2),(3,9,4),(5,3,0),(7,1,8),(3,4,2)] --you can also throw in a functor instance to remove the dependency on the Functor class, but it -- might not be worth it: instance (Zippable f) = Functor f where fmap f a = fmaps (repeat f) a Is there any good reason that there isn't something like this in the standard libraries? Or, as far as I can tell, on hackage? If not, then maybe I'll stick it on hackage. - Job Vranish ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] lifting restrictions on defining instances
Can anyone explain the theoretical reason for this limitation, ie other than it is a syntactical restriction, what would it take to lift this restriction ? - Original Message - From: Stefan Holdermans ste...@cs.uu.nl To: Petr Pudlak d...@pudlak.name Cc: haskell-cafe@haskell.org Sent: Saturday, July 18, 2009 5:25 AM Subject: Re: [Haskell-cafe] an instance in other than the last type parameters Petr, If I want to make it a functor in the last type variable (b), I can just define instance Functor (X a) where fmap f (X a b) = X a (f b) But how do I write it if I want X to be a functor in its first type variable? Short answer: you can't. Easiest way to workaround is to define a newtype wrapper around your original datatype: newtype X' b a = X' {unX' :: X a b} instance Functor (X' b) where fmap g (X' (X a b)) = X' (X b (g a)) Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] can there be (hash-table using) O(n) version of this (I think currently) n log n algo?
Haskell hash tables are a notorious performance pig, mostly due to the fact that when we deal with big arrays, if the mutable array changes at all the garbage collector will have to retraverse the entire thing during the next collection. Guess the most common scenario for imperative hash tables that are even lightly tweaked from time to time... ;) As for other non-IO hash tables, I've seen a couple of unboxed hash tables using STUArrays (which can side step this issue for unboxable data), IIRC one may have even been used for a language shootout problem. I even wrote (a rather poorly performing) Witold Litwin-style sorted linear hash table for STM a couple of years back (it should still be on hackage under 'thash'). Data.HashTable could be easily reimplemented in ST s, but it would still suffer the same GC problems as the current hash table, which no one likes. -Ed On Fri, Jul 17, 2009 at 6:24 PM, Thomas Hartman tphya...@gmail.com wrote: The code below is, I think, n log n, a few seconds on a million + element list. I wonder if it's possible to get this down to O(N) by using a hashtable implemementation, or other better data structure. Further, is there a hashtable implementation for haskell that doesn't live in IO? Maybe in ST or something? import Data.HashTable import qualified Data.Set as S import Data.List (foldl') testdata = [1,4,8,9,20,11,20,14,2,15] ++ [1..(10^6)] wantedsum = 29 -- set data structure -- findsums locates pairs of integers in a list that add up to a wanted sum. findsums :: [Int] - Int - S.Set (Int,Int) findsums xs wanted = snd . foldl' f (S.empty,S.empty) $ xs where f (candidates,successes) next = if S.member (wanted-next) candidates then (candidates, S.insert (next,wanted-next) successes) else (S.insert next candidates,successes) -- hashtable data structure -- result: t -- fromList [(15,14),(16,13),(17,12),(18,11),(19,10),(20,9),(21,8),(22,7),(23,6),(24,5),(25,4),(26,3),(27,2),(28,1)] -- probably O(n log n) complexity since using tree based Data.Set (a few seconds on million+ element list) t = findsums testdata wantedsum ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: FFI to double constants, printf
That helps, but: #include stdio.h #include math.h int main () { long double d = HUGE_VAL; printf(%.30Lf\n, d); } still prints just (as it should, I think): inf Is there maybe some way to check if a double or long double do have a proper value? You probably want something like printf(%.10Lg,d);. Here's a shot C example and its output: #include stdio.h int main(int argc, char * argv[]) { long double d = 0.123456789; printf(%.30Lf\n, d); printf(%.20Lg\n, d); printf(%.20Le\n, d); } /* 0.1234567887336054491370 0.123456788734 1.234567887336e-01 */ On Fri, Jul 17, 2009 at 6:41 PM, Mauríciobriqueabra...@yahoo.com wrote: When we printf doubles from C (like when using hsc2hs to bind to a constant) we can get something that's not valid Haskell. See these 2 examples: 3.40282347e+38F inf Do you know some way to printf a double using printf (or any other standard function) that's always going to give me valid Haskell text, even in special cases? Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why is there no Zippable class? Would this work?
2009/7/18 Edward Kmett ekm...@gmail.com: I wrote a short blog post on this: http://comonad.com/reader/2008/zipping-and-unzipping-functors/ and one on the less powerful dual operations (less powerful because while every Haskell Functor is strong, much fewer are costrong): http://comonad.com/reader/2008/cozipping/ -Edward Kmett This is getting a bit OT, but I just wanted to comment that attempting to remove polymorphism from the Functor class (see thread a couple of days ago) means that not every Functor is strong. So strength for Functor would seem to require a fully polymorphic type. I don't know if costrength is 'easier' to derive for those 'restricted' Functors... - George signature.asc Description: OpenPGP digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FFI to double constants, printf
On Jul 17, 2009, at 22:27 , Maurí cio wrote: Is there maybe some way to check if a double or long double do have a proper value? isNaN :: a - Bool True if the argument is an IEEE not-a-number (NaN) value isInfinite :: a - Bool True if the argument is an IEEE infinity or negative infinity isDenormalized :: a - Bool True if the argument is too small to be represented in normalized format isNegativeZero :: a - Bool True if the argument is an IEEE negative zero isIEEE :: a - Bool True if the argument is an IEEE floating point number (in Prelude, even. Class RealFloat) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon universityKF8NH PGP.sig Description: This is a digitally signed message part ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lifting restrictions on defining instances
[Ack, missed the reply-all button...] This was part of my motivation behind the 'removing polymorphism from Functor' thing... to select a different parameter we'd essentially need type-level lambdas... I'll use 'Λ' (capital lambda) for it: instance Functor (Λ a. X a b) where fmap f (X a b) = X (f a) b We don't have these [1], but we *do* have type families, which are kind of like type-level lambdas turned 'inside out' (at least to my eyes), so my idea was to separate this out: type family Point :: * type instance Point (X a b) = a class Functor f where fmap :: (Point f - Point f) - f - f Here I began to run into problems which are a bit irrelevant to this discussion :) [1]: I'm not sure of the exact connection, but see, e.g. Oleg's construction of computation at the type level (http://okmij.org/ftp/Haskell/TypeLC.lhs), wherein he notes the primary role of type application rather than that of abstraction. - George signature.asc Description: OpenPGP digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK
On Jul 18, 2009, at 2:27 AM, Wolfgang Jeltsch wrote: Probably just because British English took it from American English. It’s similar to the “German” word “Computer”. It’s not native. The spelling program goes back to 1633 at least; it cannot then have referred to computers, and is not likely to have been an American import. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK
On Jul 18, 2009, at 2:35 AM, Wolfgang Jeltsch wrote: So I should upload a package with German identifiers to Hackage? Sure, why not? The fact that I can't read it is my loss, not your fault, and there will be plenty of other German- reading Haskellers to benefit from it. I've happily worked with programs in French (not large ones (:-)). Mind you, I was specifically speaking of alternative *dialects* (English, Scots, American, Strine), not alternative *languages*. The library at this University contains books in a wide range of languages and is all the better for it; it would be as churlish as it would be foolish to say English books only! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Pattern matching with where free variables can be used more than once
On Jul 18, 2009, at 6:35 AM, Christopher Done wrote: [non-linear patterns] This kind of matching is provided in Prolog and Erlang. Neither of them lets the user define equality. We find the same issue with n+k patterns (e.g., n+1 as a pattern) l++r patterns (e.g., prefix++tail) (x,x) patterns (hidden ==) In each case, the question is what if the Prelude's version of the explicit or implied function is not in scope? (For n+k patterns, is the relevant function + or is it = and -? For l++r patterns, is it ++, or null, head, and tail?) My preferred answer would be to say the only functions in scope in a pattern are constructors; these aren't functions, they're syntax, and they always relate to the Prelude. The Haskell' community's preferred answer seems to be avoid the question, ban the lot of them. It's fair to say that any such pattern _can_ be rewritten to something Haskell can handle; it's also fair to say that the result is often less readable, but that a rewrite may reduce the pain. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe