Re: [Haskell-cafe] Why Not Haskell?
I have started to love haskell and like these friends I am starting to be annoying about "Why not haskell?" and realy realy why not haskell? In commercial world there are buzz-oriented languages that do the "barking to the picture" in their "communities" - which are in fact groups of free marketers for "the companies". Let all those guys continue to bulk their noisy space! But again "why not haskell?". I think - this is my opinion according to my experiences and abilities and I know they are not the best ones; I only try to participate in this discussion which is important to me - the main reasons are two: 1 - monads : there must be something to make a clear tool for a none-mathematician programmer. (I still have understanding problems with them). 2 - there must be an easy way to include existing libraries. There are many stable libraries in CPAN for perl, implemented in C for example. And why not to have a system for writing C in haskell? Or an easy interface for using these codes without reimplementing haskell identities in C? Thanks all ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Monad Imparative Usage Example
Thanks All This is about my tries to understand monads and handling state - as you perfectly know - is one of them. I have understood a little about monads but that knowledge does not satidfy me. Again Thankyou On 8/2/06, Duncan Coutts <[EMAIL PROTECTED]> wrote: On Wed, 2006-08-02 at 13:26 +0330, Kaveh Shahbazian wrote: > Haskell is the most powerfull and interesting "thing" I'v ever > encountered in IT world. But with an imparative background and lack of > understanding (because of any thing include that maybe I am not that > smart) has brought me problems. I know this is an old issue. But > please help it. > Question : Could anyone show me a sample of using a monad as a > statefull variable? > For example see this code in C# : > // > public class Test > { > int var; > static void Fun1() { var = 0; Console.Write(var); } > static void Fun2() { var = var + 4; Console.Write(var); } > static void Main() { Fun1(); Fun2(); var = 10; Console.Write("var > = " + var.ToString()); } > } > // > I want to see this code in haskell. As other people have noted, you probably don't want to to see this code in Haskell. It's possible to translate stateful code in a 1-1 style but that's not really the point. You'll not get much of the advantages of the language if you do that. You can certainly use console IO etc but for your object containing mutable state, well in a functional style you'd simply not do that and solve the problem in a different way. That's why you see the code people have suggested as translations are bigger than the code you started with, because the language is not naturally imperative. So the trick is to solve your problem in Haskell, not translate your imperative solution to Haskell. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Monad Imparative Usage Example
Thanks All This is about my tries to understand monads and handling state - as you perfectly know - is one of them. I have understood a little about monads but that knowledge does not satidfy me. Again Thankyou On 8/2/06, Donn Cave <[EMAIL PROTECTED]> wrote: On Wed, 2 Aug 2006, Donald Bruce Stewart wrote: ... > Of course, if you're learning Haskell, you should probably try to > /avoid/ mutable variables for a while. Along the same line, I note that proposed solutions seem to use features relatively recently added to the language, is that true? StateT requires multi-parameter type class, for example, so it can't have been there all along. MVar is pretty new, isn't it? IORef must be the oldest of them, but hardly there from the start, I suspect. To learn core concepts, maybe it's a good idea to stay away from GHC in the beginning, and use Hugs or something that tends not to be so much of a magnet for new features. That forces you to look for a solution on the terms of the basic language concepts. Donn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
G'day all. Quoting Udo Stenzel <[EMAIL PROTECTED]>: > Uh, this one's wrong. Does C++ of 15 years ago support today's programs? C++ of _today_ doesn't support today's programs in some cases. Just ask the Boost developers about the various workarounds they still have to deal with. > No. C++ of 10 years ago probably does, but the compiler will crash. Even compiling a fully conforming ISO C++ standard library generally requires a compiler from at most three years ago. Generally speaking, any C++ application that was written 10 years ago and hasn't been rewritten avoids large parts of the standard library precisely because it was so poorly supported, and what was supported was poorly implemented. (That's why Qt looks like it does.) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
G'day all. Quoting Jason Dagit <[EMAIL PROTECTED]>: > 15. OO is now tried and true in industry. I would say it's far from > optimal but people do know they can build large applications (say > ~100k lines of C++). So naturally shifting to a new paradigm will > meet resistance. OO on its own is also well-understood to be inadequate for programming- in-the-large. 100k lines, by the way, isn't "large". 1M lines is "large". 10M+ lines is "very large". Large or very large programs tend to use one or more varieties of componentisation (e.g. higher-level scripting layer, plugins, COM/CORBA/.NET), which is arguably at a strictly higher level than OO. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
There are two places where confusion could arise if you didn't have the case distinction in Haskell: pattern matching (does a name refer to a constructor or not) and type expressions (is it a type variable or not). In Haskell the distinction is made by case, but this is far from the only choice. There are other ways to mark what is a variable and what is not. I don't necessarily think that Haskell did it the best way, but then this is a minor syntactic issue. Changing the case of variables is a pretty low price to pay to solve this problem. -- Lennart On Aug 4, 2006, at 13:12 , Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't belong in the language definition (it belongs in the user's coding standards). I get annoyed, for example, that when I write code that manipulates matrices and vectors, I can't refer to the matrices with capital letters as is common in the literature. And to anyone who says that it's good to enforce naming consistency, I have this to say: Any language that requires me to learn about category theory in order to write imperative code should treat me like an adult when it comes to the naming of variables as well. ;-) 2. It makes it easier to write the compiler. I don't think I need to explain why this is bad... I imagine that someone is just itching to "sort me out". Do your worst! ;-) Thx Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't belong in the language definition (it belongs in the user's coding standards). If everyone uses the same coding standards it's easier to understand other people's code. Also, if you're working in a team you'd usually have to agree to adhere to someone else's idea of how to name identifiers which you might find really irritating, whereas with Haskell there is at least some global common ground that has already been established so there would be less reasons to get irritated with actual people! ;-) I get annoyed, for example, that when I write code that manipulates matrices and vectors, I can't refer to the matrices with capital letters as is common in the literature. But you also can't write things like: v' = M v in a general purpose programming language and expect it to be interpreted as v' = M * v. And to anyone who says that it's good to enforce naming consistency, I have this to say: Any language that requires me to learn about category theory in order to write imperative code should treat me like an adult when it comes to the naming of variables as well. ;-) But it does! Haskell realises that as an adult you are more interested in getting as much feedback about the correctness of your program as possible, rather than glossing over possible errors to maintain an illusory world where the lure of extra choices magnifies childish whimsy! ;-) 2. It makes it easier to write the compiler. I don't think I need to explain why this is bad... Why would you say this? If it's easier to write the compiler the chances are: a) The compiler will have a simpler and cleaner design a1) There will be less bugs in the compiler a2) It is easier to modify so more language improvements can be explored b) More people will be motivated to write or modify compilers or other language-processing tools leading to improvements in the language and better development environments I imagine that someone is just itching to "sort me out". Do your worst! ;-) The extra coding confidence you gain by having a fixed capitalisation rule probably allows you to feel more relaxed when coding so I would not be surprised if the capitalisation rule leads to health benefits and therefore a feeling of peace, well-being, and goodwill towards other coders because either one is in agreement or else there is a common enemy namely the rule that cannot be changed! ;-) All we can do is pity those poor C++ souls locked in an abyss of inflated personality, case conflicts, chronic anxiety, and bug ridden code... Best regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] fast image processing in haskell?
Jeff Briggs wrote: Hello, I am attempting to process images captured from a webcam. My aim is to do so, in real time, at the frame rate of the camera. I'm using GHC 6.4.2 with -O3. A frame consists of ~100k 24bit colour values. The webcam is interfaced through FFI bindings to some C++ -- these are all labelled 'unsafe'. The image is passed to Haskell as a Ptr Word8. To blit this to the screen (via Gtk2Hs) I do the following: data Cam = Cam { snap_width :: !Int , snap_height :: !Int , snap_bytespp :: !Int , snap_size:: !Int , cam_img :: Ptr Word8 , cam_obj :: ForeignPtr () } do (PixbufData _ dst _) <- (pixbufGetPixels pixbuf :: IO (PixbufData Int Word8)) copyBytes dst (cam_img cam) This achieves the desired throughput (25-29fps.) However, I am at a bit of a loss how to do something similar for preprocessing the data in Haskell before blitting the data (whilst also retaining some semblance of functional programming...) Currently, I have: cam_snap cam f x = do let loop (r:g:b:rest) n x = f r g b n x >>= loop rest (n+3) loop _ _ x= return x px <- peekArray (snap_size cam) (cam_img cam) loop px 0 x cam_snap2 cam f x = let loop ptr n x | n >= snap_size cam = return x | otherwise = do let ptrs = scanl plusPtr ptr [1,1] [r,g,b] <- mapM peek ptrs f r g b n x >>= loop (ptr `plusPtr` 3) (n+3) in loop (cam_img cam) 0 x do ... let sum_px r g b _ (sr,sg,sb) = return (sr+r,sg+g,sb+b) sum <- cam_snap (cam ui) sum_px (0.0,0.0,0.0) print sum cam_snap only processes at 5 fps, whereas cam_snap2 operates at 6fps. Any suggestions? I suggest trying something, using "/usr/bin/ghc -O3 -optc-O3" like this: {-# OPTIONS_GHC -funbox-strict-fields #-} import Foreign import Control.Monad data Cam = Cam { snap_width :: !Int , snap_height :: !Int , snap_bytespp :: !Int , snap_size:: !Int , cam_img :: Ptr Word8 , cam_obj :: ForeignPtr () } type F = Word8 -> Word8 -> Word8 -> Int -> Int -> Int {-# INLINE cam_snap_3 #-} cam_snap_3 :: Cam -> F -> Int -> IO Int cam_snap_3 cam f x = let end = snap_size cam loop ptr n x | ptr `seq` n `seq` x `seq` False = undefined | n >= end = return x | otherwise = do r <- peek ptr g <- peek (advancePtr ptr 1) b <- peek (advancePtr ptr 2) loop (advancePtr ptr 3) (n+3) (f r g b n x) in loop (cam_img cam) 0 x ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Type hackery help needed!
Hi fellow Haskelleers, I have a tricky problem that I just can't seem to solve. The problem is one of unresolved overloading, much like the (show . read) issue, but unlike that particular problem I feel there should be a solution to the one I'm wrestling with. I've tried to strip away all the unnecessary bits so the following will be a bit abstract, but it shows the gist of the problem. I have two overloaded functions - one I call 'build' that creates values from subparts, and one I call 'embed' that turns values into a form appropriate to call 'build' on. What they really represent is creating values of some XML tree structure, with embed making sure that the children are of the right type. Conceptually, we could imagine that these two functions to be defined as class Build x c | x -> c, c -> x where build :: String -> [c] -> x class Embed a b where embed :: a -> b They would be used together as in e.g. p c = build "p" [embed c] This works pretty well, the fundep x -> c tells me what b should be, assuming I infer a proper type for the result of the composition. The type of p is then p :: (Embed a c, Build x c) => a -> x where the c in the middle is determined by x via the fundep. My problems arise because I want to start nesting these to form tree structures, as in tree = p (p "foo") Expanding the definition of p, the argument to the outer call to build is now embed $ build "p" [embed "foo"] :: (Embed String c, Build x c, Embed x x1) => x1 Through the fundep on the outer build I can infer what x1 should be, but there's no way I can infer x (without inserting an explicit type signature which is out of the question). This problem is probably unsolvable in general, but for my particular problem there are some restrictions that makes me feel there should be a clever way of working with classes and fundeps to make this all work out. I just can't seem to find one. These are the rules that the setup must obey: * A value of any type should be embeddable inside a build expression of any result type, i.e. a -> b or b -> a cannot hold on Embed in general. * The exception to the above is that if an expression using 'build' is embedded inside an outer 'build', as in 'tree' above, the inner build should have the same result type as the outer build (in a sense forming b -> a only for types instantiating Build). In other words, children of an xml element must be of the same type as their parent, even before the call to embed. * However, it would be nice, but probably not crucial, if by using explicit type signatures where I want to, I could actually embed values of "other" xml types than the outer one I am embedding them in, and letting embed convert them to xml of the correct type. I suspect this cannot be. The types of build and embed are negotiable, and certainly the type classes, as long as the two can be used together in roughly the same way as indicated above. The calls to build and embed will be autogenerated by a preprocessor from a HSP-style XML syntax, e.g. <% c %> <==> build "p" [embed c] and for this reason any solution *must* be syntactically expressible as expressions on a form similar to the above, but those expressions can be arbitrarily convoluted. For instance in my failed attempts so far I have used let expressions around build to form self-recursive versions to "pass a type" down through the evaluation, as in p c = let x = build "p" [embed x c] in x This is an ok solution syntactically, if only it solved the problem, I still can't see how to propagate it to the next level of build. :-( Is there anyone out there with the proper type class fu who can see a way out for me? Is this even possible to do at all? If yes, tell me please, and if not, I would be most interested in seeing why it cannot work. Any and all comments are welcome. Thanks for reading this long :-) /Niklas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Haskell very specifically has the really vitally important property that when you change the imports of a module in any way whatsoever, only one of two possible results can occur 1) the module behaves identically to the way it did before. or 2) the module fails to compile with an unambiguous compile-time error. This is a very important property that I wouldn't be willing to give up. also, it is nice for a human to not have to know what is imported to be able to locally determine what a function does to some degree. this would not be possible if you couldn't tell what was a constructor and what was a variable locally. heck, you can't even tell what is being defined. think of x + y * z = ... this could be declaring three top level names, x,y, and z or the function (+) or perhaps even just y and x and not z (or even a couple more possibilities) depending on which were constructors and which were variable names which you cannot determine without examining every import. not even being able to tell what values an expression is defining is a pretty bad quality :) John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Martin Percossi wrote: > Paul Hudak wrote: > >foo x y = ... > > > >We know that x and y are formal parameters, whereas if they were > >capitalized we'd know that they were constructors. > > I agree that naming can be abused. But I think it should be *me* ... Oh, you like to decide lexical ambiguities. Well, I suppose you know a bit of C++. So what do you think this is: *> int *foo ; It's the declaration of a pointer to 'int' named 'foo', isn't it? now what's this: *> x * y ; *Obviously* this mulplies x and y and throws the result away, doesn't it? Now look more closely. Do you see it? Or does it get more blurred the closer you look? We don't have this problem in Haskell, and in a sane world, C++ shouldn't have it either. If you find second-guessing the programmer funny, try to write a parser for C++. You will have so much fun, it's almost impossible to describe. Udo. -- Even if you're on the right track, you'll get run over if you just sit there. -- Will Rogers signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] REALLY simple STRef examples
Chad | x = runST $ return (1::Int) This code looks simple, but it isn't. Here are the types: runST :: forall a. (forall s. ST s a) -> a ($) :: forall b c. (b->c) -> b -> c return 1 :: forall s. ST s Int To typecheck, we must instantiate b with (forall s. ST s Int) c with Int In H-M that's impossible, because you can't instantiate a type variable (b) with a polytype (forall s. ST s Int). GHC will now let you do that (a rather recent change), but in this case it's hard to figure out that it should do so. Equally plausible is to instantiate b with (ST s' Int), where s' is a unification variable. One way to make this work is to look at $'s first argument first. Then it's clear how to instantiate b. Then look at the second argument. But if you look at the second argument first, matters are much less clear. GHC uses an algorithm that is insensitive to argument order, so it can't take advantage of the left-to-right bias of this example. It's unfortunate that such a simple-looking piece of code actually embodies a rather tricky typing problem! Of course there is no problem if you don' use the higher order function $. Use parens instead x = runST (return 1) Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of | Chad Scherrer | Sent: 19 July 2006 23:02 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] REALLY simple STRef examples | | I've looked around at the various STRef examples out there, but still | nothing I write myself using this will work. I'm trying to figure out | how the s is escaping in really simple examples like | | x = runST $ return 1 | | y = runST $ do {r <- newSTRef 1; readSTRef r} | | Neither of these works in ghci - they both say | | :1:0: | Inferred type is less polymorphic than expected | Quantified type variable `s' escapes | Expected type: ST s a -> b | Inferred type: (forall s1. ST s1 a) -> a | In the first argument of `($)', namely `runST' | In the definition of `it': |... | | I thought maybe I needed to replace 1 with (1 :: Int) so the state | representation didn't force the type, but it still gives the same | result. | | Can someone point me to the simplest possible runST example that | actually works? Thanks! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Re[2]: [Haskell-cafe] a bunch of newbie questions
Bulat Ziganshin wrote: Hello Brian, Friday, August 4, 2006, 8:50:25 PM, you wrote: class Bar a b where bar :: a -> b (*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a type of the form A -> B: cool :: Int cool :: Char -> String class Cool -- Ooops! fundamental problem encountered ;-) class Cool a where cool :: a instance Cool Int instance Cool (Char -> String) ? Yes thanks - someone else pointed this out to me off-list as well. I think that mental block must have been caused by watching too many episodes of Star Trek yesterday! Ok I give up, there's just no excuse... ;-) Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] fast image processing in haskell?
Hello, I am attempting to process images captured from a webcam. My aim is to do so, in real time, at the frame rate of the camera. I'm using GHC 6.4.2 with -O3. A frame consists of ~100k 24bit colour values. The webcam is interfaced through FFI bindings to some C++ -- these are all labelled 'unsafe'. The image is passed to Haskell as a Ptr Word8. To blit this to the screen (via Gtk2Hs) I do the following: data Cam = Cam { snap_width :: !Int , snap_height :: !Int , snap_bytespp :: !Int , snap_size:: !Int , cam_img :: Ptr Word8 , cam_obj :: ForeignPtr () } do (PixbufData _ dst _) <- (pixbufGetPixels pixbuf :: IO (PixbufData Int Word8)) copyBytes dst (cam_img cam) This achieves the desired throughput (25-29fps.) However, I am at a bit of a loss how to do something similar for preprocessing the data in Haskell before blitting the data (whilst also retaining some semblance of functional programming...) Currently, I have: cam_snap cam f x = do let loop (r:g:b:rest) n x = f r g b n x >>= loop rest (n+3) loop _ _ x= return x px <- peekArray (snap_size cam) (cam_img cam) loop px 0 x cam_snap2 cam f x = let loop ptr n x | n >= snap_size cam = return x | otherwise = do let ptrs = scanl plusPtr ptr [1,1] [r,g,b] <- mapM peek ptrs f r g b n x >>= loop (ptr `plusPtr` 3) (n+3) in loop (cam_img cam) 0 x do ... let sum_px r g b _ (sr,sg,sb) = return (sr+r,sg+g,sb+b) sum <- cam_snap (cam ui) sum_px (0.0,0.0,0.0) print sum cam_snap only processes at 5 fps, whereas cam_snap2 operates at 6fps. Any suggestions? Thanks. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[2]: [Haskell-cafe] Why Not Haskell?
Hello Jason, Friday, August 4, 2006, 10:01:31 PM, you wrote: > 15. OO is now tried and true in industry. I would say it's far from > optimal but people do know they can build large applications (say > ~100k lines of C++). it's medium size. GHC is larger :) -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
Hello Hans, Friday, August 4, 2006, 8:17:42 PM, you wrote: > 1) Haskell is too slow for practical use, but the benchmarks I found > appear to contradict this. it's an advertisement :D just check yourself > 2) Input and output are not good enough, in particular for graphical > user interfacing and/or data base interaction. But it seems there are > several user interfaces and SQL and other data base interfaces for > Haskell, even though the tutorials don't seem to cover this. i've seen a paper which lists 7 (as i remember) causes of small Haskell popularity, including teaching, libraries, IDEs and so on. may be someone will give us the url i personally think that Haskell in its current state is appropriate for system programming > Are there other reasons why there seem to be just a few thousand > (hundred?) Haskell programmers in the world, compared to the 3 million > Java programmers and x million C/C++ programmers? i once analyzed why C++ and not Eiffel or Modula-2 becomes the language of 90's. my conclusion was what C and C++ becomes a tandem at the late 80's - C raised popularity because it had OOP successor while C++ becomes popular because it had imperative predecessor. Pascal, Modula-2 or Eiffel was great languages, but they don't form such tandems. So, now we have 3 million of Java programmers just because C was a great tool for writing DOS apps :) > Now I'm trying to come up with a business model for my algorithm and to > avoid the mistakes I made 10 years ago. There is a lot of difference > between a prototype and a working tool, and then there is a lot of > difference between a working tool and a successful commercial > application. Probably it doesn't make much sense to try and develop a > tool in C++ or even Java, but if I have to go on my own on this, maybe > Haskell could be feasible, both for fun and profit. if speed isn't critical, if you don't need to use many libs, don't need help from RAD tools in developing UI of your program - you can use Haskell, imho -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[2]: [Haskell-cafe] a bunch of newbie questions
Hello Brian, Friday, August 4, 2006, 8:50:25 PM, you wrote: > class Bar a b where > bar :: a -> b > (*) But there's one exception: you can't use typeclasses to resolve > overloadings between values and functions because non-function values don't > have a type of the form A -> B: > cool :: Int > cool :: Char -> String > class Cool -- Ooops! fundamental problem encountered ;-) class Cool a where cool :: a instance Cool Int instance Cool (Char -> String) ? -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
Jason Dagit wrote: > On 8/4/06, Donn Cave <[EMAIL PROTECTED]> wrote: > >6. Instability - available for 15 years, you say, but does the Haskell > >of 15 years ago support today's programs? Does standard Haskell > >even support today's programs? Uh, this one's wrong. Does C++ of 15 years ago support today's programs? No. C++ of 10 years ago probably does, but the compiler will crash. Similar for C, similar for Perl, and the question cannot even be asked for Java. So no, that's *not* the reason for low acceptance. The right question would be, does Haskell of today support the programs from 15 years ago? Mostly it does, with minor changes. The bitrot isn't worse than in other languages. > 15. OO is now tried and true in industry. I would say it's far from > optimal but people do know they can build large applications (say > ~100k lines of C++). So naturally shifting to a new paradigm will > meet resistance. Closer to reality is: People know that *some* 100 kLoC OO programs in C++ have not yet crumbled under their own weight. However, most have. Is that track record worth imitating? Well, "decision makers" seem to think so... Anyway, *some* 10 kLoC Haskell programs are also still standing upright (no, I didn't forget a zero). > Yes, trying to meet deadlines with untrusted tools is scary business. ...and so is trying to meet deadlines with trusted tools. Paraphrasing Paul Graham: if you do what everyone does, you get average results. The average result is blowing your budget by a factor of 2 (or 3), missing your deadline (twice) and delivering a broken product (if anything). > Not everyone likes to gamble with their jobs :) Yet everyone does... Udo. -- The most happy marriage I can imagine to myself would be the union of a deaf man to a blind woman. -- Samuel Taylor Coleridge signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
On Fri, 4 Aug 2006, Brian Hulley wrote: > > 4) Haskell is open source and licensing restrictions forbid commercial > > applications. I haven't seen any such restrictions, but is this a > > problem for the standard modules? > > You can discover the licensing situation by downloading the GHC source (or > source for whatever distro you're using) and looking in the directories for > each package. For example the base package uses a BSD-style licence and HaXml > uses LGPL with the exception to allow static linking. A license which requires programmers to disclose their sources shouldn't be a problem for a commercial application. Which C hacker would or could steal code from it? :-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
On Fri, 4 Aug 2006, Udo Stenzel wrote: > Hans van Thiel wrote: >> I'm wondering why I can't find any commercial Haskell applications on >> the Internet. Is there any reason for this? > > Of course. Corporations are conservative to the point of being > boneheaded. So to avoid risk, they all went on the internet and said, > "Gee, I can't find any commercial Haskell applications on the Internet. > There must be a reason for that, so I better use something else." Or maybe they're more clever than you imagine, and they all have rooms full of Haskell programmers sworn to secrecy, trying to get a jump on the competition. Wouldn't it be funny if it turned out that the Python stuff at Google was just a side-show, and Haskell was really the big development language all along? (Not true, I'm sure - you could sort of stand a chance of starting a secret Python development project, but Haskell I doubt.) Donn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
On Fri, 4 Aug 2006, Martin Percossi wrote: > > I agree that naming can be abused. But I think it should be *me*, the > programmer, or in the limit ghc, the glorious compiler (but only because of > unresolvable ambiguities), who decides it -- not *you*, the language > implementor!!! ;-) The ML constructor/variable ambiguity introduces a nasty maintenance headache: what if you upgrade to a new version of a library which introduces a new constructor which happens to be the same as a variable you have been using? Suddenly the meaning of your functions changes! Tony. -- f.a.n.finch <[EMAIL PROTECTED]> http://dotat.at/ FISHER: WEST OR NORTHWEST 4 OR 5 BECOMING VARIABLE 3 OR 4. FAIR. MODERATE OR GOOD. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Paul Hudak wrote: Ok, you asked for it, so here's my worst :-) You're too gentle! I was expecting some serious community flagellation for my heretical remarks! 1) Here's what the "History of Haskell" has to say about this: Namespaces were a point of considerable discussion in the Haskell Committee. We wanted the user to have as much freedom as possible, while avoiding any form of ambiguity. So we carefully defined a set of lexemes for each namespace that were orthogonal when they needed to be, and overlapped when context was sufficient to distinguish their meaning. As an example of overlap, capitalised names such as Foo can, in the same lexical scope, refer to a type constructor, a data constructor, and a module, since whenever the name Foo appears, it is clear from context to which entity it is referring. As an example of orthogonality, we designed normal variables, infix operators, normal data constructors, and infix data constructors to be mutually exclusive. We adopted from Miranda the convention that data constructors are capitalised while variables are not; and added a similar convention for infix constructors, which in Haskell must start with a colon. ... The key point here is that we wanted data constructors to be orthogonal to formal parameters. For example, in: foo x y = ... We know that x and y are formal parameters, whereas if they were capitalized we'd know that they were constructors. Some of us had had experience with ML where this distinction is not made, and we didn't like that. There are surely other ways to achieve this, but captilization was one of the least painful, as we saw it. I agree that naming can be abused. But I think it should be *me*, the programmer, or in the limit ghc, the glorious compiler (but only because of unresolvable ambiguities), who decides it -- not *you*, the language implementor!!! ;-) 2) Note that this is not a compiler issue -- the compiler won't have much problem either way -- but it is a readability issue. Ok - that's what I suspected - contrary to some of the other replies which seem to imply that it would cause big problems in the compiler. While I have never written a compiler of anything near the complexity of haskell (I just about managed an awk-like language! ;-), you still feel that it shouldn't be that difficult to handle these cases. 3) I suspect that you are mostly kidding, but Haskell doesn't require you to know any category theory to write imperative code! True again - but I think you understood the general gist. I hope this helps, -Paul It does, thanks for your time. And now I will stop complaining! ;-) Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
Hans van Thiel wrote: Hello All, I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? I'm actually working on a Haskell program which I hope to release as a commercial application. The biggest problem I'm encountering is the lack of a really solid collections library that's as well thought out as C++ STL because although there are several competing collections libraries, each allowing fast development of powerful code, they all have various faults and limitations and I hate the idea of my code resting on half-baked foundations. I'm also a rabid perfectionist (and extremely fussy with regard to code aesthetics) when it comes to these kind of things so perhaps it's my fault. Perhaps it's also because Haskell raises your expectations regarding what a good program should be like, so it's easy to get lost in abstraction. Eg last week all I needed was an equivalent of the C++ std::vector but I've wasted the whole of this week trying to create the perfect factoring of collection classes to try and avoid having concrete types everywhere and to be a foundation for all the uses of collection types in my program, and now I'm totally lost in a miasma of undecidable instances and difficult decisions. I can think of the following possibilities only: 1) Haskell is too slow for practical use, but the benchmarks I found appear to contradict this. I think it's fast enough. There's also a very good foreign function interface if you need to get the full speed of C for some inner loop. And a bonus is that as more and more people use it, it's likely that more effort will be done to make it faster. 2) Input and output are not good enough, in particular for graphical user interfacing and/or data base interaction. But it seems there are several user interfaces and SQL and other data base interfaces for Haskell, even though the tutorials don't seem to cover this. You just need to check the licences for the various bindings and also the licences for the C libs they're bound to so you don't end up with a GPL infested program. WxWidgets uses LGPL with the linking exception so it should be 100% safe and easy to use (http://wxhaskell.sourceforge.net/license.html ). Gtk2Hs uses the LGPL according to http://haskell.org/gtk2hs/overview/ but it does not appear to admit the linking exception though this is not insurmountable - it just means you need to supply an object file of your code along with your exe (and if you use Unix there's no trouble at all because the lib is linked dynamically iirc) 3) Haskell is not scaleable for commercial use. This looks unlikely to me, but could this be a factor? It can be difficult to know how to organise a large program in Haskell if you're used to OOP but I don't think there are any limits on scalability per se - GHC is itself an example of a very large Haskell program that's widely used on many platforms. 4) Haskell is open source and licensing restrictions forbid commercial applications. I haven't seen any such restrictions, but is this a problem for the standard modules? You can discover the licensing situation by downloading the GHC source (or source for whatever distro you're using) and looking in the directories for each package. For example the base package uses a BSD-style licence and HaXml uses LGPL with the exception to allow static linking. It would be good if this info was also on the wiki somewhere but if it is I can't find it, or if there was a tool to identify or gather together the various licenses and create a composite license (eg including the list of the names of all contributors who want to be mentioned) to distribute with your app (a free lawyer implemented in Haskell together with its own self-generated license!!!). If you're going to release your app on Windows using GHC you'll need to prepare an object file to distribute along with your exe to satisfy the annoying LGPL linking restriction imposed by the GMP library that's currently part of the statically linked runtime, but this shouldn't be an obstacle once you've written the appropriate batch file to generate it. (There's a thread on the ghc users mailing list indicating that GMP might be removed from GHC at some point which would make life even easier - see http://www.haskell.org/pipermail/glasgow-haskell-users/2006-August/010665.html ) [snip] Why hasn't Haskell made it into the business world (yet), after being available for 15 years, or is this the wrong question? This might just be because computers were too slow in the past to run programs written in such high level languages as Haskell, so everyone had to use low-level languages like C and C++ (people even now still spend sleepless nights debating whether or not to use a virtual function in a C++ class because of the extra indirection it requires). Also, the bottom line imho is that Haskell is a difficult language to understan
Re: [Haskell-cafe] Why Not Haskell?
Hans van Thiel wrote: > I'm wondering why I can't find any commercial Haskell applications on > the Internet. Is there any reason for this? Of course. Corporations are conservative to the point of being boneheaded. So to avoid risk, they all went on the internet and said, "Gee, I can't find any commercial Haskell applications on the Internet. There must be a reason for that, so I better use something else." > Are there other reasons why there seem to be just a few thousand > (hundred?) Haskell programmers in the world, compared to the 3 million > Java programmers and x million C/C++ programmers? Yah. 2.995 million programmer-wannabes were too lazy to think for themselves and choose what everybody uses. > Probably it doesn't make much sense to try and develop a > tool in C++ or even Java, but if I have to go on my own on this, maybe > Haskell could be feasible, both for fun and profit. It never makes sense to limit yourself to only one programming language, even if it happens to be Haskell. There's always the FFI, should it turn out that some part is better done in C or assembly or Fortran or whatever comes to mind. Udo. -- The two most abundant things in the universe are hydrogen and stupidity. -- Harlan Ellison signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Ok, you asked for it, so here's my worst :-) 1) Here's what the "History of Haskell" has to say about this: Namespaces were a point of considerable discussion in the Haskell Committee. We wanted the user to have as much freedom as possible, while avoiding any form of ambiguity. So we carefully defined a set of lexemes for each namespace that were orthogonal when they needed to be, and overlapped when context was sufficient to distinguish their meaning. As an example of overlap, capitalised names such as Foo can, in the same lexical scope, refer to a type constructor, a data constructor, and a module, since whenever the name Foo appears, it is clear from context to which entity it is referring. As an example of orthogonality, we designed normal variables, infix operators, normal data constructors, and infix data constructors to be mutually exclusive. We adopted from Miranda the convention that data constructors are capitalised while variables are not; and added a similar convention for infix constructors, which in Haskell must start with a colon. ... The key point here is that we wanted data constructors to be orthogonal to formal parameters. For example, in: foo x y = ... We know that x and y are formal parameters, whereas if they were capitalized we'd know that they were constructors. Some of us had had experience with ML where this distinction is not made, and we didn't like that. There are surely other ways to achieve this, but captilization was one of the least painful, as we saw it. 2) Note that this is not a compiler issue -- the compiler won't have much problem either way -- but it is a readability issue. 3) I suspect that you are mostly kidding, but Haskell doesn't require you to know any category theory to write imperative code! I hope this helps, -Paul Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't belong in the language definition (it belongs in the user's coding standards). I get annoyed, for example, that when I write code that manipulates matrices and vectors, I can't refer to the matrices with capital letters as is common in the literature. And to anyone who says that it's good to enforce naming consistency, I have this to say: Any language that requires me to learn about category theory in order to write imperative code should treat me like an adult when it comes to the naming of variables as well. ;-) 2. It makes it easier to write the compiler. I don't think I need to explain why this is bad... I imagine that someone is just itching to "sort me out". Do your worst! ;-) Thx Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: I'm not so sure about variable names and constructors, but the type syntax just wouldn't work without a lexical distinction between type names and type variables. Is (Int -> Int) supposed to be polymorphic with a type variable named "Int", or is it talking about a type "Int"? Perhaps you'd be happier reserving names beginning with apostrophes for variables? I think case is a bit easier to see - subattentive visual processing, and all that. Mostly, case is used so you know what basic sort of thing some object is, without reviewing everything in scope. Mathematicians use typesetting similarly to tell basic kinds of things appart. Imagine a mathematician complaining that he was forced to learn category theory to get a degree, and people still don't let him use letter with an arrow over it to denote a scalar quantity. It's just that ascii is more restricted, so we don't have things like fonts, greek letters, and accents. Lexical syntax is the least important kind of linguistic freedom. Brandon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
On 8/4/06, Donn Cave <[EMAIL PROTECTED]> wrote: On Fri, 4 Aug 2006, Hans van Thiel wrote: ... > Are there other reasons why there seem to be just a few thousand > (hundred?) Haskell programmers in the world, compared to the 3 million > Java programmers and x million C/C++ programmers? I can think of several other possible reasons - 6. Instability - available for 15 years, you say, but does the Haskell of 15 years ago support today's programs? Does standard Haskell even support today's programs? 7. Some difficult concepts, at a level that goes way beyond the commonly used languages. 8. Problems with evaluation model and space that other languages don't have to deal with. 9. Missing libraries 10. I think most commercial applications are developed for windows users. For the last 15 years this has primarily meant the application ran in windows (this is starting to change but that's another story). I'm currently using ghc to do windows development for a company I work at. I'm often running into "corner" cases where ghc has bugs on windows or poor support for some MS technology that is assumed when using other languages like .NET. Both COM and dlls have problems right now (but this is getting better monotonically). 11. If you read the History of Haskell paper (http://haskell.org/haskellwiki/History_of_Haskell) you will see that haskell was meant as a vehicle for research. This BTW, would be a highly relevant read for someone that wants more insight into why Haskell is not a Java killer. 12. Chicken and the egg. Having lots of users will attract more users. 13. Some industry programmers don't choose their tools based on technical worth so much as who is backing them. I'd like to think this explains the popularity of C++ and now Java/C#. I have 2nd hand information that Bjarne never meant for C++ to escape AT&T or really even go outside of the domain he was working in (which I recall was something embedded) but when people found out AT&T had a new OO capable language they jumped on. I'm not sure if it's really true, but watching Java/C# gain popularity it wouldn't surprise me. 14. I've heard arguments that a lot of the people who become industry devs are really turned off from functional languages during typical CS theory courses. I have no idea how anyone could verify this claim, plus I had the exact opposite reaction. I was transformed into a fan of FP by my theory courses. 15. OO is now tried and true in industry. I would say it's far from optimal but people do know they can build large applications (say ~100k lines of C++). So naturally shifting to a new paradigm will meet resistance. There also seems to be a lack of programs in the open source world which are written in Haskell. We have two big open source projects that people outside of the haskell community may hear of, pugs and darcs.I would say this reflects #6 but I'm relatively new to haskell so I could be wrong. Even with all this there are some people that are using haskell commercially (or lobbying for it). Joel Reymount Tim Sweeny* Galois Connections Myself * I think Tim is just wanting more of haskell's great features in the languages he already uses (http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/sweeny.pdf) Also, check the Haskell Communities and Activities Report: http://www.haskell.org/communities/ I'm sure I missed someone. and more, I suppose. I'm not saying any of these are necessarily compelling reasons not to use Haskell, but altogether, maybe another way to look at it is that it's really a strong statement when people decide to bet their livelihood on Haskell software development - it isn't the safe choice, and it means someone finds the reasons for it very compelling. Yes, trying to meet deadlines with untrusted tools is scary business. Not everyone likes to gamble with their jobs :) I hope that helps, Jason ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why shouldn't variable names be capitalized?
On Aug 4, 2006, at 1:12 PM, Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't belong in the language definition (it belongs in the user's coding standards). I get annoyed, for example, that when I write code that manipulates matrices and vectors, I can't refer to the matrices with capital letters as is common in the literature. This is occasionally irritating. And to anyone who says that it's good to enforce naming consistency, I have this to say: Any language that requires me to learn about category theory in order to write imperative code should treat me like an adult when it comes to the naming of variables as well. ;-) 2. It makes it easier to write the compiler. I don't think I need to explain why this is bad... Eh? I'm not convinced this is a bad reason. It obviously needs to be balanced against other competing factors, but ease of implementation should always a consideration when designing a language. 3. It removes a whole class of possible ambiguities from the language. You the programmer (and the compiler, as an added bonus) can always identify the syntactic class of an identifier from _purely local_ context. Suppose I remove the case restriction. Is the following a pattern match or a function definition? Is M a variable or a data constructor? let f x M = z M in You can't tell! Worse, it could change depending on what identifiers are in scope. It could happen that you import a module and it silently causes your function definition to change to a pattern match. The situation is similar with type classes and type variables. You could magically end up with an instance declaration that is less polymorphic than you expect (if you have extensions turned on). I imagine that someone is just itching to "sort me out". Do your worst! ;-) Thx Martin Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
Hans van Thiel wrote: Hello All, I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? I can think of the following possibilities only: 1) Haskell is too slow for practical use, but the benchmarks I found appear to contradict this. 2) Input and output are not good enough, in particular for graphical user interfacing and/or data base interaction. But it seems there are several user interfaces and SQL and other data base interfaces for Haskell, even though the tutorials don't seem to cover this. 3) Haskell is not scaleable for commercial use. This looks unlikely to me, but could this be a factor? 4) Haskell is open source and licensing restrictions forbid commercial applications. I haven't seen any such restrictions, but is this a problem for the standard modules? I wonder, how many languages have you seen commercial applications written in? I suppose you mean the sort of applications that might be sold in stores. I think a more interesting question around Haskell is what it takes to succeed in writing an application in a relatively uncommon language, what aspects of popularity are actually useful, and how you can compensate. What languages have gotten big without being the main language for a popular operating system, or pushed really hard by a big company? Then there are moderately popular languages like perl and Python, but are there lots of commercial application even in those? Brandon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Why shouldn't variable names be capitalized?
Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't belong in the language definition (it belongs in the user's coding standards). I get annoyed, for example, that when I write code that manipulates matrices and vectors, I can't refer to the matrices with capital letters as is common in the literature. And to anyone who says that it's good to enforce naming consistency, I have this to say: Any language that requires me to learn about category theory in order to write imperative code should treat me like an adult when it comes to the naming of variables as well. ;-) 2. It makes it easier to write the compiler. I don't think I need to explain why this is bad... I imagine that someone is just itching to "sort me out". Do your worst! ;-) Thx Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Why Not Haskell?
On Fri, 4 Aug 2006, Hans van Thiel wrote: ... > Are there other reasons why there seem to be just a few thousand > (hundred?) Haskell programmers in the world, compared to the 3 million > Java programmers and x million C/C++ programmers? I can think of several other possible reasons - 6. Instability - available for 15 years, you say, but does the Haskell of 15 years ago support today's programs? Does standard Haskell even support today's programs? 7. Some difficult concepts, at a level that goes way beyond the commonly used languages. 8. Problems with evaluation model and space that other languages don't have to deal with. 9. Missing libraries and more, I suppose. I'm not saying any of these are necessarily compelling reasons not to use Haskell, but altogether, maybe another way to look at it is that it's really a strong statement when people decide to bet their livelihood on Haskell software development - it isn't the safe choice, and it means someone finds the reasons for it very compelling. Donn Cave, [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Martin Percossi wrote: Bulat Ziganshin wrote: this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t -> t id x = x b) Haskell supports ad-hoc polymorphism via type classes Sometimes a distinction is made between ad-hoc polymorphism of the kind you'd get in C++ with method overloading, and "restricted parametric polymorphism" as in "Monad m =>" ie: 1) id :: t -> t -- Unrestricted parametric polymorphism 2) foo :: Monad m => m a -- Restricted parametric polymorphism for (m) and unrestricted for (a) 3) bar :: Int -> Int -> String bar :: Char -> Bool The only way to describe this is ad-hoc polymorphism, and the fact that any function is of the form A -> B means regardless of the arity of the overloaded functions it can also be supported by typeclasses (*) eg: class Bar a b where bar :: a -> b instance Bar Int (Int -> String) where ... instance Bar Char Bool where ... And a function or value in scope can be making use of unrestricted, restricted, and ad-hoc polymorphism at the same time eg: zap :: Monad m => Char -> m a zap :: Int -> String -> a String class Zap a b where zap :: a -> b instance Monad m => Zap Char (m a) where ... instance Zap Int (String -> a String) where ... (*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a type of the form A -> B: cool :: Int cool :: Char -> String class Cool -- Ooops! fundamental problem encountered ;-) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Why Not Haskell?
Hello All, I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? I can think of the following possibilities only: 1) Haskell is too slow for practical use, but the benchmarks I found appear to contradict this. 2) Input and output are not good enough, in particular for graphical user interfacing and/or data base interaction. But it seems there are several user interfaces and SQL and other data base interfaces for Haskell, even though the tutorials don't seem to cover this. 3) Haskell is not scaleable for commercial use. This looks unlikely to me, but could this be a factor? 4) Haskell is open source and licensing restrictions forbid commercial applications. I haven't seen any such restrictions, but is this a problem for the standard modules? Are there other reasons why there seem to be just a few thousand (hundred?) Haskell programmers in the world, compared to the 3 million Java programmers and x million C/C++ programmers? The reason I ask is that in the early nineties I wrote a data mining /machine learning program. This was not a commercial success and since then I've been working as a free lance IT journalist. As such I covered the O'Reilly European Open Source Convention in Amsterdam last year and there I heard of Haskell. I became interested and started learning from the available free tutorials and Hugs. As an aside, I'd like to thank all those people. I really appreciate their work and I'd like to single out Hal Daume III's 'Yet Another Haskell Tutorial', while not diminishing the other authors in any way. Meanwhile I kept working on a data mining algorithm in my spare time and finally I came up with something that appears to work. While I was learning Haskell, I thought, why not try this part of the algorithm as a Haskell exercise. I could easily test it in Hugs. To my own surprise, after only a few weeks of this, I had a working prototype of my algorithm, printed out on less than 3 pages, using only standard functions in the Prelude. So, I'm really impressed by the power of Haskell, and I'm just a beginner. Now I'm trying to come up with a business model for my algorithm and to avoid the mistakes I made 10 years ago. There is a lot of difference between a prototype and a working tool, and then there is a lot of difference between a working tool and a successful commercial application. Probably it doesn't make much sense to try and develop a tool in C++ or even Java, but if I have to go on my own on this, maybe Haskell could be feasible, both for fun and profit. So, that's the background of my question (while introducing myself to the Cafe at the same time). Why hasn't Haskell made it into the business world (yet), after being available for 15 years, or is this the wrong question? Many thanks for your comments, Hans van Thiel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Bulat Ziganshin wrote: this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t -> t id x = x b) Haskell supports ad-hoc polymorphism via type classes Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[2]: [Haskell-cafe] a bunch of newbie questions
Hello Mark, Friday, August 4, 2006, 3:03:54 PM, you wrote: > I've always been a little surprised when this doesn't happen more widely > for things other than instances. For instance, when IntMap.size, > Map.size and Set.size (or whatever) are all in scope as "size", it > should be fairly obvious what (size x) is about once we've inferred, for > other reasons, that x is an IntMap. Similarly with records, if we had this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. i'm not a language lawyer ;) but thinks that difference between C++ which supports former and Haskell that supports later is the following: C++ can infer only result type based on arguments type while Haskell can infer in _both_ directions. i can imagine C++ type inferring algorithm, with a little imagination i even can think about Haskell's algorithm :) but two-way type inferring together with ad-hoc polymorphism make me a little nervous :) how about, for example, two ad-hoc-polymorphic functions: f (g x)? or dozens of such calls enclosed? how error messages should be generated: "it may be Int::f with Char::g or Char::f with Bool::g or ... or ... or ..." ? one more cause is that Haskell was defined by scientists, not practical programmers, and scientists prefer to use more systematic ways to do the same things nevertheless, there is no principal differences. in many cases you can define type classes, include your ad-hoc polymorphic functions into these classes and sleep easy. in particular, as Brian already said, there is a proposal to use automatically generated type classes for record fields -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Hello Imam, Friday, August 4, 2006, 12:19:04 PM, you wrote: >> (read "56")::Integer > does it in fact pass the type (Integer) to the > function (read)? it tells the compiler that result should be of type Integer. this info used by compiler to select among the different 'read' instances proper one. actually, in type inference algorithm, some types are already known from context (function types if you given type declarations, types of some results or parameters, types of global variables and fields in datatypes) and compiler infer types of all other values using this information > theoretically is it possible to do a strictness > analysis without any help from the programmer? compiler contains such analyzer, it just not so smart as people writing the program. in the definition inc n = n+1 compiler infers that function is strict -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Mark T.B. Carroll wrote: Janis Voigtlaender <[EMAIL PROTECTED]> writes: (snip) Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. (snip) I've always been a little surprised when this doesn't happen more widely for things other than instances. For instance, when IntMap.size, Map.size and Set.size (or whatever) are all in scope as "size", it should be fairly obvious what (size x) is about once we've inferred, for other reasons, that x is an IntMap. Similarly with records, if we had field names that cause functions for extracting the value of those fields, where we used the same field name in two different record types, I figure that there's usually no ambiguity because we can usually infer the type of the object to which the 'extractor' is being applied. Am I just not seeing the big picture, or would people not find this use of type information to resolve such ambiguities as nice as I would, or is it harder to do that than I'm expecting? I think this is because in Haskell the only way to overload function names is to use type classes and instances just as the one and only way to qualify an identifier is by using modules. This has the advantage that different concerns are clearly separated out and dealt with in exactly one place by one concern-specific mechanism. Perhaps the basic problem is that (size) really belongs in a type class and IntMap, Set, Map etc were created before anyone bothered to try and factor their portions of common functionality into type classes. This factoring is a non-trivial problem however (as you can see from the various posts on the subject of sequences) since the design space is not nearly as well understood as basic mathematical objects like monoids, monads etc and without a mathematical foundation it is difficult to design a type class factoring with any confidence. For record fields, I suggested a while back that the compiler could automatically create the relevant type classes and instances eg: data Point i = Point {x :: i} would ensure that a global typeclass was created if not already present: class (.x) a b | a -> b where (.x) :: a -> b and would also create an instance for that type: instance (.x) (Point i) i where (.x) (Point k) = k where ".x" is parsed as a single lexeme and treated as a postfix operator ie: -- no space between '.' and fieldname exp .x or exp.x === (.x) exp but exp . x === (.) exp x -- composition To refer to a particular field name directly you could use: g = ((.x) :: Point a -> a) but I also thought it might be nice to have a special syntax to make things less clunky eg: g = Point^x (It could not be written as Point.x because Point is not a module name, unless you wanted to destroy the very simple rule that Foo.xyz qualifies xyz by the module Foo) In any case with the trivial syntactic sugar above it would already be possible to use the same record names in multiple types simultaneously. I think the reason there was no positive feedback about this idea before is that unfortunately it looks as if the record system is to be extended to deal with subtyping or horrible anonymous records such as {x=5} that don't have an explicit value constructor in front of them instead of just concentrating on making the existing system (which I really like apart from the lack of field name overloading and dot access syntax) more usable as above. For value constructors, a change in the type inference algorithm would be needed if they were to be resolved based on their types so you could write eg: data Location = Left | Right | Up | Down data Hand = Left | Right foo :: Location -> Hand foo Left = Left foo Up = Left foo Right = Right foo Down = Right and again there could be a syntax like Location^Left as a less clunky alternative to (Left::Location) in cases where ambiguity needs to be resolved explicitly eg if someone didn't want to write a top level type signature for their function. Imho this would make life a lot easier because you could concentrate on names that are appropriate to the type without having to know about all the other types you'd want to use unqualified in the same scope. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Janis Voigtlaender <[EMAIL PROTECTED]> writes: (snip) > Yes, as long as enough type information is provided for the > typechecker to decide what is the correct instance to use. (snip) I've always been a little surprised when this doesn't happen more widely for things other than instances. For instance, when IntMap.size, Map.size and Set.size (or whatever) are all in scope as "size", it should be fairly obvious what (size x) is about once we've inferred, for other reasons, that x is an IntMap. Similarly with records, if we had field names that cause functions for extracting the value of those fields, where we used the same field name in two different record types, I figure that there's usually no ambiguity because we can usually infer the type of the object to which the 'extractor' is being applied. Am I just not seeing the big picture, or would people not find this use of type information to resolve such ambiguities as nice as I would, or is it harder to do that than I'm expecting? -- Mark ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9
On Sat, Jul 29, 2006 at 05:35:30PM -0700, Andrew Pimlott wrote: > On Sat, Jul 29, 2006 at 02:59:06AM +0200, Udo Stenzel wrote: > > Andrew Pimlott wrote: > > > Second, "foo" is just as good a directory > > > as "foo/" to the system > > > > ...unless you have both (think Reiser4) or you want to create the file > > (I think, but I'm not sure). However, what's the point in being > > ambiguous when we can be explicit? Sometimes there is a difference, > > libraries and tools shouldn't gloss over that without consideration. > > As I said, it's one of those line-drawing exercises. But your points > are well taken, and maybe the trailing delimiter should be part of the > model. (My criterion has been whether any filesystem operations require > the trailing delimiter. It sounds like with reiser4fs they might.) Actually, I just read in LWN that that part of reiser4 has been dropped. On the other hand, it was only dropped after considerable debate, and people using an older version of reiser4 still have the strange file-as-directory semantics. -- David Roundy http://www.darcs.net ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] a bunch of newbie questions
Imam Tashdid ul Alam wrote: what's the difference between data and co-data exactly? or between inductive data types and co-inductive data types? In Haskell there is no such difference, as inductive and coinductive types coincide in the semantic setting in which Haskell is usually interpreted. If there were a difference, that is, if we interpret Haskell minus general recursion in a somewhat simpler semantic setting, then data types would contain inly finite values, whereas codata types could also contain infinite values. can you give me some reference points that explain these? Papers by Uustalu and Vene might be a good start. Watch out for corecursion and coalgebras. (read "56")::Integer does it in fact pass the type (Integer) to the function (read)? No, it just says that the result of read should be an Integer. I guess what we want is for the (Integer) implementation of the (read) function to evaluate, not really to cast the value of (read) function to (Integer). Exactly. And that's what is happening. Based on the information provided when giving the result type. in the regex libraries, (~=) cast this way results in completely different things altogether, should type classes have namespaces associated with them? somewhat like Integer.read "56"? I don't think that we need this. this way of selecting the intended implementation, does it work without trouble with multiparameter type classes as well? Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. One way of reducing the amount of information needed is using functional dependencies. theoretically is it possible to do a strictness analysis without any help from the programmer? Yes, such analyses exist, and are implemented in GHC, for example. They are just approximative, and cannot be exact by computability reasons. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] a bunch of newbie questions
what's the difference between data and co-data exactly? or between inductive data types and co-inductive data types? can you give me some reference points that explain these? > (read "56")::Integer does it in fact pass the type (Integer) to the function (read)? I guess what we want is for the (Integer) implementation of the (read) function to evaluate, not really to cast the value of (read) function to (Integer). in the regex libraries, (~=) cast this way results in completely different things altogether, should type classes have namespaces associated with them? somewhat like Integer.read "56"? this way of selecting the intended implementation, does it work without trouble with multiparameter type classes as well? theoretically is it possible to do a strictness analysis without any help from the programmer? thanks a bunch in advance. __ Do You Yahoo!? Tired of spam? Yahoo! Mail has the best spam protection around http://mail.yahoo.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe