On Sat, 30 Mar 2002, Richard Uhtenwoldt wrote: > The bottom line is a social one: language communities compete fiercely > for programmers. There is no shortage of languages with open-sourced > implementations in which James could have written his program. (Er, > actually James is embedding a DSL in Haskell, which brings many > programmers to Haskell.) If we want Haskell to grow, we must make > it as easy as possible for programmers to solve their problems in > Haskell. > > Of course there are some things that are essential to Haskell that we > should not compromise on. Those who describe a >> b = a >>= \_ -> b > as a law might maintain that it is one of those essential things. > Well, to them I ask, are id x = x and const x y = y laws, too? How > about fix f = f (fix f)? swap (a,b) = (b,a)? > > mirror (Right a) = Left a > mirror (Left a) = Right a?
This brings up a point in my mind. What should one do instances of the class Monad which might violate some monad law? THE MONAD LAWS [1] 1. return a >>= k = k a 2. m >>= return = m 3. m >>= (\x -> k x >>= h) = (m >>= k) >>= h ####long discursion begins, go down far below to see my point #### I was going to have a section in the Strictness FAQ I'm writing which gives examples why lazy evaluation rocks, so to remind the readers that there are reasons for haskell using a lazy evaluation strategy. (I'm sad to say that this is one of sections I don't think I'll complete to the point of releasing anytime soon.) Here's the long story of one of the examples I'm contemplating. I one day came across this idea for a monad. For background, the list (nondeterminism) monad is defined as something like [2] instance Monad [] where return x = [x] >>= = bindL [] `bindL` f = [] (x:xs) `bindL` f = f x ++ (xs `bindL` f) this looks equivalant to the Haskell reports definition for >>= m >>= k = concat (map k m) I suppose this is (partially) used to define the list comprehensions we grew to like so well, and you can use those to write expressions almost like you could query a database, or give all possible scenarios, or whatever. One problem with this definition may be that you can only find out all possible scenarios for finite lists only (except for the first binded list, which could be infinite. Example. [(a,b,c) | a<-[1..],b<-[True,False],c<-"Cheeze Whiz"] Analyzing the above definition you may find that the cuprit is (++). So, what's another way to join two lists so that members of both lists will eventially be found in the combined list? Interweave them! [3]. >interleave [] l' = l' >interleave (x:xs) l' = x :interleave l' xs So you might think that all you have to do is switch `interleave` for (++) and you have this new, powerful monad that allows you to combine elements from anysize lists (countable or finite) and generate every expression thereof. >unC1 (C1 x) = x >newtype C1 a = C1 [a] > >instance Monad C1 where > return x = C1 [x] > (C1 []) >>= f = C1 [] > (C1 (x:xs)) >>= f = C1 $ > unC1 (f x) `interleave` unC1 (C1 xs >>= f) > >allnats = [1..]::[Integer] > >-- generate_all_integers >-- use C1 constructor so we can use that monad instance. > >g = C1 (0:(interleave allnats (map negate allnats))) > >all_integral_3dpoints = unC1 $ > do x<-g > y<-g > z<-g > return (x,y,z) >--give all points that have a integral distance from the origion > >anyzero (0,_,_) = True >anyzero (_,0,_) = True >anyzero (_,_,0) = True >anyzero _ = False >points = filter (issquare . (\(x,y,z) -> x^2+y^2+z^2)) > $ filter (not . anyzero) all_integral_3dpoints > <snip> definition of issquare, a predicate which determines if a integer is the square of another, is left up to the imagination of the reader >main = print $ (take 10 points) We'll call it a Cantor Monad for lack of imagination (Cantor is the mathematician that is associated with the many concepts of infinity and countablility) And you are all good and happy. The only problem is, you HAVEN'T DEFINED A MONAD! It disobeys the monad associativity law! That is, it violates this [1] m >>= (\x -> k x >>= h) = (m >>= k) >>= h (or to restate this) do x <- m;y <-k x; h y = do y<- (do x <- m; k x); h y This can be checked by seeing that list1 is not equal to list2 in this snippit. >k x = do y<-g > return (x,y) >h (x,y) = do z<-g > return (x,y,z) >list1 = unC1 $ g >>= (\x-> k x >>= h) >list2 = unC1 $ (g >>= k)>>= h >main = > do print "first list" > print (take 10 list1) > print "second list" > print (take 10 list2) (whew! this is a long message!) However, I am not completely certain as to a verifiable proof of what I am about to say, but I'm very certain that you could say that list1 is SET equal to list 2, in otherwords, every element in list2 is in list2, and visa versa. So, assuming I had that proof, what would I call this? a non associative monad? a psuedo-monad? a quasi-monad? A funky-monkey-monad? I mean, I have heard of non-associative algebras or what-not, why cant monads have the same nomenclature? #### POINT COMMING UP #### I have defined something like a monad which violates a monad law, but probably holds for (with a weaker measurement of equality). Assuming it does hold, what should be done with it? Jay Cox [1] typed directly from Paul Hudak's The Haskell School of expression, pg 254. any errors are mine [2] adapted from the paper Monadic Parser Combinators, pg 26. Grahm Hutton and Erik Meijer. (any errors are mine, again) [3]: i stole the idea of interleaving from SICP 2nd Ed pg 341, which also got it from somewhere else... follow the trail back as far as you want. _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell