Re: Monads
Rijk-Jan van Haaften >>= Hannah Schroeter: > > ... However, not using the Monadic do syntax results in > > hardly-readible code. > > I don't really think so. The operator precedences for >> and >>= are > quite okay, especially combined to the precedence of lambda binding. ... > main = do > putStr "Hello! What's your name?" ... > Yes, I use do syntax where appropriate (e.g. also for usual parser > monads), however, the operator syntax can be written quite readably > too. I would add that sometimes you may be interested in Monadic SEMANTICS at a more profound level, trying to hide it completely at the surface. Then, the <> syntax is an abomination. The examples are already in the Wadler's "Essence". Imagine the construction of a small interpreter, a virtual machine which not only evaluates the expressions (belonging to a trivial Monad), but perform some side effects, or provides for exceptions propagated through a chain of Maybes. Then the idea is to * base the machine on the appropriate Monad * "lift" all standard operators so that an innocent user can write (f x) and never x >>= f (or even worse). The <> construct in such a context resembles the programming in assembler, and calling it more readable is h... not very convincing. (My favourite example is the "time-machine" monad, a counter-clock-wise State Monad proposed once by Wadler, and used by myself to implement the reverse automatic differentiation algorithm. Understanding what's going on is difficult. The <> syntax makes it *worse*.) Jerzy Karczmarczuk Caen, France ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Wadler (was RE: Monads)
On 2001-05-17T09:35:19-0400, Joe Bowers wrote: >There have been several references to "a paper by >Wadler" in this thread- some folks (well, at least >one folk :) on this list may not be familiar with >the work surrounding Haskell yet, and (from this context) >This paper seems like a pretty good place to start. > >Would anybody have a detailed citation for it, >or (even better) is it up on the web? Wadler's monad papers, including "Comprehending Monads", are at http://cm.bell-labs.com/cm/cs/who/wadler/topics/monads.html -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig My god, I've seen heaven. - Flute at Band Camp PGP signature
Re: Questions about Trie
> "M. Faisal Fariduddin Attar Nasution" wrote: > > Greeting, I'm a last year student in a computer science field. I'm > currently trying to code an implementation for a compression using > basic Lempel-zif technique. I use a Trie (retrieval) as a data > structure for the dynamic dictionary aplication. The problem is Trie > uses not just an ordinary binary tree, but it uses a multiple-weighted > tree, where one node has at most 256 children. Most literatures about > Haskell show only binary tree for the example in tree or Abstract Data > Structures subject. So, does anyone know how to code the > implementation for trie. Thanks for paying attention and I'm really > hoping for the answer immediately. > IIRC, there's a trie implementation in Chris Okasaki's "Purely Functional Data Structures" -- that might be a start (there's also his "Edison" library, which contains many of the components you'd need). HTH (and sorry if it doesn't) --ag -- Artie Gold, Austin, TX (finger the cs.utexas.edu account for more info) mailto:[EMAIL PROTECTED] or mailto:[EMAIL PROTECTED] -- I am looking for work. Contact me. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
Ashley Yakeley wrote: > At 2001-05-17 02:03, Jerzy Karczmarczuk wrote: > > >Monads are *much* more universal than that. [...] > >[...] Imperative programming is just one facet of the true story. > > Perhaps, but mostly monads are used to model imperative actions. And > their use in imperative programming is the obvious starting point to > learning about them. I don't know about that; I use monads most often when dealing with container classes (sets, bags, lists). They also provide a useful way to reason about parts of XPath and XSLT. As far as learning about them goes, I don't think I really "got" monads until reading Wadler's aptly-titled "Comprehending Monads", which approaches them from this perspective. --Joe English [EMAIL PROTECTED] ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Proposal for generalized function partition in List-library
17 May 2001 19:36:44 GMT, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> pisze: > PS. What I would perhaps put into standard library: And also: split :: (a -> Bool) -> [a] -> [[a]] split p c = let (xs, ys) = break p c in xs : case ys of [] -> [] _:zs -> split p zs softSplit :: (a -> Bool) -> [a] -> [[a]] -- softSplit p c = filter (not . null) (split p c) softSplit p c = case dropWhile p c of [] -> [] x:xs -> let (ys, zs) = break p xs in (x:ys) : softSplit p zs It follows that words = softSplit isSpace. Any better name? -- __("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Proposal for generalized function partition in List-library
Thu, 17 May 2001 10:06:55 +0200, Bernd Holzmüller <[EMAIL PROTECTED]> pisze: > I would like to propose a new function for module List that generalizes > the current function partition :: (a -> Bool) -> [a] -> [[a]] No, current partition has type (a -> Bool) -> [a] -> ([a], [a]) so your function is not compatible with it, so shouldn't replace such standard function. > partition:: Eq b => (a -> b) -> [a] -> [[a]] > partition _ [] = [] > partition f (a:as) = >let (as',as'') = foldr (select (f a)) ([],[]) as >in (a:as'):partition f as'' > where >select b x (ts,fs) | f x == b = (x:ts,fs) > | otherwise = (ts,x:fs) This function doesn't give a hint which sublists correspond to which results of the function, so I'm afraid it's easy to make errors by assuming that they will come in a different order. And it's inefficient: the cost is the number of elements times the number of different results of the function. I would write it thus: \f xs -> groupBy (\(a, _) (b, _) -> a == b) $ sortBy (\(a, _) (b, _) -> compare a b) [(f x, x) | x <- xs] You can apply 'map (map snd)' to the result to remove the results of f. I don't have a good name for it and I'm not sure it's common enough to put it in the standard library. It can also be more efficiently written using Array.accumArray for particular types of the result of the function. PS. What I would perhaps put into standard library: uniq :: Eq a => [a] -> [a] uniqBy :: (a -> a -> Bool) -> [a] -> [a] so people don't use nub unnecessarily (if elements are adjacent or can be made adjacent by sorting), and takeLastWhile :: (a -> Bool) -> [a] -> [a] dropLastWhile :: (a -> Bool) -> [a] -> [a] spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) (with some better names) which iterate forward and are lazy, to avoid double reversing in case the test is cheap but the list is long, and partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a]) Here are implementations of some of these: takeLastWhile p xs = case span p xs of (ys, []) -> ys (_, _:zs) -> takeLastWhile p zs dropLastWhile p xs = case span p xs of (_, []) -> [] (ys, z:zs) -> ys ++ z : dropLastWhile p zs spanEnd p xs = case span p xs of (ys, []) -> ([], ys) (ys, z:zs) -> (ys ++ z : ys', zs') where (ys', zs') = spanEnd p zs -- __("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Proposal for generalized function partition in List-library
this is just how I understand things at the moment, if I am wrong or misleading anywhere then please speak up. I am unconvinced that such generalizations must come as speed hits, but perhaps someone can enlighten me. compilers seem to support seperate compilation and polymorphism at the moment by boxing polymorphic types and passing their class-context (term?) as a hidden parameter to the polymorphic function. but it seems that since haskell is strongly type checked at compile time, we already KNOW all of the types with certainty when it comes to compiling the program in the end so this would seem to be unnecisarry. now there are two cases where this breaks down * seperate compilation * code bloat namely that you don't necisarilly know all of the types of polymorphic functions when they are in a module that is compiled seperately from the rest of the program. the solution used by many C++ compilers is to inline all polymorphic code in place (this is why templates are in header files). there is no reason this won't work in haskell and give back all of the speed benefits of base types everwhere (as it would in this example) but has the unfortunate side effect of causing worst case exponential code bloat as every function is re-written for every type combination it is used with. the solution I see (and probably exists) is a hybrid model, one that lets the compiler know to specialize certain polymorphic functions as well as let the compiler utilize such specialized functions. a pragma which lets the compiler know that a certain specialization would be useful such as partition :: (Eq b) => (a -> b) -> [a] -> [[a]] partition fn ls = ... {-# specialize partition :: (a -> Bool) -> [a] [[a]] -} which would let the compiler know to generate code for partition specificially optimized for (a -> Bool) and thus obviating the need for the Eq hidden argument. the fully polymorphic version would of course also have to be generated. specializations would be advertised in the header file and utilized whenever the typechecker determined you were using partition in the specialized case. this seems like a better solution than the current practice of providing seperate general and specific functions, take, genTake, max, genMax and whatnot. you would just specify that specializations for the case of 'Int' should be generated as it would be the most common case. an {-# inline partition -} might also be useful which would actually place the text of the function into the .hi file to be in-line expanded as is done in C++... I imagine there would be some tweaking to determine when this is a win and when it isn't... some of this stuff probably exists in current compilers, but polymorphism need not be at the expense of speed. -John On Thu, May 17, 2001 at 12:36:39PM +0200, Michal Gajda wrote: > On Thu, 17 May 2001, Bernd [iso-8859-2] Holzmüller wrote: > > This partitioning function builds equivalence classes from the list > > argument, where each element list within the result list consists of > > elements that all map to the same value when applying f to it. > > Thus: partition (`div` 2) [1..5] yields [[1],[2,3],[4,5]] > > > > This is much more general than the existing partitioning function and > > applicable in many practical cases. > > But here generality comes at the expense of speed I think. -- -- John Meacham http://www.ugcs.caltech.edu/~john/ California Institute of Technology, Alum. [EMAIL PROTECTED] -- ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
MVar Problem (Concurrent Hugs)
Hello, I was trying to write an abstraction for bidirectional communication between two threads. For some reason, MVars seem to break: --- class Cords c t u where newCord :: IO (c t u) listen :: c t u -> IO t speak :: c t u -> u -> IO () data Cord t u = Cord (IO (MVar t)) (IO (MVar u)) instance Cords Cord t u where newCord = return (Cord newEmptyMVar newEmptyMVar) speak (Cord _ s) t = do s' <- s ; putMVar s' t listen (Cord h s) = do h' <- h ; takeMVar h' otherEnd (Cord t u) = Cord u t showT :: Cord Int String -> IO () showT cord = do putStrLn "Runnning..." x <- listen cord putStrLn ("Heard " ++ show x) speak cord (show x) putStr ("Said " ++ (show x)) showT cord main :: IO () main = do cord <- newCord forkIO (showT (otherEnd cord)) speak cord 1 str <- listen cord putStrLn str --- Hugs writes: Main> main Runnning... Program error: no more threads (deadlock?) (131 reductions, 307 cells) Any ideas? Thanks, Andreas. Andreas Gruenbacher [EMAIL PROTECTED] Research Assistant Phone +43(1)58801-12723 Institute for Geoinformation Fax+43(1)58801-12799 Technical University of Vienna Cell phone +43(664)4064789 ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
RE: Ix class
I rather agree with Matt's message below. I'm desperately trying NOT to change the H98 libraries, but this is a very non-disruptive change, as he points out, and it does lift two apparently-unnecessary restrictions. a) Remove Ord from Ix's superclasses b) Add rangeSize to Ix's methods Does anyone have any thoughts about this. (We made a similar change to Random, adding a method.) Simon | -Original Message- | From: Matt Harden [mailto:[EMAIL PROTECTED]] | Sent: 16 May 2001 00:43 | To: Haskell list | Subject: Ix class | | | Hello, | | I am working on an Ix instance for one of my types and | finding it rather restrictive. For me it would be useful to | have rangeSize be defined in the Ix class (with a default | definition of course), so that it can be overridden. | | Also, does anybody know why Ix derives from Ord? It seems to | me this is an unnecessary limitation on the types that can be | instances of Ix. I cannot think of a reason why the | implementation of anything in the Ix or Array modules would | require that every Ix be an Ord (with a minor exception -- | see below). If an implementation is using a comparison on an | Ix type, chances are it should be using inRange or comparing | (index bnds x) with (index bnds y) instead. | | One change would have to be made in the Array module if Ord | is removed from Ix: | instance (Ix a, Eq b) => Eq (Array a b) where | a == a' = assocs a == assocs a' | instance (Ix a, Ord b) => Ord (Array a b) where | a <= a'= assocs a <= assocs a' | | would become: | instance (Ix a, Eq a, Eq b) => Eq (Array a b) where | a == a' = assocs a == assocs a' | instance (Ix a, Ord a, Ord b) => Ord (Array a b) where | a <= a'= assocs a <= assocs a' | | As I said, I think this is a very minor issue. | | I believe that making these changes in the standard would not | impact existing programs in any way. Could these changes be | considered as a possible "typo" to be fixed in the Library Report? | | | P.S. In case anybody's interested, here's why I want to override | rangeSize: | | > newtype Honeycomb = Hx (Int,Int) deriving (Eq,Show,Ord) | > | > indexError = error "Index out of range" | > | > instance Ix Honeycomb where | >range (Hx b1, Hx b2) = | > [Hx x | x <- range (b1,b2), isHexIx x] | >inRange (Hx b1, Hx b2) (Hx x) = | > inRange (b1,b2) x && isHexIx x | >index (Hx b1, Hx b2) (Hx x) = | > let i = index (b1,b2) x in | > if isHexIx x then i `div` 2 else indexError | > | > isHexIx :: (Int,Int) -> Bool | > isHexIx (x,y) = x `mod` 2 == y `mod` 2 | | This implements a honeycomb or hexagonal tiling for a maze | generating program. The honeycomb is superimposed on a grid | such that only every other square is "active", corresponding | to a particular hexagon in the honeycomb. It's similar to a | checkers game, where only the dark squares are used. | | I would like _any_ pair of Ints to be an acceptable boundary | for the honeycomb, not just the ones that represent valid | indexes. For example, (Hx (0,0), Hx (15,12)) should be a | valid set of bounds. The current definition of rangeSize | makes this impossible, which is why I would like to override | it. By the way, the Library Report does not explicitly say | that the bounds have to both be valid indexes, though it does | imply this with the sample definition of rangeSize. | | Thanks, | Matt Harden | | ___ | Haskell mailing list | [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell | ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
Hello! On Thu, May 17, 2001 at 11:57:45AM +0200, Rijk-Jan van Haaften wrote: > >So what you are saying is that I actually don't need > >Monads to perform the tasks Monads supports ? > Indeed. However, not using the Monadic do syntax results in > hardly-readible code. I don't really think so. The operator precedences for >> and >>= are quite okay, especially combined to the precedence of lambda binding. How is main = getLine >>= \line -> let number = read line in let result = number + 42 in print result less readable than main = do line <- getLine let number = read line let result = number + 42 print result ? Or main = putStr "Hello! What's your name?" >> getLine >>= \name -> putStrLn ("Hello, " ++ name ++ "!") compared to main = do putStr "Hello! What's your name?" name <- getLine putStrLn ("Hello, " ++ name ++ "!") > [...] Yes, I use do syntax where appropriate (e.g. also for usual parser monads), however, the operator syntax can be written quite readably too. Kind regards, Hannah. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Questions about Trie
Greeting, I'm a last year student in a computer science field. I'm currently trying to code an implementation for a compression using basic Lempel-zif technique. I use a Trie (retrieval) as a data structure for the dynamic dictionary aplication. The problem is Trie uses not just an ordinary binary tree, but it uses a multiple-weighted tree, where one node has at most 256 children. Most literatures about Haskell show only binary tree for the example in tree or Abstract Data Structures subject. So, does anyone know how to code the implementation for trie. Thanks for paying attention and I'm really hoping for the answer immediately. Aerith Gainsborough (Final Fantasy VII)"All I know is..." "The Cetra were born from the Planet, speak with the Planet, and unlock the Planet." "And... then.." "The Cetra will return to the Promised Land. A land that promises supreme happiness." ===M. Faisal Fariduddin Attar Nasution---[EMAIL PROTECTED]
Final CfP: BABEL Workshop on Multilanguage Infrastructure and Interoperability
BABEL'01 FINAL CALL FOR PAPERS First Workshop on Multi-Language Infrastructure and Interoperability http://research.microsoft.com/~nick/babel01.htm Satellite to PLI'01 Firenze, Italy, 8th September 2001 Submission Deadline: 1st June 2001 ** The Submission Site is now open ** http://cmt.research.microsoft.com/BABEL01/ AIMS AND SCOPE Recent years have seen a resurgence of interest in multi-language tools and intermediate languages, and in interoperability between programs and components written in different programming languages. Shared infrastructure such as code generators, analysis tools and garbage collectors can greatly ease the task of producing a high-quality implementation of a new programming language, whilst being able to interoperate easily with code written in existing languages is essential for such an implementation to be useful in practice. This workshop aims to bring together researchers and developers working on multi-language integration. Contributions are welcome on topics including, but not limited to: * Compilation of high level languages to common executable formats such as Sun's Java Virtual Machine, the DRA's ANDF or Microsoft's .NET Common Language Runtime. * Defining and using bindings for component middleware such as OMG's CORBA or Microsoft's COM. * Language constructs to support interoperability between different languages, particularly from different paradigms (e.g. OO/functional). * Multi-language backends for compilation and/or analysis (e.g. MLRISC, FLINT, C--, TAL, SUIF). * Type theoretic and semantic foundations for multi-language work. * Multi-language development environments and tools (e.g. debuggers, profilers). Submissions may address any programming paradigm. Experience papers which describe the use of multiple languages in application development are also welcome. Authors unsure of the appropriateness of a potential submission should email the PC chair ([EMAIL PROTECTED]). PROGRAMME COMMITTEE Nick Benton (chair) Microsoft Research Fergus Henderson University of Melbourne Andrew Kennedy (organiser) Microsoft Research Greg Morrisett Cornell University Martin Odersky Ecole Polytechnique Federale de Lausanne John Reppy Bell Labs Andrew Tolmach Portland State University David Wakeling University of Exeter INVITED SPEAKERS Zhong Shao Yale University IMPORTANT DATES Deadline for submission 1st June 2001 Notification of acceptance 9th July 2001 Final version due 10th August 2001 SUBMISSION DETAILS Papers should be at most 14 pages and should be submitted in Ghostscript-compatible PostScript or PDF format and be printable on both US letter and A4 paper. Authors are strongly encouraged to use ENTCS style files (see http://math.tulane.edu/~entcs/). Papers should be submitted electronically via the submission site at http://cmt.research.microsoft.com/BABEL01/ Submissions should not overlap significantly with work which has already been published or submitted to any other conference or journal. An informal proceedings will be published as a technical report and distributed at the workshop. It is intended that a final proceedings will be published in a volume of ENTCS.
RE: Monads
I should probably mention that one doesn't need to know that a list is a monad in order to use a list. However, understanding that a list obeys the monad laws is a useful way to learn about monads. --PeterD > -Original Message- > From: Peter Douglass > Sent: Thursday, May 17, 2001 9:26 AM > To: '[EMAIL PROTECTED]'; [EMAIL PROTECTED] > Subject: RE: Monads > > > Monads are used not only for programming IO, state, > exceptions etc, but also > are the foundation of lists. It is hard to imagine > functional programming > without this basic datatype. Sets, Bags, trees etc are also > monads. Phil > Wadler wrote a very useful paper Comprehending Monads which I > notice is not > found on the Haskell/bookshelf web page. It can be found at > > http://www.cs.bell-labs.com/who/wadler/topics/monads.html > > I recommend this page for anyone interested in monads. > --PeterD > > > > -Original Message- > > From: Mads Skagen [mailto:[EMAIL PROTECTED]] > > Sent: Thursday, May 17, 2001 4:25 AM > > To: [EMAIL PROTECTED] > > Subject: Monads > > > Hi > > > I'v currently working on a school-project where I have > > to describe the Haskell programming language. > > > I've been looking through Monads and especially the IO > > monad, the Maybe monad and the list monad > > > > My question is why are monads necessary in the > > language ? > > > Is it not possible to construct the features provided > > by Monads using basic functional constructs ? > > > What do I gain using Monads ? > > > Thank you very much. > > > Regards Skagen > > > ___ > Haskell mailing list > [EMAIL PROTECTED] > http://www.haskell.org/mailman/listinfo/haskell > ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Wadler (was RE: Monads)
Title: Wadler (was RE: Monads) There have been several references to "a paper by Wadler" in this thread- some folks (well, at least one folk :) on this list may not be familiar with the work surrounding Haskell yet, and (from this context) This paper seems like a pretty good place to start. Would anybody have a detailed citation for it, or (even better) is it up on the web? Joe
RE: Monads
Monads are used not only for programming IO, state, exceptions etc, but also are the foundation of lists. It is hard to imagine functional programming without this basic datatype. Sets, Bags, trees etc are also monads. Phil Wadler wrote a very useful paper Comprehending Monads which I notice is not found on the Haskell/bookshelf web page. It can be found at http://www.cs.bell-labs.com/who/wadler/topics/monads.html I recommend this page for anyone interested in monads. --PeterD > -Original Message- > From: Mads Skagen [mailto:[EMAIL PROTECTED]] > Sent: Thursday, May 17, 2001 4:25 AM > To: [EMAIL PROTECTED] > Subject: Monads > Hi > I'v currently working on a school-project where I have > to describe the Haskell programming language. > I've been looking through Monads and especially the IO > monad, the Maybe monad and the list monad > > My question is why are monads necessary in the > language ? > Is it not possible to construct the features provided > by Monads using basic functional constructs ? > What do I gain using Monads ? > Thank you very much. > Regards Skagen ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: HUGS error: Unresolved overloading
David Scarlett wrote: > > Can anyone shed some light on the following error? Thanks in advance. > > isSorted :: Ord a => [a] -> Bool > isSorted [] = True > isSorted [x] = True > isSorted (x1:x2:xs) > | x1 <= x2 = isSorted (x2:xs) > | otherwise = False > > [...] > Main> isSorted [] > ERROR: Unresolved overloading > *** Type : Ord a => Bool > *** Expression : isSorted [] > The list constructor [] is overloaded, so it's type cannot be infered inambigously. The empty list can be of any list type, HUGS cannot check if it's parameter's type is an instance of Ord. -- Ralf Krueger E-Mail: [EMAIL PROTECTED] URL:http://www.Ralf-Krueger.DE Bielefeld University Center for Interdisciplinary Research (ZiF) WWW Administration Wellenberg 1 33615 Bielefeld Germany Tel: ++49 521 106-2777 ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
Ashley Yakeley comments: > > Jerzy Karczmarczuk wrote: > > >Monads are *much* more universal than that. They are "convenient patterns" > >to code the non-determinism (lazy list monads), to generalize the concept > >of continuations, to add tracing, exceptions, and all stuff called > >"computation" by the followers of Moggi. They are natural thus to construct > >parsers. Imperative programming is just one facet of the true story. > > Perhaps, but mostly monads are used to model imperative actions. And > their use in imperative programming is the obvious starting point to > learning about them. "Mostly" is very relative. The real power of monads is their universality. This "modelling of imperative actions" is just a way to hide the State, which in IO is rather unavoidable. But in my opinion it is rather antipedagogic to introduce monads in such a way to beginners. "Obvious starting point"? My goodness, but this is selling a black, closed box, which smells badly (imperatively) to innocent souls. People see then just do rubbish <- rubbish more_rubbish and don't know anything about the true sense of return, of the relation of <- to >>=, and finally they can use ONLY the IO Monad, nothing else. They start posing questions what is the difference between a <- b and let a = b ... and they get often ungodly answers to that, answers which say that the main difference is that <- "executes side-effects", and let doesn't. It choked me a bit. (Was it on comp.lang.functional, or on one of Haskell lists?) My philosophy is completely opposite. Introduce Monads as a natural way of chaining complex data transfer and hiding useless information, and when the idea is assimilated, then pass to IO. I begin usually with Maybe, then with backtrack Monad, and some simple State Transformers. Then, the students can grasp the Wadler's style slogan "Monads can Change the World". Oh, well, all teaching approaches are imperfect. Jerzy Karczmarczuk Caen, France ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
HUGS error: Unresolved overloading
Can anyone shed some light on the following error? Thanks in advance. isSorted :: Ord a => [a] -> Bool isSorted [] = True isSorted [x] = True isSorted (x1:x2:xs) | x1 <= x2 = isSorted (x2:xs) | otherwise = False Hugs session for: /usr/local/share/hugs/lib/Prelude.hs haskell/sort.hs Main> isSorted [1] True Main> isSorted [1,2] True Main> isSorted [2,1] False Main> isSorted [] ERROR: Unresolved overloading *** Type : Ord a => Bool *** Expression : isSorted [] ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Proposal for generalized function partition in List-library
On Thu, 17 May 2001, Bernd [iso-8859-2] Holzmüller wrote: > This partitioning function builds equivalence classes from the list > argument, where each element list within the result list consists of > elements that all map to the same value when applying f to it. > Thus: partition (`div` 2) [1..5] yields [[1],[2,3],[4,5]] > > This is much more general than the existing partitioning function and > applicable in many practical cases. But here generality comes at the expense of speed I think. Greetings :-) Michal Gajda [EMAIL PROTECTED] ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
>So what you are saying is that I actually don't need >Monads to perform the tasks Monads supports ? Indeed. However, not using the Monadic do syntax results in hardly-readible code. For an explanation of how monads can be written in a functional way, see http://www.engr.mun.ca/~theo/Misc/haskell_and_monads.htm ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
At 2001-05-17 02:03, Jerzy Karczmarczuk wrote: >Monads are *much* more universal than that. They are "convenient patterns" >to code the non-determinism (lazy list monads), to generalize the concept >of continuations, to add tracing, exceptions, and all stuff called >"computation" by the followers of Moggi. They are natural thus to construct >parsers. Imperative programming is just one facet of the true story. Perhaps, but mostly monads are used to model imperative actions. And their use in imperative programming is the obvious starting point to learning about them. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
Ashley Yakeley answer to Mads Skagen: > >My question is why are monads necessary in the > >language ? > > > >Is it not possible to construct the features provided > >by Monads using basic functional constructs ? > > Monads themselves are made purely out of basic functional constructs. > > >What do I gain using Monads ? > > They happen to be a very convenient pattern. Mostly they're used to model > imperative actions: while a purely functional language cannot actually > execute actions as part of its evaluation, it can compose them, along the > lines of "AB is the action of doing A, and then doing B with its result". > Monads happen to be a useful pattern for such things. PLEASE!!! I disagree quite strongly with such severely limited answers addressed to people who don't know about monads. Monads are *much* more universal than that. They are "convenient patterns" to code the non-determinism (lazy list monads), to generalize the concept of continuations, to add tracing, exceptions, and all stuff called "computation" by the followers of Moggi. They are natural thus to construct parsers. Imperative programming is just one facet of the true story. Mads Skagen: please read the paper by Wadler on the essence of functional programming, and other stuff picked, say, from here: http://hypatia.dcs.qmw.ac.uk/SEL-HPC/Articles/FuncArchive.html That's right you don't really NEED monads (unless you are forced to do IO...), but when you learn them you will feel better and older. Jerzy Karczmarczuk Caen, France ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Monads
Thank you for your reply. So what you are saying is that I actually don't need Monads to perform the tasks Monads supports ? Thank you very much. Regards Skagen __ Går mail for langsomt for dig? Så prøv Yahoo! Messenger - her kan du i løbet af få sekunder udveksle beskeder med de venner, der er online. Messenger finder du på adressen: http://dk.messenger.yahoo.com ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Monads
At 2001-05-17 01:25, Mads Skagen wrote: >My question is why are monads necessary in the >language ? > >Is it not possible to construct the features provided >by Monads using basic functional constructs ? Monads themselves are made purely out of basic functional constructs. >What do I gain using Monads ? They happen to be a very convenient pattern. Mostly they're used to model imperative actions: while a purely functional language cannot actually execute actions as part of its evaluation, it can compose them, along the lines of "AB is the action of doing A, and then doing B with its result". Monads happen to be a useful pattern for such things. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Monads
Hi I'v currently working on a school-project where I have to describe the Haskell programming language. I've been looking through Monads and especially the IO monad, the Maybe monad and the list monad My question is why are monads necessary in the language ? Is it not possible to construct the features provided by Monads using basic functional constructs ? What do I gain using Monads ? Thank you very much. Regards Skagen __ Går mail for langsomt for dig? Så prøv Yahoo! Messenger - her kan du i løbet af få sekunder udveksle beskeder med de venner, der er online. Messenger finder du på adressen: http://dk.messenger.yahoo.com ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Proposal for generalized function partition in List-library
Hi all, knowing that the Haskell library report is currently being rewritten, I would like to propose a new function for module List that generalizes the current function partition :: (a -> Bool) -> [a] -> [[a]] in the following way: partition :: Eq b => (a -> b) -> [a] -> [[a]] partition _ [] = [] partition f (a:as) = let (as',as'') = foldr (select (f a)) ([],[]) as in (a:as'):partition f as'' where select b x (ts,fs) | f x == b = (x:ts,fs) | otherwise = (ts,x:fs) This partitioning function builds equivalence classes from the list argument, where each element list within the result list consists of elements that all map to the same value when applying f to it. Thus: partition (`div` 2) [1..5] yields [[1],[2,3],[4,5]] This is much more general than the existing partitioning function and applicable in many practical cases. Cheers, Bernd Holzmüller ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: BAL paper available >> graphic libraries
Jerzy Karczmarczuk writes: [Some interesting points on functional wrappings of graphics libraries] Has anyone considered writing a haskell wrapper for SDL - Simple Directmedia Layer at http://www.libsdl.org ? This is a cross platform library intended for writing games, and aims for a high performance, low level API. It would be interesting to see how clean a functional API could be built around such an imperative framework. Tim ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell