Re: [Haskell-cafe] IO is not a monad

2007-02-07 Thread Yitzchak Gale
Aaron McDaid wrote: Apologies for referring to this old thread... At least for me, this is not old. It is still very much on my mind. Simply, 'undefined undefined' is a bit more defined than simply 'undefined'. Just like 'undefined:undefined' is at least a non-empty list; which can be

Re: [Haskell-cafe] IO is not a monad

2007-02-07 Thread Yitzchak Gale
Just for the record, I think this completes the requirements of my challenge. Please comment! Is this correct? Thanks. 1. Find a way to model strictness/laziness properties of Haskell functions in a category in a way that is reasonably rich. We use HaskL, the category of Haskell types,

Re: [Haskell-cafe] Re: Re: nested maybes

2007-02-07 Thread Yitzchak Gale
Mikael Johansson wrote: A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () - A. Dan Weston wrote: This rather inconveniently clashes with the fact that A and () -

[Haskell-cafe] Re: Importance of MonadRandom

2007-02-07 Thread Yitzchak Gale
OK, thanks! Regards, Yitz Cale Gibbard wrote: The splittable idea isn't mine, it looks like perhaps Remi Turk did it. One thing which I'd recommend is including getRandom, getRandomR as implemented in terms of getR and the ordinary random operations, simply because they're the two most common

Re: [Haskell-cafe] IO is not a monad

2007-02-07 Thread Yitzchak Gale
Aaron McDaid wrote: Could seq be changed so that it will not give an error if it finds undefined? The definition of seq is that seq _|_ x = _|_. That is what it is supposed to do. Actually, the behavior of seq on undefined is very tame - it raises an exception which can be caught. Sometimes

[Haskell-cafe] Re: Importance of MonadRandom

2007-02-06 Thread Yitzchak Gale
I wrote: Cale Gibbard's MonadRandom... I would like to suggest a change to the interface... class (Monad m) = MonadRandom m where nextR :: m Int splitR :: m (m ()) rangeR :: m (Int, Int) getR :: (forall g . RandomGen g = g - a) - m a I see that I have inadvertently done two things

Re: [Haskell-cafe] Re: Generalizing three programs

2007-02-06 Thread Yitzchak Gale
apfelmus wrote: I'm unsure whether it's a good idea to simulate the situations, I'd prefer a more denotational approach... Queuing theory is a very large and mature area of research, with many important applications in industry. It is not a coincidence that a certain telephone company named a

Re: [Haskell-cafe] Re: nested maybes

2007-02-06 Thread Yitzchak Gale
J. Garrett Morris wrote: Again, from the earlier example, I'm not sure how typing: apply :: (MonadCont m, MonadState Blargh m, MonadError Fzzt m, MonadIO m) = Handle - Attribute a - m a is simpler than apply :: Handle - Attribute a - m a Well, no, but it is at least no worse than apply

Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-06 Thread Yitzchak Gale
Philippe de Rochambeau wrote: I have tried map (putStrLn) pImpliesQAndRLoopShow but that results in the following error message: Try mapM_ putStrLn pImpliesQAndRLoopShow or putStrLn $ unlines pImpliesQAndRLoopShow Regards, Yitz ___ Haskell-Cafe

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Yitzchak Gale
J. Garrett Morris wrote: This is where my favorite part of the mtl steps in: monad transformers. I agree, the Error monad is very helpful here. First, we'll create a transformed version of the IO monad, Why go to the trouble of creating a new monad? The existing ones are fine. (While

Re: [Haskell-cafe] Generalizing three programs

2007-02-05 Thread Yitzchak Gale
Andrew Wagner wrote: I've got several problems which seem to have a very similar structure. I want to find a way to abstract them to solve other problems which can be thought about in the same way. Here they are: http://hpaste.org/307 http://hpaste.org/308 http://hpaste.org/309 Note that these

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Yitzchak Gale
I wrote: Why go to the trouble of creating a new monad? The existing ones are fine. J. Garrett Morris wrote: Mainly to keep the type error messages simpler. There are two ways to get around that problem: 1. Make your functions polymorphic, using MonadState, MonadError, etc. Each function

Re: [Haskell-cafe] List operation question

