[Haskell-cafe] Is Show special? Of course not but...

2011-02-11 Thread Cristiano Paris
Hi cafè, given the following toy code: --- module Main where class Dumb p where dumb :: p - String newtype Branded a b = Branded b unbrand :: Branded a b - b unbrand (Branded x) = x wrong :: Dumb a = b - Branded a b wrong = Branded right :: Show a = b - Branded a b right

Re: [Haskell-cafe] Is Show special? Of course not but...

2011-02-11 Thread Cristiano Paris
On Fri, Feb 11, 2011 at 20:00, Daniel Fischer daniel.is.fisc...@googlemail.com wrote: ... It's because there's no way to determine the type variable a (in either wrong or right). That's what I thought when I wrote the code at first but then I was surprised to see it working with the Show

[Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
Hi all, I've a type problem that I cannot solve and, before I keep banging my head against an unbreakable wall, I'd like to discuss it with the list. Consider the following code: module Main where class PRead p where {} class PWrite p where {} newtype Sealed p a = Sealed a

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 18:43, Steffen Schuldenzucker sschuldenzuc...@uni-bonn.de wrote: ... let good = appendLog Foo Bar :: Sealed Admin String unseal (undefined :: Admin) good FooBar That's true, but putting apart the problem I posed, in my construction I wouldn't expose unseal directly nor

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 19:33, Alexey Khudyakov alexey.sklad...@gmail.com wrote: ... If Private is not exported one cannot add instances to PRead. Nice trick. I would have thought of hiding the classes PRead and PWrite but I'm not sure if it could break the code. Thank you! -- Cristiano GPG

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 20:14, Alexey Khudyakov alexey.sklad...@gmail.com wrote: ... My solution is based on heterogenous lists and require number of language extensions. I'd recomend to read paper Strongly typed heterogeneous collections[1] which describe this technique in detail Curious: I

Re: [Haskell-cafe] Synthetic values?

2011-02-09 Thread Cristiano Paris
On Wed, Feb 9, 2011 at 20:14, Alexey Khudyakov alexey.sklad...@gmail.com wrote: ... instance            PRead (WRead ::: b) instance PRead b = PRead (a ::: b) instance             PWrite (WWrite ::: b) instance PWrite b = PWrite (a ::: b) Brilliant! I was thinking to something like this but

[Haskell-cafe] Choosing a type-class instance based on the context

2011-01-05 Thread Cristiano Paris
Hi all, I was reading: http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap and I became curious. Playing with the code I started to find a way to say: instance Show a = ShowPred a HTrue instead of enumerating all the instances, mirroring those of the Show class: instance ShowPred Int

Re: [Haskell-cafe] Choosing a type-class instance based on the context

2011-01-05 Thread Cristiano Paris
On Wed, Jan 5, 2011 at 20:35, Stephen Tetley stephen.tet...@gmail.com wrote: Though its quite different to AdvancedOverlap, Conal Elliott has a method of answering the title of your post - Choosing a type-class instance based on the context. See the CxMonoid (context monoid) in Section 3.

Re: [Haskell-cafe] RE: ssh ports for monk and nun?

2010-01-22 Thread Cristiano Paris
On Fri, Jan 22, 2010 at 11:38 AM, Bayley, Alistair alistair.bay...@invesco.com wrote: ... Tried and failed. Our firewall will be closed to port 22 for the forseaable future. I'll give the OpenVPN thing a go, if I can find some time. Trying to ask how to pierce your company's firewall in a

Re: [Haskell-cafe] Name overloading

2010-01-14 Thread Cristiano Paris
I wish to thank all of you for your comments. In fact, the solutions you proposed mostly coincided with mine (including the one using type families) but, in my opinion, they are more cumbersome than the prefixed names solution. Going back to my example: f x = open $ open x where: data Foo = {

[Haskell-cafe] Name overloading

2010-01-13 Thread Cristiano Paris
Hi, these days I'm thinking about name scoping in Haskell and a question built up silently but steadily in my mind. Many times I see code like this: data Foo = { fooBar :: Int, fooSay :: String, fooClose :: String } which reminds me of Ye Olde Times of C where you prepend the structure name

Re: [Haskell-cafe] How to understand such a newtype ?

2009-11-22 Thread Cristiano Paris
On Sun, Nov 22, 2009 at 3:47 AM, Felipe Lessa felipe.le...@gmail.com wrote: ... Well, “ReaderT XConf (StateT XState IO) a” is *the* type :). It's a monad that is a Reader of XConf and has a State of XState. ... and also wraps a monad to allow IO access inside the X monad. Cristiano

Re: [Haskell-cafe] Typefuck: Brainfuck in the type system

2009-11-19 Thread Cristiano Paris
On Mon, Nov 16, 2009 at 6:26 PM, Gwern Branwen gwe...@gmail.com wrote: ... Too late: ... http://hackage.haskell.org/package/loli What's the point with loli? Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] type inference question

2009-10-08 Thread Cristiano Paris
On Thu, Oct 8, 2009 at 11:04 AM, minh thu not...@gmail.com wrote: Hi, I'd like to know what are the typing rules used in Haskell (98 is ok). Specifically, I'd like to know what makes let i = \x - x in (i True, i 1) legal, and not let a = 1 in (a + (1 :: Int), a + (1.0 :: Float)) Is it

Re: [Haskell-cafe] type inference question

2009-10-08 Thread Cristiano Paris
On Thu, Oct 8, 2009 at 12:48 PM, Lennart Augustsson lenn...@augustsson.net wrote: The reason a gets a single type is the monomorphism restriction (read the report). Using NoMonomorphismRestriction your example with a works fine. Could you explain why, under NoMonomorphismRestriction, this

Re: [Haskell-cafe] Re: Is it safe to use unsafePerformIO here?

2009-09-20 Thread Cristiano Paris
On Sat, Sep 19, 2009 at 6:53 PM, Ben Franksen ben.frank...@online.de wrote: Cristiano Paris wrote: Daniel Fischer wrote: I would separate the reading of headers and bodies, reopening the files whose body is needed, for some (maybe compelling) reason he wants to do it differently. Yes

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-18 Thread Cristiano Paris
On Fri, Sep 18, 2009 at 4:06 AM, Ryan Ingram ryani.s...@gmail.com wrote: I am confused about why this thread is talking about unsafePerformIO at all.  It seems like everything you all want to do can be accomplished with the much less evil unsafeInterleaveIO instead.  (Which is still a bit evil;

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-18 Thread Cristiano Paris
On Fri, Sep 18, 2009 at 5:15 AM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... But that does something completely different from what Cristiano wants to do. He wants to read many files files quasi-parallel. As far as I can tell, he needs to read a small chunk from the beginning of every

[Haskell-cafe] Thank you guys

2009-09-18 Thread Cristiano Paris
I wish to thank Cafè's people for their great support in understanding Haskell. Thank you all! Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-17 Thread Cristiano Paris
On Thu, Sep 17, 2009 at 8:36 AM, Ryan Ingram ryani.s...@gmail.com wrote: ... Explicitly: Haskell: test1 :: forall a. a - Int test1 _ = 1 test2 :: (forall a. a) - Int test2 x = x explicitly in System F: test1 = /\a \(x :: a). 1 test2 = \(x :: forall a. a). x @Int /\ is type-level

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 11:31 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... Yeah, you do *not* want the whole file to be read here, except above for testing purposes. That's not true. Sometimes I want to, sometimes don't. But I want to use the same code for reading files and exploit

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-17 Thread Cristiano Paris
On Thu, Sep 17, 2009 at 10:01 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... readBit fn = do    txt - readFile fn    let (l,_:bdy) = span (/= '\n') txt    return $ Bit (read l) bdy ? With main = do    args - getArgs    let n = case args of                (a:_) - read a      

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-16 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 11:38 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... foo :: forall a. a - a This is exactly the same type as foo :: a - a (unless you're using ScopedTypeVariables and there's a type variable a in scope), since type signatures are implicitly forall'd.

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-16 Thread Cristiano Paris
On Wed, Sep 16, 2009 at 7:12 PM, Ryan Ingram ryani.s...@gmail.com wrote: Here's the difference between these two types: test1 :: forall a. a - Int -- The caller of test1 determines the type for test1 test2 :: (forall a. a) - Int -- The internals of test2 determines what type, or types, to

[Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
Hi Cafè, I've the following problem: I have a (possibly very long) list of files on disk. Each file contains some metadata at the beginning and continues with a (possibly very large) chunk of data. Now, the program I'm writing can be run in two modes: either read a specific file from the disk

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:13 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... Still, the body should be read lazily. I'm not sure, but the tracing message may be output because of its position. With where    readBody = withFile fn ReadMode $ \h - do        b - hGetContents h        

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:16 PM, Svein Ove Aas svein@aas.no wrote: I have a number of suggestions, some of which conflict with each other, so I'll just throw them out here. Let's see.. :) First off, the IO monad does indeed enforce sequencing; that's its primary purpose. So,

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:39 PM, Svein Ove Aas svein@aas.no wrote: As a general sort of warning, do not use hGetContents (or lazy i/o, in general) in combination with withFile. withFile closes the handle when the program lexically exits its scope. However, when using hGetContents, the

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:12 PM, Ross Mellgren rmm-hask...@z.odi.ac wrote: Wouldn't seq b only force (at minimum) the first character of the file? I think it force the evaluation of the Cons in the String but not the characters therein. Cristiano ___

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:11 PM, Cristiano Paris fr...@theshire.org wrote: On Tue, Sep 15, 2009 at 10:08 PM, Cristiano Paris fr...@theshire.org wrote: ... So, it seems that seq b is completely ineffective and program is not correct. Correction: removing seq b results in nothing being

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:20 PM, Ross Mellgren rmm-hask...@z.odi.ac wrote: Ack, IGNORE ME! Way too strict. Oh, well, I used foldr+seq to achieve the same result... I think, but I think that, if this is the solution, I'll use rnf as I did on other occasions. Thanks. Cristiano

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:25 PM, Cristiano Paris fr...@theshire.org wrote: ... Two points: 1 - I had to cut off file1.txt to be just above 1024 bytes otherwise the program becomes extremely slow even on a 100KB file with a line being output every 5 seconds and with my CPU being completely

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:08 PM, Cristiano Paris fr...@theshire.org wrote: ... So, it seems that seq b is completely ineffective and program is not correct. Correction: removing seq b results in nothing being displayed :) So, it's not completely effective. I suspect this is related

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:29 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: Am Dienstag 15 September 2009 21:13:02 schrieb Daniel Fischer: Still, the body should be read lazily. I'm not sure, but the tracing message may be output because of its position. With where     readBody =

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:29 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: ... It evaluates the String far enough to know whether it's or (_:_), that is, to weak head normal form. It doesn't look at any character, but it forces at least one character to be read from the file. Yep,

Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:42 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: Aaawww. let b' = length b or let b' = foldl' seq () b or let b' = b `using` rnf if you want to force the whole file to be read. But then you should definitely be using ByteStrings. Yep. But that

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-15 Thread Cristiano Paris
On Wed, Sep 2, 2009 at 7:16 AM, zaxis z_a...@163.com wrote: Isnot it clear without the 'forall' ? data Branch tok st a = Branch (PermParser tok st (b - a)) (GenParser tok st b) thanks! I elaborated on this and I wish to add my personal way of figuring out what the forall keyword means.

Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-02 Thread Cristiano Paris
On Wed, Sep 2, 2009 at 11:00 AM, zaxisz_a...@163.com wrote: seems a bit understanding, i still need to think it  for a while thanks! I think I've understood the existential types thing, but I still can't put them to work when I think to a solution for a particular problem, i.e. it's not among

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Cristiano Paris
On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingramryani.s...@gmail.com wrote: unsafeCoerce is ugly and I wouldn't count on that working properly. Here's a real solution: {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables, FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-}

Re: [Haskell-cafe] How to convert a list to a vector encoding its length in its type?

2009-08-25 Thread Cristiano Paris
On Tue, Aug 25, 2009 at 7:15 PM, Ryan Ingramryani.s...@gmail.com wrote: On Tue, Aug 25, 2009 at 6:07 AM, Cristiano Parisfr...@theshire.org wrote: On Tue, Aug 25, 2009 at 12:07 AM, Ryan Ingramryani.s...@gmail.com wrote: {-# LANGUAGE GADTs, RankNTypes, TypeFamilies, ScopedTypeVariables,

Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-17 Thread Cristiano Paris
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

Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-17 Thread Cristiano Paris
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

[Haskell-cafe] Python vs Haskell in tying the knot

2009-07-17 Thread Cristiano Paris
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

[Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Cristiano Paris
Hi, as pointed out in this list, it seems that a tying the knot example would be the one better explaining the power of Haskell's lazy-by-default approach against Python+Iterator's approach to laziness. So, in these days I'm trying to grasp the meaning of this tying the knot concept which seems

Re: [Haskell-cafe] What to say about Haskell?

2009-07-14 Thread Cristiano Paris
On Tue, Jul 14, 2009 at 3:42 PM, Thomas Davietom.da...@gmail.com wrote: On 14 Jul 2009, at 15:30, Patai Gergely wrote: Hello all, I was asked to give a one-hour 'introductory' seminar on Haskell. The audience is a bunch of very clever people with a wider than usual perspective on

Re: [Haskell-cafe] What to say about Haskell?

2009-07-14 Thread Cristiano Paris
2009/7/14 Patai Gergely patai_gerg...@fastmail.fm: Hello all, I was asked to give a one-hour 'introductory' seminar on Haskell. The audience is a bunch of very clever people with a wider than usual perspective on programming and mathematics, and my talk should be rather informational than

Re: Re[2]: [Haskell-cafe] What to say about Haskell?

2009-07-14 Thread Cristiano Paris
On Tue, Jul 14, 2009 at 4:46 PM, Bulat Ziganshinbulat.zigans...@gmail.com wrote: ... the question is how to justify this in 1 hour. technical people don't buy such arguments with justification. but if it will be done, it would be best presentation possible I think it's important to elaborate

Re: Re[2]: [Haskell-cafe] What to say about Haskell?

2009-07-14 Thread Cristiano Paris
On Tue, Jul 14, 2009 at 5:12 PM, Cristiano Parisfr...@theshire.org wrote: ... Why don't we create a specific Wiki page about Haskell advocation, http://haskell.org/haskellwiki/Advocation Cristiano ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Laziness enhances composability: an example

2009-07-10 Thread Cristiano Paris
2009/7/9 Marcin Kosiba marcin.kos...@gmail.com: On Thursday 09 July 2009, Cristiano Paris wrote: Thanks. In fact, I was stuck trying to find an example which couldn't be written using Python's iterators. The only difference coming up to my mind was that Haskell's lists are a more natural way

Re: [Haskell-cafe] Alternative IO

2009-07-10 Thread Cristiano Paris
On Fri, Jul 10, 2009 at 10:35 AM, Wolfgang Jeltschg9ks1...@acme.softbase.org wrote: ... Hello Cristiano, 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

[Haskell-cafe] Laziness enhances composability: an example

2009-07-09 Thread Cristiano Paris
Hi, I'm wondering what a good example of why laziness enhances composability would be. I'm specifically looking for something that can't implemented in Python with iterators (at least not elegantly), but can actually be implemented in Haskell. Thanks, Cristiano

Re: [Haskell-cafe] Laziness enhances composability: an example

2009-07-09 Thread Cristiano Paris
Thank you for your suggestions! C. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Alternative IO

2009-07-09 Thread Cristiano Paris
As a joke, I wrote an instance of Alternative for IO actions: {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Applicative import Control.Exception instance Alternative IO where empty = undefined x | y = handle (\ (_ :: SomeException) - y) x This would allow to write IO

Re: [Haskell-cafe] Alternative IO

2009-07-09 Thread Cristiano Paris
On Thu, Jul 9, 2009 at 3:42 PM, Edward Kmett ekm...@gmail.com wrote: Hrmm. This should probably be made consistent with the MonadPlus instance for IO, so empty = ioError (userError mzero) I agree. Of course, that was only a first attempt :) Cristiano

Re: [Haskell-cafe] Laziness enhances composability: an example

2009-07-09 Thread Cristiano Paris
On Thu, Jul 9, 2009 at 3:42 PM, Bulat Ziganshin bulat.zigans...@gmail.com wrote: Hello Cristiano, Thursday, July 9, 2009, 4:55:09 PM, you wrote: the best known example is chessmate implementation in Wadler's why functional programming matter but i don't know much about Python iterators,

Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Cristiano Paris
On Wed, May 27, 2009 at 7:14 PM, Manu Gupta manugu...@gmail.com wrote: Dear anyone, I wish to learn HASKELL. That's good for you. However my institution does not teach it so plus I don't have a clue how to get around with it. Everything seems so unconventional and out of place I know that

Re: [Haskell-cafe] Getting the x out

2009-04-22 Thread Cristiano Paris
On Wed, Apr 22, 2009 at 2:49 AM, michael rice nowg...@yahoo.com wrote: How do I get the x out of Just x? Hi Michael, in your code you're using Maybe to inform the caller of safeDivision about an exceptional situation. This way, you made a full coverage of all the input cases and nothing is left

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread Cristiano Paris
On Tue, Apr 14, 2009 at 4:54 PM, rodrigo.bonifacio rodrigo.bonifa...@uol.com.br wrote: Dear Sirs, I guess this is a very simple question. How can I convert IO [XmlTree] to just a list of XmlTree? Quick and dirty answer: unsafePerformIO. That's an easy finding on Hoogle:

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread Cristiano Paris
On Tue, Apr 14, 2009 at 5:01 PM, Luke Palmer lrpal...@gmail.com wrote: ... This is very important: you cannot. I'd answer You shouldn't, unless you know what you are doing. In some cases, not only is unsafePerformIO desirable but also necessary (I'm thinking of Debug.Trace). Cristiano

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread Cristiano Paris
On Tue, Apr 14, 2009 at 5:09 PM, Luke Palmer lrpal...@gmail.com wrote: ... Please don't say that.  He's a beginner. You realize that the path of least resistance will be to use it, right? You see why that's not a good thing? Even experts don't use this function. (To the O.P.:  don't use it)

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread Cristiano Paris
On Tue, Apr 14, 2009 at 5:42 PM, Luke Palmer lrpal...@gmail.com wrote: ... However, the way I see it is that unsafePerformIO *is* evil by itself, and it is only by the addition of Holy Water that it is benign to use. That's what I meant but your words are indeed more effective :) Ryan

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread Cristiano Paris
On Tue, Apr 14, 2009 at 5:54 PM, Jules Bean ju...@jellybean.co.uk wrote: ... I'm convinced about what you say and perhaps I answered the way I did just because I'm convinced that, for a newbie, knowing about the existence of unsafePerformIO can't cause any harm. I was a bit surprised by the

Re: [Haskell-cafe] System.Process.Posix

2009-04-07 Thread Cristiano Paris
On Tue, Apr 7, 2009 at 3:31 PM, Neil Mitchell ndmitch...@gmail.com wrote: I was implementing full package support last weekend. With any luck, I'll manage to push the changes tonight. If not, I'll push them as soon as I get back from holiday (a week or so) Thank you, Neil. Cristiano

Re: [Haskell-cafe] System.Process.Posix

2009-04-05 Thread Cristiano Paris
On Sat, Apr 4, 2009 at 10:28 PM, Don Stewart d...@galois.com wrote: cristiano.paris: ... Isn't this the goal of the process package? Hi Don, thank you for the reference. I saw System.Process but when I needed it I was in a hurry and having a UNIX background I googled for some snippet

[Haskell-cafe] System.Process.Posix

2009-04-04 Thread Cristiano Paris
Is it me or the above package is not included in Hoogle? Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] System.Process.Posix

2009-04-04 Thread Cristiano Paris
On Sat, Apr 4, 2009 at 10:21 PM, Bulat Ziganshin bulat.zigans...@gmail.com wrote: Hello Cristiano, ... there was a large thread a few months ago and many peoples voted for excluding any OS-specific packages at all since this decreases portability of code developed by Hoogle users :))) Nice

Re: [Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread Cristiano Paris
On Mon, Mar 30, 2009 at 9:46 PM, Gü?nther Schmidt gue.schm...@web.de wrote: Thanks Don, I followed some examples but have not yet seen anything that would show me how, for instance, turn a nested Map like Map Int (Map Int (Map String Double) into a zipped version. That is presuming of

Re: [Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread Cristiano Paris
On Tue, Mar 31, 2009 at 10:13 PM, Dan Weston weston...@imageworks.com wrote: What I've learned: Zippers are structured collections[1] with a focus. Through a Zipper you can O(1) change the value of the focused element: that's the fundamental property. In addition, you can change the focus

Re: [Haskell-cafe] Ease of Haskell development on OS X?

2009-03-20 Thread Cristiano Paris
2009/3/20 Mark Spezzano mark.spezz...@chariot.net.au: Hi, I’ve been thinking of changing over to an iMac from my crappy old PC running Windows Vista. Question: Does the iMac have good support for Haskell development? Question: What environment setups do people commonly use (e.g. Eclipse

Re: [Haskell-cafe] Re: Has anybody replicated =~ s/../../ or even something more basic for doing replacements with pcre haskell regexen?

2009-03-17 Thread Cristiano Paris
On Fri, Mar 13, 2009 at 1:19 AM, ChrisK hask...@list.mightyreason.com wrote: At the cost of writing your own routine you get exactly what you want in a screen or less of code, see http://hackage.haskell.org/packages/archive/regex-compat/0.92/doc/html/src/Text-Regex.html#subRegex for

Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-13 Thread Cristiano Paris
2009/3/13 Marcin Kosiba marcin.kos...@gmail.com: ... Threading the state is not the problem. Maybe this will help: what I have now: fsm world state = case state of  first -    do_stuff_one    (move_up, succ state)  second -    do_stuff_two    (move_left, succ state)  third -    

Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-13 Thread Cristiano Paris
2009/3/13 Marcin Kosiba marcin.kos...@gmail.com: Hi,        I've already checked those out. I tried using your yield implementation and while it works, I couldn't get it to work with the state monad.        So while: data RecPair a b = Nil | RP (b, a - RecPair a b) yield x = Cont $ \k - RP

Re: [Haskell-cafe] Re: Zippers

2009-03-05 Thread Cristiano Paris
On 3/5/09, Ryan Ingram ryani.s...@gmail.com wrote: ... Here is the problem with your update: tree = Fork (Leaf 1) (Leaf 2) ztree = initZ tree test = fromJust $ do z1 - moveLeft ztree let z2 = update z1 3 z3 - moveUp z2 z4 - moveLeft z3 this z4 I'd expect test to equal

Re: [Haskell-cafe] Re: Zippers

2009-03-05 Thread Cristiano Paris
On Thu, Mar 5, 2009 at 11:21 AM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: ... Such self-reference is usually called tying the knot, see also  http://www.haskell.org/haskellwiki/Tying_the_Knot I didn't know. Would you call this Tying the knot as well?

Re: [Haskell-cafe] Re: Zippers

2009-03-04 Thread Cristiano Paris
On Wed, Mar 4, 2009 at 12:50 PM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: ... The unusual thing about your implementation is probably that you're tying a knot by making both  moveUp  and  moveLeft  record fields. This reminds me of  Weaving a web. Ralf Hinze and Johan Jeuring.

Re: [Haskell-cafe] Re: Zippers

2009-03-04 Thread Cristiano Paris
On Wed, Mar 4, 2009 at 9:53 PM, Cristiano Paris fr...@theshire.org wrote: ... Thank you for any further comments. I forgot to mention one drawback I found in my implementation: it can't be (de)serialized to a String, which is clearly possible with Huet's. I think this accounts for the Zipper

[Haskell-cafe] Zippers

2009-03-02 Thread Cristiano Paris
Hi, I'm trying to catch the connection between delimited continuations and zippers so I wrote a (kinda) zipper interface to a simple tree structure. Here's the code: --- module Main where import Data.Maybe data Tree a = Leaf a | Fork (Tree a) (Tree a) deriving Show tree = Fork (Fork (Leaf

Re: [Haskell-cafe] HackageDB suggestion [WAS: Re: Hidden module?]

2009-02-28 Thread Cristiano Paris
On Fri, Feb 27, 2009 at 9:53 PM, Achim Schneider bars...@web.de wrote: ... In general, just try the maintainer and/or author adresses given on hsc2hs's hackage page. Ok, thanks. I suggest to add a comment section to every package's area in the HackageDB so as to let users report errors, info

[Haskell-cafe] Hidden module?

2009-02-27 Thread Cristiano Paris
Cabalising hsc2hc I get (this is actually from manually building the package): --- [pa...@bagend hsc2hs-0.67.20061107]$ runghc Setup.hs build Preprocessing executables for hsc2hs-0.67.20061107... Building hsc2hs-0.67.20061107... Main.hs:32:7: Could not find module `System.Process': it

Re: [Haskell-cafe] Hidden module?

2009-02-27 Thread Cristiano Paris
On Fri, Feb 27, 2009 at 3:19 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: Cabal hides all packages not listed among the build-depends when building the libraries. I think in 2006, System.Process was in the base package ('twas before the base-split), so process is not listed among the

Re: [Haskell-cafe] Status of Haskell under OsX

2009-02-26 Thread Cristiano Paris
On Thu, Feb 26, 2009 at 2:31 AM, Manuel M T Chakravarty c...@cse.unsw.edu.au wrote: I'm planning to purchase a MacBookPro so I'm wondering how well Haskell is supported under this platform. At least two of the regular contributors to GHC work on Macs.  That should ensure that Mac OS X is well

[Haskell-cafe] Status of Haskell under OsX

2009-02-25 Thread Cristiano Paris
Hi, I'm planning to purchase a MacBookPro so I'm wondering how well Haskell is supported under this platform. Thanks, Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] question on types

2009-02-18 Thread Cristiano Paris
2009/2/18 Luke Palmer lrpal...@gmail.com: ... Using dependent types, you could have Prime come with a proof that the integer it contains is prime, and thus make those assumptions explicit and usable in the implementation. Unfortunately, it would be a major pain in the ass to do that in

Re: [Haskell-cafe] question on types

2009-02-18 Thread Cristiano Paris
On Wed, Feb 18, 2009 at 10:50 AM, Lennart Augustsson lenn...@augustsson.net wrote: I just want to make one thing clear. With a type that just contains prime numbers the onus is on you (the programmer) to provide the proof that a number is a prime number whenever you claim it is. So you have

Re: [Haskell-cafe] Delimited continuations: please comment

2009-02-15 Thread Cristiano Paris
On Sat, Feb 14, 2009 at 2:04 AM, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote: liftIO is defined there, I believe. Many of the monad modules re-export it with their MonadTrans definitions, but apparently Control.Monad.CC doesn't so you need to go to the source. Yeah, I knew the answer

Re: [Haskell-cafe] Re: Delimited continuations: please comment

2009-02-13 Thread Cristiano Paris
On Fri, Feb 13, 2009 at 2:05 AM, Chung-chieh Shan ccs...@post.harvard.edu wrote: ... It's not unheard of for the scheduler to react in different ways to the same system call -- I'm thinking of reading from a file, for example. Sure, I went implementing something slitghtly different to double

Re: [Haskell-cafe] Re: Can this be done?

2009-02-12 Thread Cristiano Paris
On Wed, Feb 11, 2009 at 6:41 PM, Achim Schneider bars...@web.de wrote: ... I got curious and made two pages point to each other, resulting in as many stale continuations as your left mouse button would permit. While the model certainly is cool, I'm not aware of any implementation that even

[Haskell-cafe] Delimited continuations: please comment

2009-02-12 Thread Cristiano Paris
Hi, I'm experimenting with delimited continuations in the effort to understand how they work and when it's convenient to use them. Consider this piece of code (install the CC-delcont before running it): {-# LANGUAGE NoMonomorphismRestriction #-} import Control.Monad.CC import

[Haskell-cafe] Can this be done?

2009-02-11 Thread Cristiano Paris
I wonder whether this can be done in Haskell (see muleherd's comment): http://www.reddit.com/r/programming/comments/7wi7s/how_continuationbased_web_frameworks_work/ Cristiano ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Can this be done?

2009-02-11 Thread Cristiano Paris
On Wed, Feb 11, 2009 at 2:30 PM, Peter Verswyvelen bugf...@gmail.com wrote: I haven't looked at the details, but I think this is what a library like Reactive from Conal Elliott could do, but as far as I understand it, it is still work in progress. I'm interested in the possibility of

Re: [Haskell-cafe] Can this be done?

2009-02-11 Thread Cristiano Paris
On Wed, Feb 11, 2009 at 2:53 PM, Sebastian Sylvan syl...@student.chalmers.se wrote: I think that would be difficult. You could probably store the continuation in a server-side cache if you aren't doing CGI but have a persistent server process, but eventually you'll need to discard unused

Re: [Haskell-cafe] Can this be done?

2009-02-11 Thread Cristiano Paris
On Wed, Feb 11, 2009 at 4:08 PM, Manlio Perillo manlio_peri...@libero.it wrote: Cristiano Paris ha scritto: On Wed, Feb 11, 2009 at 2:30 PM, Peter Verswyvelen bugf...@gmail.com wrote: I haven't looked at the details, but I think this is what a library like Reactive from Conal Elliott could

Re: [Haskell-cafe] Gentle introduction questions / comments

2009-01-27 Thread Cristiano Paris
2009/1/27 Matthijs Kooijman matth...@stdin.nl Hi all, I've been reading the gentle introduction to Haskell a bit more closely today and there a few things which I can't quite understand (presumably because they are typo's). I've found two issues with the Using monads section [1]. Not sure

Re: [Haskell-cafe] Gentle introduction questions / comments

2009-01-27 Thread Cristiano Paris
On Tue, Jan 27, 2009 at 3:17 PM, Matthijs Kooijman matth...@stdin.nl wrote: Hi Cristiano, Mmmmhhh... this seems the signature of the liftM function, whose purpose is to make a function operate on monadic values instead of pure values. Notice that this is different from the lift function you

Re: [Haskell-cafe] Taking Exception to Exceptions

2009-01-08 Thread Cristiano Paris
On Thu, Jan 8, 2009 at 12:32 AM, Austin Seipp mad@gmail.com wrote: Excerpts from Immanuel Litzroth's message of Wed Jan 07 16:53:30 -0600 2009: ... I am little amazed that I cannot get catch, try or mapException to work without telling them which exceptions I want to catch. What is the

Re: [Haskell-cafe] Defining methods generically for a class

2009-01-08 Thread Cristiano Paris
On Thu, Jan 8, 2009 at 6:04 PM, Jeff Heard jefferson.r.he...@gmail.com wrote: ... How do I declare all Regions to be Eqs without putting it in the class body (since I define a function over all Regions that is independent of datatype that is an instance of Region)? Would this be a solution?

Re: [Haskell-cafe] What are side effects in Haskell?

2009-01-02 Thread Cristiano Paris
On Tue, Dec 30, 2008 at 8:35 AM, Conal Elliott co...@conal.net wrote: Everything in Haskell is a function [...] Where did this idea come from? I'd say every expression in Haskell denotes a pure value, only some of which are functions (have type a-b for some types a b). Maybe more formally

Re: [Haskell-cafe] What are side effects in Haskell?

2009-01-02 Thread Cristiano Paris
On Fri, Jan 2, 2009 at 8:53 PM, Conal Elliott co...@conal.net wrote: I have some speculations: * In pure OO programming, everything is an object, so in pure functional programming, one might assume everything is a function. I find the term value-oriented programming a more accurate label

Re: [Haskell-cafe] Use of abbreviations in Haskell

2009-01-02 Thread Cristiano Paris
On Fri, Jan 2, 2009 at 9:21 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote: module Element where import QName import ... data Element = Element {name :: QName, attribs :: [Attr], content :: [Content], line :: Maybe Line} module Attr where import QName import ... data Attr = Attr {key

  1   2   >