2007-02-04 Thread Yitzchak Gale
Nicolas Frisby wrote: I've always thought that when certain operations are of particular interest, it's time to use more appropriate data structures, right? Lists are great and simple and intuitive, but if you need such operations as shifts, something like a deque is the way to go. This sounds

Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-03 Thread Yitzchak Gale
Hi Sergey, You wrote: Suppose I want show Nothing to return , and show (Just foo) return show foo. I don't seem to be able to. Looks like I either have to use some other function name, like `mShow' That is correct. Show instances are supposed to follow the convention that show x is a Haskell

Re: [Haskell-cafe] (a - [b]) vs. [a - b]

2007-02-02 Thread Yitzchak Gale
Chad Scherrer wrote: Are (a - [b]) and [a - b] isomorphic? I'm trying to construct a function f :: (a - [b]) - [a - b] that is the (at least one-sided) inverse of f' :: [a - b] - a - [b] f' gs x = map ($ x) gs Anything better than this? f g = [\x - g x !! n | n - [0..]] -Yitz

Re: [Haskell-cafe] Re: DevRandom

2007-02-01 Thread Yitzchak Gale
Bryan Donlan wrote: {-# NOINLINE hDevRandom #-} hDevRandom = unsafePerformIO $ openFile /dev/random ReadMode I wrote: The NOINLINE guarantees that openFile is called only once. But does it guarantee that openFile is NOT called if we do not need it? We could check what the compilers actually

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Yitzchak Gale
On 1/31/07, Kirsten Chevalier [EMAIL PROTECTED] wrote: On 1/31/07, Bill Wood [EMAIL PROTECTED] wrote: On Wed, 2007-01-31 at 19:51 +1100, Donald Bruce Stewart wrote: . . . foldl (\water dish - wash water dish) soapywater dishes :: [Dishes] Nice example. First, note that you can't

Re: [Haskell-cafe] Levels of recursion

2007-02-01 Thread Yitzchak Gale
Hi Andrew, You wrote: combine :: [Int] - [Int] - [[Int]] combine [] _ = [] combine (x:xs) ys = (take x ys) : (combine xs (drop x ys)) ...A much more experienced haskeller told me he preferred to write it like this: combine' :: [Int] - [Int] - [[Int]] combine' xs ys = snd $ mapAccumL aux ys xs

[Haskell-cafe] Importance of MonadRandom

2007-02-01 Thread Yitzchak Gale
I would like to point out the importance of Cale Gibbard's MonadRandom, beyond what is currently mentioned on its wiki page: http://www.haskell.org/haskellwiki/New_monads/MonadRandom This monad makes it possible to write functions that use randomness without having to specify in advance whether

Re: [Haskell-cafe] Re: DevRandom

2007-01-31 Thread Yitzchak Gale
Bryan Donlan wrote: This re-opens the device every time we need it. How about opening once, when it's first needed? Good idea. hDevRandom :: Handle {-# NOINLINE hDevRandom #-} hDevRandom = unsafePerformIO $ openFile /dev/random ReadMode hDevURandom :: Handle {-# NOINLINE hDevURandom #-}

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-31 Thread Yitzchak Gale
Bulat Ziganshin wrote: FP way is to represent everything as function, imperative way is to represent everything as algorithm. Magnus Therning wrote: Neither way may be natural, but imperative thinking is extremely common in society, I'd say much more than functional thinking. Just think of

[Haskell-cafe] DevRandom

2007-01-30 Thread Yitzchak Gale
Have I re-invented the wheel yet again? I have a module the following simple functions, that I have been using for some time: -- Read data from the system random device. -- Return Nothing if there is currently not -- enough entropy in the system random device. devRandom :: Storable a = IO

[Haskell-cafe] Re: DevRandom

2007-01-30 Thread Yitzchak Gale
It's short, so I'll post it here. Any comments? Thanks, -Yitz module DevRandom where import System.IO import System.IO.Error import Foreign.Marshal.Alloc import Foreign.Storable import Foreign.Ptr data BlockingMode = Blocking | NonBlocking deriving (Eq, Show) -- Read data from the system

Re: [Haskell-cafe] Re: Multiparamater class type-inference error

2007-01-29 Thread Yitzchak Gale
Alfonso Acosta wrote: fstSY = mapSY fst No instance for (Synchronous s ((a, b) - a) (a, b) a)... ...no error arises if I explicitly give the type signature of fstSY fstSY :: Signal (a,b) - Signal a This is the notorious Monomorphism Restriction. See

Re: [Haskell-cafe] How did you stumble on Haskell?

2007-01-29 Thread Yitzchak Gale
After many years of OO Perl, I looked at Python. Within fifteen minutes I had switched, and I never looked back at Perl. A few years later, I had a need to hack into the Python interpreter. While reading up on that, I came across references to Haskell. I soon realized that everything I liked

Re: [Haskell-cafe] Simple HTTP lib for Windows?

2007-01-29 Thread Yitzchak Gale
Neil Mitchell wrote: I will be releasing this function as part of a library shortly Alistair Bayley wrote: no! The code was merely meant to illustrate how a really basic HTTP GET might work. It certainly doesn't deal with a lot of the additional cases, like redirects and resource moves, and

Re: [Haskell-cafe] How did you stumble on Haskell?

2007-01-29 Thread Yitzchak Gale
I wrote: I soon realized that everything I liked about Python had been borrowed from Haskell in diluted form. Doaitse Swierstra wrote: I do not think you are entirely right here; a lot of things were borrowed from a language called ABC, See: http://homepages.cwi.nl/~steven/abc/ True. I

Re: [Haskell-cafe] State of OOP in Haskell

2007-01-29 Thread Yitzchak Gale
Steve Downey wrote: OO, at least when done well, maps well to how people think. Um, better duck. I am afraid you are about to draw some flames on that one. I hope people will try to be gentle. OO does NOT always map well to how most people think. OO maps well to how people trained in OO

Re: [Haskell-cafe] Re: IO in lists

2007-01-28 Thread Yitzchak Gale
Hi Magnus, You wrote: This piece has type problems. I couldn't get ghci to accept it without making some changes... You are absolutely correct, and I apologize for the errors. I will try one more time to give a corrected version below. Let me point out, though, that this does not exactly

Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-28 Thread Yitzchak Gale
Frederick Ross wrote: here's my completely anecdotal view of the history of hard in programming... This history is accurate and insightful. ...when the kids... and the professors pretend that it was always this way... then they will grow up... Until then, I will continue to hear people say

Re: [Haskell-cafe] Simple HTTP lib for Windows?

2007-01-28 Thread Yitzchak Gale
Daniel McAllansmith wrote: The cheap and cheerful solution might be to invoke cURL. Or MissingPy. The bottom line is that URL loading is not the same as HTTP. It is higher level. While Haskell does have a nice HTTP library, it does not have a URL loading library yet as far as I can see from

Re: [Haskell-cafe] Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
Neil Mitchell wrote: http://haskell.org/hawiki/MonomorphismRestriction Note to others (esp Cale): does this page not appear on the new wiki? I did a very rough quick conversion: http://www.haskell.org/haskellwiki/MonomorphismRestriction The old wiki is locked, for obvious reasons. But

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Yitzchak Gale
Scott Turner wrote: Paul B. Levy's studies of call-by-push-value model strictness/laziness using a category theoretic approach. That sounds interesting. Do you have a reference for that? Thanks, Yitz ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Yitzchak Gale
I wrote: 1. Find a way to model strictness/laziness properties of Haskell functions in a category in a way that is reasonably rich. Duncan Coutts wrote: The reason it's not obvious for categories is because the semantics for Haskell comes from domain theory (CPOs etc) not categories. The

[Haskell-cafe] Re: Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
I wrote: I did a very rough quick conversion: http://haskell.org/hawiki/MonomorphismRestriction http://www.haskell.org/haskellwiki/MonomorphismRestriction Oops. Moved to: http://www.haskell.org/haskellwiki/Monomorphism_Restriction Alistair Bayley wrote: You can see the source for the page

Re: [Haskell-cafe] Re: IO in lists

2007-01-23 Thread Yitzchak Gale
Hi Dan, You have written a great explanation of how ListT works by writing out its definitions in an interesting way! Dan Piponi wrote: A slightly different approach that doesn't use anything unsafe: A list of type [Char] is essentially a solution to the equation X = Maybe (Char,X) Yes. In

[Haskell-cafe] IO is not a monad

2007-01-23 Thread Yitzchak Gale
troll Prelude let f .! g = ((.) $! f) $! g Prelude let f = undefined :: Int - IO Int Prelude f `seq` 42 *** Exception: Prelude.undefined Prelude ((= f) . return) `seq` 42 42 Prelude ((= f) .! return) `seq` 42 42 /troll Regards, Yitz ___ Haskell-Cafe

Re: [Haskell-cafe] IO is not a monad

2007-01-23 Thread Yitzchak Gale
I wrote: Prelude let f .! g = ((.) $! f) $! g Prelude let f = undefined :: Int - IO Int Prelude f `seq` 42 *** Exception: Prelude.undefined Prelude ((= f) . return) `seq` 42 42 Prelude ((= f) .! return) `seq` 42 42 Duncan Coutts wrote: Perhaps I'm missing something but I don't see what's

Re: [Haskell-cafe] IO is not a monad

2007-01-23 Thread Yitzchak Gale
Hi, Lennart Augustsson wrote: Could you explain why would a class Seq not be sufficient? If there were a class Seq, I'd not want functions to be in that class. Oh, I see. Well that is pretty much the same as ignoring seq altogether. I am hoping to get a better answer than that - where we can

Re: [Haskell-cafe] Re: IO in lists

2007-01-23 Thread Yitzchak Gale
Magnus Therning wrote: I assume you aren't talking about the standard ListT, the one that forces unnecessary strictness, right? But rather how ListT ought to be implemented. Ha! There it is again! :) Regards, Yitz ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Re: IO in lists

2007-01-23 Thread Yitzchak Gale
I wrote: You have written a great explanation of how ListT works by writing out its definitions in an interesting way! Dan Piponi wrote: I put quite a bit of time into understanding why the old ListT isn't a monad [1]. But I thought I didn't yet understand the new one. Now I see that I did, I

Re: [Haskell-cafe] IO is not a monad

2007-01-23 Thread Yitzchak Gale
Hi Brian, Brian Hulley wrote: I thought it was: return x = f = f x ...I think the problem you're encountering is just that the above law doesn't imply: (= f) . return = f Sorry, I was not clear. For the purposes of this thread, I am using the word monad in the category-theoretic

Re: [Haskell-cafe] Fractional sqrt

2007-01-22 Thread Yitzchak Gale
Henning Thielemann wrote: there is already an implementation of continued fractions for approximation of roots and transcendent functions by Jan Skibinski: http://darcs.haskell.org/numeric-quest/Fraction.hs I wrote: Wow, nice. Now - how was I supposed to have found that?

Re: [Haskell-cafe] Fractional sqrt

2007-01-22 Thread Yitzchak Gale
I wrote: I added a new page for the Numeric Quest library... http://www.haskell.org/haskellwiki/Numeric_Quest I also updated the references to Numeric Quest on the Mathematics and Physics page. http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics Henning Thielemann wrote I

Re: [Haskell-cafe] Fractional sqrt

2007-01-21 Thread Yitzchak Gale
Henning Thielemann wrote: Certainly no surprise - there is already an implementation of continued fractions for approximation of roots and transcendent functions by Jan Skibinski: http://darcs.haskell.org/numeric-quest/Fraction.hs Wow, nice. Now - how was I supposed to have found that? It

Re: [Haskell-cafe] Article review: Category Theory

2007-01-20 Thread Yitzchak Gale
I wrote: Time to re-write the Note paragraph yet again. David House wrote: This was a bit much to include in the introduction section I agree 100%. I added a footnote. It's excellent! I tend to take the view that we should ignore seq when talking about abstract language properties

Re: [Haskell-cafe] Fractional sqrt

2007-01-20 Thread Yitzchak Gale
Sorry folks, it is just wrong to use Newton's method for Rational. Andrew Bromage wrote: First off, note that for fractions, sqrt(p/q) = sqrt p / sqrt q. Don't do that for Rational - you lose precious precision. The whole idea for calculations in Rational is to find a lucky denominator that

Re: [Haskell-cafe] for loops and 2d arrays in haskell

2007-01-19 Thread Yitzchak Gale
Hi Fernan, You wrote: what is the simplest way to implement the following code in haskell? it's just printing the contents of 2D array. for(i = 0; i imax; i++){ for(n = 0; n nmax; n++){ printf(%i:%i = %f\n, array[i][n]); } } There are many different ways of

Re: [Haskell-cafe] Fractional sqrt

2007-01-19 Thread Yitzchak Gale
Hi Zoltán, I only need sqrt, so probably I will... use... just the simple Newton alg. It is still not clear to me what type you want to work in. Is it Rational? In that case, you don't need the Newton algorithm. realToFrac . sqrt . realToFrac works fine, as you originally suggested. If that

Re: [Haskell-cafe] Currying

2007-01-18 Thread Yitzchak Gale
Hi, Phiroc wrote: what is so great about currying? What are its uses, apart from letting one define functions with less parentheses? Chris Eidhof wrote: it's just really handy. It saves you a lot of tedious typing I agree. But I think there is more to it than that. Currying is more than

Re: [Haskell-cafe] Article review: Category Theory

2007-01-18 Thread Yitzchak Gale
I wrote: Will (id :: A - A $!) do the trick? Ulf Norell wrote: The problem is not with id, it's with composition. For any f and g we have f . g = \x - f (g x) So _|_ . g = \x - _|_ for any g. OK, so then how about f .! g = ((.) $! f) $! g -Yitz

Re: [Haskell-cafe] Simple HTTP lib for Windows?

2007-01-18 Thread Yitzchak Gale
Alistair Bayley wrote: I'd like to write a very simple Haskell script that when given a URL, looks up the page, and returns a string of HTML. I don't see an HTTP library in the standard libs... Neil Mitchell wrote: MissingH? MissingPy. It would be great to have a full-featured native

Re: [Haskell-cafe] Fractional sqrt

2007-01-18 Thread Yitzchak Gale
Lennart Augustsson wrote: I don't see a much better way than using something like Newton- Raphson and testing for some kind of convergence. The Fractional class can contain many things; for instance it contains rational numbers. So your mysqrt function would have to be able to cope with

Re: [Haskell-cafe] IO in lists

2007-01-17 Thread Yitzchak Gale
I wrote: But the list monad [] is not a transformer, so you can't lift in it, even if the contained type happens also to be a monad. Andrew Bromage wrote: ListT is also not a transformer. True, unfortunately. But it does provide MonadTrans and MonadIO instances that solve problems like this

Re: [Haskell-cafe] Article review: Category Theory

2007-01-17 Thread Yitzchak Gale
David House wrote: I've written a chapter for the Wikibook that attempts to teach some basic Category Theory in a Haskell hacker-friendly fashion. http://en.wikibooks.org/wiki/Haskell/Category_theory Very, very nice! A few comments: A few semicolons were missing in the do blocks of the

Re: [Haskell-cafe] Article review: Category Theory

2007-01-17 Thread Yitzchak Gale
David House wrote: I've added a bit more explanation, so it may now be palatable. It is quite a hard exercise, though, perhaps it shouldn't come so early on. In my opinion, it is now much more clear. And it is a very instructive example. If people still find it too hard, you could add the

Re: [Haskell-cafe] Article review: Category Theory

2007-01-17 Thread Yitzchak Gale
I wrote: It is nice that you gave proofs of the = monad laws in terms of the join monad laws... Maybe give the proofs in the opposite direction as an exercise. David House wrote: Yes, they are, here are my proofs:... I've added the suggested exercise. Alas, too late - you've published the

Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Yitzchak Gale
Magnus Therning wrote: Not a very descriptive subject, I know, but here's what I'd like to do. I can take getChar and create an infinate list: listChars = getChar : listChars but how do I go about creating a finite list, e.g. a list that ends as soon as 'q' is pressed? I was thinking of

Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Yitzchak Gale
Oops, sorry, that should be: listChars2 :: ListT IO Char listChars2 = do c - lift getChar if c == 'q' then return c else return c `mplus` listChars2 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Yitzchak Gale
Iavor Diatchki wrote: The state transformer inherits its behavior from the underlying monad. Ross Paterson wrote: This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted. I think it does - if you run his program with

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Yitzchak Gale
Josef Svenningsson wrote: Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful. I wrote: Are those really needed? ...it wouldn't be very convenient, would it? Sometimes

Re: [Haskell-cafe] HaskellForge?

2007-01-11 Thread Yitzchak Gale
tphyahoo wrote: I think people want something like CPAN. This implies a centralized official repository I agree. I think we also need a notion of a canonical standard package for each popular category. True, it is sometimes nice to have a lot of alternatives to choose from. And to be able to

Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale
Dean Herington wrote: I can't seem to figure out how to achieve strictness in the context of the State monad. Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad. It seems to me that this should clearly be

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale
Hi Bulat, I wrote: [State and StateT] should be consistent. I would much prefer for them both to be lazy. Bulat Ziganshin wrote: imho, lazy monads (as any other lazy things) is a source of beginner's confusion. therefore it may be better to provide default monads as strict and lazy ones -

Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale
Hi Josef, Josef Svenningsson wrote: ...the fun doesn't end there. There are other strictness properties to consider. Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need for control over strictness is =, like Dean's example.

Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale
Wow! Now we are talking! Josef Svenningsson wrote: So instead of: newtype State s a = State { runState :: (s - (a, s)) } we have: newtype StateP p s a = StateP { runStateP :: (s - p a s) } Now, instantiating this with different pair types with different strictness properties will give us total

Re: [Haskell-cafe] State monad strictness - how?

2007-01-10 Thread Yitzchak Gale
...how would one know that State is lazy and StateT is strict? I don't see that in the Haddock documentation. You're right, it is not in the docs. I don't think anyone would have planned it that way. StateT is strict only because there happens to be a line in a do-expression that looks like:

Re: [Haskell-cafe] trouble installing greencard -- -fno-prune-tydecls flag ( was Re: trivial function application question )

2007-01-08 Thread Yitzchak Gale
I wrote: In the meantime, how about the following: In default non-verbose mode, silently memoize the list of packages that were not found. Then, only if something goes wrong, say something like: The package failed to build. Perhaps the reason is that one of the following packages was not

Re: [Haskell-cafe] trouble installing greencard -- -fno-prune-tydecls flag ( was Re: trivial function application question )

2007-01-07 Thread Yitzchak Gale
Ross Paterson wrote: Cabal would need to crawl over the source files to see what preprocessors are really needed. Duncan Coutts wrote: Yes, this is exactly what Cabal should do. In the meantime, how about the following: In default non-verbose mode, silently memoize the list of packages

Re: [Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-05 Thread Yitzchak Gale
Brian Hulley wrote: ...allow a superclass (or ancestor class) method default to be redefined in a subclass. This has been proposed several times over the years. I remember seeing Simon PJ propose it within the past year or two, I think. I personally have needed this on several occasions. So I

Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Yitzchak Gale
tphyahoo wrote: There are various haskell regex libraries out there, Jules Bean wrote: But that's such a perler attitude. When all you have is a regex, everything looks like a s///! Not always, sometimes it is right to use regexes in Haskell also. If there are more than a few patterns to

Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale
Seth Gordon wrote: From a friendliness-to-newbies point of view, these error messages are a tremendous wart... Eeeww. Neil Mitchell wrote: If the interface for some feature requires rank-2 types I'd call that an abstraction leak in most cases. As the original poster of this thread, the one

Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale
Paul Moore wrote: ...your nice helpful intuitions about monads can break down into real confusion when you hit complex monads, monad transformers and the like - *and you hit them quite early in the APIs of some libraries*! I don't think that is a problem with the design of the libraries. It is

Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale
I wrote: Combining ST and MTL can be messy, even in this simple case. You will probably write something with a type like RandomGen g = [a] - g - ST s ([a], g) Udo Stenzel wrote: But why would you even want to do this? It's ugly and cumbersome. Yes indeed. You'd plug a runST in there and

Re: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale
I wrote: Am I missing something? Yes! In reality, I do not need unsafeSTRef for this at all, using a type suggested earlier by Udo: stToState :: MonadState st m = (forall s. STRef s st - ST s a) - m a stToState f = do s - get let (y, s') = runST (stm f s) put s' return y where

Re: Re[2]: [Haskell-cafe] Composing functions with runST

2007-01-04 Thread Yitzchak Gale
Hi Bulat, I wrote: One is the confusion caused by the strange semantics to those not familiar with the theory... Like me, of course. The other is awkwardness in extending the capabilites of ST. For that, I would propose that the function unsafeRunST be added to the library. Bulat

Re: [Haskell-cafe] Composing functions with runST

2007-01-02 Thread Yitzchak Gale
Hi Thomas, You wrote: How do I import Control.Monad.ST so I can experiment with it from ghci and just do runST like you had. Instead of qualifying it in some way. In GHCi, use the :module command (:m) for built-in modules, and :load and :add for source files. In Hugs, use :load and :also

Re: [Haskell-cafe] Announce: Package rdtsc for reading IA-32 time stamp counters

2007-01-02 Thread Yitzchak Gale
On 1/2/07, Martin Grabmueller wrote: version 1.0 of package rdtsc has just been released. This small package contains one module called 'Rdtsc.Rdtsc'. This module provides the function 'rdtsc' for accessing the 'rdtsc' machine register on modern IA-32 processors. Very nice! I have a few

[Haskell-cafe] Composing functions with runST

2007-01-01 Thread Yitzchak Gale
Can anyone explain the following behavior (GHCi 6.6): Prelude Control.Monad.ST runST (return 42) 42 Prelude Control.Monad.ST (runST . return) 42 interactive:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1' In the second argument of `(.)', namely

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Yitzchak Gale
I wrote: Prelude Control.Monad.ST runST (return 42) 42 Prelude Control.Monad.ST (runST . return) 42 interactive:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1' Brian Hulley wrote: Hazarding a guess, I suggest it *might* be due to the fact that

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Yitzchak Gale
Brandon S. Allbery KF8NH wrote: I think the problem is that technically runST is a data constructor (possibly not relevant) No, at least not in GHC. It is a function. which takes a function as a parameter (definitely relevant). It takes the type (forall s. ST s a) as its only parameter.

[Haskell-cafe] Re: Composing functions with runST

2007-01-01 Thread Yitzchak Gale
The plot thickens... It seems that I can't even use STRefs. Something is really wrong here. Prelude Control.Monad.ST Data.STRef runST $ do {r-newSTRef 2; readSTRef r} interactive:1:8: Couldn't match expected type `forall s. ST s a' against inferred type `a1 b' In the second

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Yitzchak Gale
Simon Peyton-Jones wrote: There is nothing wrong with the program you are writing, but it's hard to design a type inference algorithm that can figure out what you are doing. Thank you for your response. What I was actually trying to do was this: It seems to me that a natural notion of a state

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Yitzchak Gale
I wrote: It seems to me that a natural notion of a state transformer in the ST monad is the type: STRef s st - ST s a Udo Stenzel wrote: Are there any useful functions of this type? Sure. Anything that can be written as a pure state transformer can be written this way, of course. In

Re: [Haskell-cafe] A type class puzzle

2006-11-02 Thread Yitzchak Gale
On Tue, Oct 31, 2006 I wrote: Consider the following sequence of functions that replace a single element in an n-dimensional list: replace0 :: a - a - a replace1 :: Int - a - [a] - [a] replace2 :: Int - Int - a - [[a]] - [[a]] Generalize this using type classes. Thanks to everyone for the

[Haskell-cafe] A type class puzzle

2006-10-31 Thread Yitzchak Gale
Consider the following sequence of functions that replace a single element in an n-dimensional list: replace0 :: a - a - a replace0 = const replace1 :: Int - a - [a] - [a] replace1 i0 x xs | null t= h | otherwise = h ++ (replace0 x (head t) : tail t) where (h, t) = splitAt i0 xs replace2

Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Yitzchak Gale
Tomasz Zielonka wrote: It's quite easy if you allow the indices to be put in a single compound value. Hmm. Well, I guess I don't need to insist on the exact type that I gave in the statement of the puzzle - although something like that would be the nicest. This is actually a function that is

[Haskell-cafe] Haskore dependency trouble

2006-07-12 Thread Yitzchak Gale
I am having trouble installing Haskore due to a dependency issue. I am a pampered user of Debian. Thanks to wonderful work by the Cabal people and the Debian package maintainers, I have never had to use Cabal manually to install a package before. In order to learn how to do that, I practiced by

Re: [Haskell-cafe] Haskore dependency trouble

2006-07-12 Thread Yitzchak Gale
Henning Thielemann (lemming) wrote: ...Yitz Gale wrote: I am having trouble installing Haskore due to a dependency issue... Cabal... The configure command fails with the following error: Setup.lhs: cannot satisfy dependency Hsc-any This belongs to a SuperCollider wrapper:

Re: [Haskell-cafe] Haskore dependency trouble

2006-07-12 Thread Yitzchak Gale
Setup.lhs: cannot satisfy dependency Hsc-any This belongs to a SuperCollider wrapper: http://www.slavepianos.org/rd/f/409875/ Thanks! I'll just install the Debian package. I installed the supercollider Debian package, got hsc using darcs and installed it using Cabal. All seemed to work

[Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Yitzchak Gale
I personally use split :: Eq a = [a] - [a] - [[a]] all the time, much more often than splitBy :: (a - Bool) - [a] - [[a]] But I don't call it split. By analogy with concatMap, the Haskell analogue of Perl/Python join is concatIntersperse. Then, by analogy with lines/unlines, the Haskell

Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Yitzchak Gale
Is there a shorter way to write the if-then-else part below? -- tryTakeSeat :: [Word8] - Word8 - ScriptState (Maybe Word8) tryTakeSeat _ _ = do ... if (cmdType cmd) /= (CmdSitError Server) then return $ Just seat_num else return Nothing -- tryTakeSeat _ _

[Haskell-cafe] Monad strictness

2005-11-21 Thread Yitzchak Gale
In the following, why does testA work and testB diverge? Where is the strictness coming from? Thanks, Yitz module Test where import Control.Monad.State import Control.Monad.Identity repeatM :: Monad m = m a - m [a] repeatM = sequence . repeat testA = take 5 $ flip evalState [1..10] $

Re: [Haskell-cafe] generics question, logical variables

2005-09-19 Thread Yitzchak Gale
Ralf Lammel wrote: Does anyone want to speak up and mention scenarios that would benefit from kind polymorphism? (In Haskell, we are likely to see kind polymorphism, if at all, in the form of type classes whose type parameters can be of different, perhaps of all kinds.) Here are two

Re: [Haskell-cafe] Newbie syntax question

2005-09-18 Thread Yitzchak Gale
Hi, Andre, map (foo 5) my_list_of_lists_of_doubles ...But how to do that (if possible) when I invert the parameters list ?! Let me add one more solution, and then summarize: The problem disapears if you use a list comprehension instead of map: [foo x 5 | x - my_list_of_lists_of_doubles]

Re: [Haskell-cafe] Language Workbenches - the Haskell solution?

2005-09-13 Thread Yitzchak Gale
Correction - I wrote: If you want a GUI for configuration, you could, for example, write a fairly simple transformation of the master XML into a .NET dialog, or glade file for GTK, or whatever. We never did that, though. Actually, Yael Weinbach wrote a beautiful GUI for this configuration

Re: [Haskell-cafe] Language Workbenches - the Haskell solution?

2005-09-12 Thread Yitzchak Gale
Ralf Lammel wrote: XML... I wonder whether they discuss it... yoann padioleau wrote: Yes, fowler mentionned XML: XML has its uses, but isn't exactly easy to read... I dont think XML is a good idea for files that are managed/edited by humans. It can be very human readable if set up

Re: [Haskell-cafe] Monadic vs pure style (was: pros and cons of sta tic typing and side effects)

2005-09-01 Thread Yitzchak Gale
On Thu, Sep 01, 2005 at 12:41:06AM -0700, Juan Carlos Arevalo Baeza wrote: You can get the correct order by using lists, but you want to use the Asc versions: myMapM someAction someMap = do list - sequence $ map (\(k, a) - someAction a = (\b - return (k,b))) $

Re: [Haskell-cafe] Monadic vs pure style (was: pros and cons of sta tic typing and side effects)

2005-08-30 Thread Yitzchak Gale
There seems to be a misconception in this thread that there is something non-functional or imperative about using monads. That is simply not true. When what you are trying to write is most naturally and clearly expressed as a series of steps - there is no reason not to use a monad. Even when a

[Haskell-cafe] Re: Coin changing algorithm

2005-07-14 Thread Yitzchak Gale
Actually, something along the lines of Dinh's attempted solution to the original partition problem is a very nice solution to the coin changing problem: Make change for the amount a, using at most k of the coins cs. coins _ 0 _ = [[]] coins _ _ 0 = [] coins cs a k = [h:s | t - init (tails

<    1   2   3   4   5   6   >