Re: [Haskell-cafe] Exercise in point free-style
G'day all. Quoting Donald Bruce Stewart <[EMAIL PROTECTED]>: > Get some free theorems: > lambdabot> free f :: (b -> b) -> [b] -> [b] > f . g = h . f => map f . f g = f h . map f I finally got around to fixing the name clash bug. It now reports: g . h = k . g => map g . f h = f k . map g Get your free theorems from: http://andrew.bromage.org/darcs/freetheorems/ Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Re: A free monad theorem?
You are right, but I was using "extraction" in a rather non-technical sense. Look at it this way: we have 'x >>= f', let's assume it's the continuation monad. Assuming f has type 'a -> C b' we must have something of type a to be able to call the function be at all. Somehow >>= is able make sure that f is called (modulo non- termination), so I still claim it "extracts" an 'a'. It's not a value that >>= will actually ever get its hands on, it only manages to make sure its passed to f. So somewhere there is an 'a' lurking, or f could not be called. Perhaps you don't want to call that "extraction", and that's fine by me. :) -- Lennart On Sep 3, 2006, at 12:32 , Daniel Fischer wrote: Am Sonntag, 3. September 2006 15:39 schrieb Lennart Augustsson: Well, bind is extracting an 'a'. I clearly see a '\ a -> ...'; it getting an 'a' so it can give that to g. Granted, the extraction is very convoluted, but it's there. -- Lennart But instance Monad (Cont r) where return = flip id (>>=) = (. flip) . (.) -- or would you prefer (>>=) = (.) (flip (.) flip) (.) ? if we write it points-free. No '\a -> ...' around. And, being more serious, I don't think, bind is extracting an 'a' from m. How could it? m does not produce a value of type a, like a (State f) does (if provided with an initial state), nor does it contain values of type a, like [] or Maybe maybe do. And to my eyes it looks rather as though the '\a -> ...' tells us that we do _not_ get an 'a' out of m, it specifies to which function we will eventually apply m, namely 'flip g k'. But I've never really understood the Continuation Monad, so if I'm dead wrong, would you kindly correct me? And if anybody knows a nontrivial but not too advanced example which could help understanding CPS, I'd be glad to hear of it. Cheers, Daniel On Sep 2, 2006, at 19:44 , Udo Stenzel wrote: Benjamin Franksen wrote: Sure. Your definition of bind (>>=): ... applies f to something that it has extracted from m, via deconstructor unpack, namely a. Thus, your bind implementation must know how to produce an a from its first argument m. I still have no idea what you're driving at, but could you explain how the CPS monad 'extracts' a value from something that's missing something that's missing a value (if that makes sense at all)? For reference (newtype constructor elided for clarity): type Cont r a = (a -> r) -> r instance Monad (Cont r) where return a = \k -> k a m >>= g = \k -> m (\a -> g a k) Udo. -- Streitigkeiten dauerten nie lange, wenn nur eine Seite Unrecht hätte. -- de la Rochefoucauld ___ 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 -- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A free monad theorem?
G'day all. Quoting Benjamin Franksen <[EMAIL PROTECTED]>: > As we all know, the monadic bind operation has type: > > bind :: Monad m => m a -> (a -> m b) -> m b > > My intuition says that in order to apply the second argument to some > non-trivial (i.e. non-bottom) value of type a, the bind operator needs to > be able to somehow 'extract' a value (of type a) from the first argument > (of type m a). I would like to argue that this is because bind is > polymorphic in a, which makes it impossible to construct values of type > a 'out of thin air' (besides bottom). ...which you can indeed do, and it is indeed a free theorem. Let's forget for a moment that we know any monad laws, and only know the laws for Functor: fmap (f . g) = fmap f . fmap g fmap id = id Assuming M is a Functor, then bind, by virtue of its type alone, has a free theorem: forall f :: A1 -> A2 forall g :: B1 -> B2 forall m :: M A1 forall k1 :: A1 -> M B1 forall k2 :: A2 -> M B2 ( fmap g . k1 = k2 . f => fmap g (m >>= k1) = (fmap f m) >>= k2 ) Setting g = id and doing a bit of rearranging and renaming gives: forall f :: A1 -> A2 forall m :: M A1 forall k :: A1 -> M B bind (fmap f m) k = bind m (k . f) This gives the law for shifting f across a bind operation. To see how "values" can be shifted, we can simply set f = const x: forall m :: M A forall k :: A -> M B forall x :: A bind (fmap (const x) m) k = bind m (\_ -> k x) If x is a specific non-bottom value, this shows exactly how x can be shifted from the left hand side of a bind to the right hand side. And, as you can see, the only place where k can get the value x is from the left-hand side. As someone else on this thread pointed out, in category theory, monads are usually understood in terms of these operations: return :: a -> M a join :: M (M a) -> M a The bind operation can then be defined as: bind m k = join (fmap k m) Like the laws for bind, the laws for return and join are not actually needed to prove the above law. You only need to assume that M is a Functor: bind (fmap (const x) m) k =(defn. of bind) join . fmap k . fmap (const x) $ m =(M is a functor) join . fmap (k . const x) $ m =(defn. of bind) bind m (k . const x) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Advantages of using qualified names and a uniform naming convention
Hi - There's lots of great Haskell libraries available, but little standardization regarding naming conventions or code organization. In this post I try to illustrate some dimensions of the question of how to form names for things and offer my opinion on specific examples knowing that this of course only represents my own personal view but may nevertheless be of objective interest as an *example* of a view and a possible starting point for discussion/ unification of naming conventions in Haskell code if such a thing is even desired/desireable at all. It would be helpful to build up a more rigorous algorithm for determining names, but I think the first step is to try and isolate aspects of the problem thus the following is an initial attempt in this direction... Firstly, I found the following advice by Henning Thielemann very useful in my own code [1]: In the style of Modula-3 I define one data type or one type class per module. The module is named after the implemented type or class. Then a type is named T, and a type class C. I use them qualified, e.g. Music.T or Collection.C. Similarly, if a type has only one constructor then I call it Cons and use it qualified MidiFile.Cons [I don't agree with this last suggestion]. This style also answers the annoying question whether the module name should be in singular or plural form: Always choose singular form! where the only thing I change is that the name of the value constructor for a type with only one value constructor should be the same as the name of the type constructor eg newtype T a = T (a->Int) which seems to be the normal convention anyway and seems better imho than introducing a different identifier for the value constructor when the namespaces for values and types/classes are already distinct. The advantage of such a strict rule is that code becomes deliciously uniform and neat, even if you just follow the part of it that deals with types and modules and use some different convention for classes. It's also particularly nice if you're used to object oriented languages, since it preserves the intuition that you can deal with one thing at a time just as you would put each object into its own separate file or C++ unit. Of course, not all modules can have just one type but I find that most only need to export one type and in any case the (main) exported type can be called "T". The exception is when the types are mutually recursive, so that different types which should really have their own module have to be put into the same module due to limitations of the compiler being used (eg GHC does not yet support mutually recursive modules involving types declared using newtype deriving and also requires hs-boot files which is imho a horrible mess as bad as the need to write separate header files in C and keep decls in sync therefore I avoid them at all costs). Consider the following: import Data.IORef main = do x <- newIORef (0::Int) writeIORef x 3 compared to: import qualified Prime.Data.IORef as Ref main = do x <- Ref.new (0::Int) Ref.write x 3 To my mind the latter is infinitely cleaner looking, because the names of the functions just specify their purpose and nothing else, and it is immediately clear which module they have come from, and there is also the advantage that a shorter prefix could be used if required eg "R". In contrast, the first code example is polluted with mutiple repetitions of "IORef" - we already know we're in the IO monad so why keep stressing the point that we're using IORefs as opposed to STRefs etc? - and there is not even any certainty that the functions so named even come from that module (unless we're already familiar with the contents of the other modules of course). Not only does the latter code look startlingly beautiful, but there is a significant advantage when using an editor which is sophisticated enough to make use of it: after typing the dot in "Ref.", it should be possible for an editor to then display a pop-up list of the visible contents of the module (various possible patent issues aside :-( ) ie the programmer just needs to know the module alias name rather than the names of each individual function/value/type/class when coding. Furthermore (see there's almost no end to the advantages of this convention! ;-)) if the implementation of IORef's was improved later, the whole module can be instantly ported to use the improved implementation just by changing the one import line rather than a painful search and replace of "newIORef" by "newBetterIORef" etc. I think the current presence of names like "newIORef" in the base library is perhaps a result of historical development - qualified names or aliases may not yet have been invented so there was probably a need to follow a convention of appending the type to the purpose when creating a functio
Re: [Haskell-cafe] practice problems?
Paul Johnson wrote: "Brian Hulley" <[EMAIL PROTECTED]> wrote: What about a library for interval arithmetic [1]? [Interval 5 5] / [Interval -1 1] = [FromNegInfinityTo -5, ToPosInfinityFrom 5] Take a look at my Ranged Sets library at http://sourceforge.net/projects/ranged-sets Hi Paul - Thanks for the link to your lib (do you want to add a link from http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics ?) I've only had time to have a brief look but it seems that RSet's could be used as interval arithmetic numbers with suitable instance decls for Num etc. My knowledge of interval arithmetic itself however is not sufficient to tell at this moment if the full generality of RSet's is actually needed ie perhaps it is enough to just say that division by a range containing zero should be undefined and perhaps there are no other ops which would cause more than one result range in which case it would be inefficient to use a more general representation than needed. Possibly there could be two different implementations of interval arithmetic - one allowing for multiple ranges and one that just treated division by an interval containing zero (and other problematic situations) to be undefined, so that the results of each op would be a single range when machine-level speed is needed and it is known in advance that division by zero etc will not happen in the specific problem domain. Anyway thanks for sharing your library with a nice BSD3 license! :-) 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] Re: beginner's problam with a monad
Benjamin Franksen wrote: > Partially applying Tracker to one argument ('T a') gives you a type > constructor that has only one remaining 'open' argument and thus can be > made an instance of class Monad. Totally clear, thanks a lot (also to Keegan). Julien ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: beginner's problam with a monad
Julien Oster wrote: > Now if anyone could enlighten me about the "instance Monad Tracker a" > instead of "instance Monad Tracker" part, everything will be clear! Hello Julien, The way you defined it, Tracker is a type constructor with two arguments, both of which are types; another way to state this is to say that Tracker has kind (* -> * -> *). However, a monad is a type constructor with kind * -> *, i.e. it accepts only one type argument. This can be seen from the class definition, where m is always used with one argument (i.e. 'm a' or 'm b' and a and b are types). Partially applying Tracker to one argument ('T a') gives you a type constructor that has only one remaining 'open' argument and thus can be made an instance of class Monad. HTH, Ben ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Problems trying to understand the BSD license
Hi - I'm not sure if this is the right place to ask this question but since a lot of Haskell code is under the BSD license I think the answer could be useful for other people as well. The question I have is if I want to redistribute a binary executable under my own proprietary license that uses code from various BSD libraries, what exact text do I need to add to my license to satisfy the BSD licenses that came with the libraries? Is the code that is part of the executable considered to be a redistribution of the library in binary form? Also consider this apparent contradiction: Copyright (c) 1988 XYZ ... 1) Redistributions of source code... 2) Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 3) Neither the name of XYZ nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. In order to comply with 2), it suggests I'd need to insert something along the lines of: Portions of this software are copyrighted by XYZ, PQR, STU, ... Portions of this software are provided by XYZ, ..., "as is" and any express or implied warranties ... but does this infringe on 3), which states that the name of XYZ should not be used to endorse the product? Ie is the mention of XYZ's name in the license considered to *not* be an endorsement? And what about "this list of conditions"? Does that also include the first condition ("Redistributions of source code ...") even though only a binary executable is being supplied to the licensee? I also don't want the licensee to get confused and think the whole executable is being distributed under BSD. Also what about the application's "about" dialog or help pages? Would an acknowledgement of libraries used in the code and their authors be considered to be using them to endorse my product or would it be regarded as a welcome acknowledgement for their hard work in making the libraries available? Is this required or prohibited by the BSD license? Surprisingly, although I have looked at several websites which discuss the BSD license, none of them actually say what the practical down to earth text of a proprietary license of a binary executable using BSD licensed components is supposed to look like. Any ideas? Thanks, 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] beginner's problam with a monad
Now if anyone could enlighten me about the "instance Monad Tracker a" instead of "instance Monad Tracker" part, everything will be clear! A Monad always takes one type argument -- the a in IO a, Maybe a, etc. So Tracker can't be a Monad (it needs two arguments), but (Tracker a) is, for any a. This is basically partial application at the type level. Formally, we say a Monad needs to have "kind" * -> *. Kinds are like types for the type level. A kind of * indicates an actual type which can have values, etc. A kind of k1 -> k2 indicates a type operator which wants as an argument a type of kind k1, and will produce a type of kind k2. As with types, the kind arrow is right-associative and partial application is allowed. We can see the mismatch in the following (hypothetical) GHCi session: Prelude> :info Monad class Monad (m::* -> *) where ... Prelude> :kind Tracker Tracker :: * -> * -> * Prelude> :kind Tracker Bool Tracker Bool :: * -> * Hope that helps, keegan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] beginner's problam with a monad
Dan Doel wrote: > Thus, unfortunately, you won't be able to implement the general bind > operator. To do so, you'd need to have Tracker use a list that can > store values of heterogeneous types, which is an entire library unto > itself (HList). Telling me that it just won't work was one of the best answers you could give me, because now I know that I can stop trying (well, I think I will have a look at HList. If it's easy enough...) Now if anyone could enlighten me about the "instance Monad Tracker a" instead of "instance Monad Tracker" part, everything will be clear! Thanks a lot, Julien ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] beginner's problam with a monad
On 9/3/06, Julien Oster <[EMAIL PROTECTED]> wrote: Hello, Hi. Why does the interpreter infer Tracker a a instead of the more general Tracker a c? The problem is that you're trying to keep a list of all computations performed, and lists can only store values of one uniform type. So, if you have a Tracker storing a list of values of type [a], it must also represent a computation of type a via the second argument, because that's the only type it can append to the list. Thus, unfortunately, you won't be able to implement the general bind operator. To do so, you'd need to have Tracker use a list that can store values of heterogeneous types, which is an entire library unto itself (HList). Hope that helps some, Dan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] beginner's problam with a monad
Hello, after succeeding in implementing my first monad (Counter, it increments a counter every time a computation is performed) I though I'd try another one and went on to implement "Tracker". "Tracker" is a monad where a list consisting of the result of every computation is kept alongside the final value, kind of a computation history. It really just serves me as an exercise to implement monads. However, the following source code fails: {-} data Tracker a b = Tracker [a] b deriving Show instance Monad (Tracker a) where m >>= f = let Tracker l x = m in let Tracker l' x' = f x in Tracker (x':l) x' return x = Tracker [] x bar = do x <- Tracker [] 12 y <- return (x*2) z <- return (y*3) return (z+3) {-} Of course, style recommendations and the like are always appreciated. (by the way, I don't really understand why I have to type instance Monad (Tracker a) instead of instance Monad Tracker which may very well be the problem. If it's not, can someone tell me anyway?) Trying to load this piece of code leads to the following error message: Hugs.Base> :load Test.hs ERROR "Test.hs":30 - Inferred type is not general enough *** Expression: (>>=) *** Expected type : Monad (Tracker a) => Tracker a b -> (b -> Tracker a c) -> Tracker a c *** Inferred type : Monad (Tracker a) => Tracker a b -> (b -> Tracker a a) -> Tracker a a Why does the interpreter infer Tracker a a instead of the more general Tracker a c? Thanks, Julien ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] practice problems?
"Brian Hulley" <[EMAIL PROTECTED]> wrote: What about a library for interval arithmetic [1]? I'd imagine it could start something like: data Interval a = Interval !a !a deriving (Eq, Show) instance Num a => Num (Interval a) where Interval llow lhigh + Interval rlow rhigh = Interval (min llow rlow) (max lhigh rhigh) The Interval type would probably need to explicitly represent several kinds of intervals eg (-infinity, x] etc and there are some tricky issues about what to do with the operations whose result sometimes needs to be represented by more than one interval to be useful such as division by an interval containing zero eg you might want to use a list of intervals to deal with these cases: instance Num a => [Interval a] where ... ie [Interval 5 5] / [Interval -1 1] = [FromNegInfinityTo -5, ToPosInfinityFrom 5] Take a look at my Ranged Sets library at http://sourceforge.net/projects/ranged-sets Paul. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Re: A free monad theorem?
Lennart Augustsson wrote: > Well, bind is extracting an 'a'. I clearly see a '\ a -> ...'; it > getting an 'a' so it can give that to g. Granted, the extraction is > very convoluted, but it's there. Oh, that can be remedied... > m >>= g = m . flip g In fact, why even mention m? > (>>=) = (. flip) . (.) Anyway, there's no "a extracted from m", since a function cannot be deconstructed. That lets the "free theorem" degenerate into "m >>= k does something with m and/or k, most of the time", which is kinda meaningless and explains exactly nothing. Udo. signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Re: A free monad theorem?
Am Sonntag, 3. September 2006 15:39 schrieb Lennart Augustsson: > Well, bind is extracting an 'a'. I clearly see a '\ a -> ...'; it > getting an 'a' so it can give that to g. Granted, the extraction is > very convoluted, but it's there. > > -- Lennart But instance Monad (Cont r) where return = flip id (>>=) = (. flip) . (.) -- or would you prefer (>>=) = (.) (flip (.) flip) (.) ? if we write it points-free. No '\a -> ...' around. And, being more serious, I don't think, bind is extracting an 'a' from m. How could it? m does not produce a value of type a, like a (State f) does (if provided with an initial state), nor does it contain values of type a, like [] or Maybe maybe do. And to my eyes it looks rather as though the '\a -> ...' tells us that we do _not_ get an 'a' out of m, it specifies to which function we will eventually apply m, namely 'flip g k'. But I've never really understood the Continuation Monad, so if I'm dead wrong, would you kindly correct me? And if anybody knows a nontrivial but not too advanced example which could help understanding CPS, I'd be glad to hear of it. Cheers, Daniel > > On Sep 2, 2006, at 19:44 , Udo Stenzel wrote: > > Benjamin Franksen wrote: > >> Sure. Your definition of bind (>>=): > >> ... > >> applies f to something that it has extracted from m, via > >> deconstructor > >> unpack, namely a. Thus, your bind implementation must know how to > >> produce > >> an a from its first argument m. > > > > I still have no idea what you're driving at, but could you explain how > > the CPS monad 'extracts' a value from something that's missing > > something > > that's missing a value (if that makes sense at all)? > > > > For reference (newtype constructor elided for clarity): > >> type Cont r a = (a -> r) -> r > >> > >> instance Monad (Cont r) where > >>return a = \k -> k a > >>m >>= g = \k -> m (\a -> g a k) > > > > Udo. > > -- > > Streitigkeiten dauerten nie lange, wenn nur eine Seite Unrecht hätte. > > -- de la Rochefoucauld > > ___ > > 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 -- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] practice problems?
On Sep 3, 2006, at 8:22 AM, Brian Hulley wrote: Tamas K Papp wrote: On Sun, Sep 03, 2006 at 12:47:45PM +0400, Bulat Ziganshin wrote: i also suggest you to start write some library. there is enough useful libs that are still bnot implemented because lack of time (and insterest in such simple code) on side of more experienced programmers. i once proposed you to write strings library, another interesting and useful thing will be gzip/bzip2-lib bindings Bulat, I would be happy to write a strings library, I just don't know that it is supposed to do... (I have no CS education, only math/economics). If you show me the specifications or documentation in another language, I would write one as practice. What about a library for interval arithmetic [1]? I'll sign up to write this just as soon as I can control the floating- point rounding mode in purely functional code with low overhead. :-) Without this control, you end up with a toy which can't actually be used for real work. Sadly, I don't think GHC's built-in thread scheduler plays nicely with floating-point mode changes unless you do them across the entire program for the entire run. The interval multiplication algorithm turns out to be exciting. :-) -Jan-Willem Maessen smime.p7s Description: S/MIME cryptographic signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Re: A free monad theorem?
Well, bind is extracting an 'a'. I clearly see a '\ a -> ...'; it getting an 'a' so it can give that to g. Granted, the extraction is very convoluted, but it's there. -- Lennart On Sep 2, 2006, at 19:44 , Udo Stenzel wrote: Benjamin Franksen wrote: Sure. Your definition of bind (>>=): ... applies f to something that it has extracted from m, via deconstructor unpack, namely a. Thus, your bind implementation must know how to produce an a from its first argument m. I still have no idea what you're driving at, but could you explain how the CPS monad 'extracts' a value from something that's missing something that's missing a value (if that makes sense at all)? For reference (newtype constructor elided for clarity): type Cont r a = (a -> r) -> r instance Monad (Cont r) where return a = \k -> k a m >>= g = \k -> m (\a -> g a k) Udo. -- Streitigkeiten dauerten nie lange, wenn nur eine Seite Unrecht hätte. -- de la Rochefoucauld ___ 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] practice problems?
Brian Hulley wrote: Interval llow lhigh + Interval rlow rhigh = Interval (min llow rlow) (max lhigh rhigh) Not a good start!!! ;-) Interval llow lhigh + Interval rlow rhigh = Interval (llow+rlow) (lhigh+rhigh) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] practice problems?
Tamas K Papp wrote: On Sun, Sep 03, 2006 at 12:47:45PM +0400, Bulat Ziganshin wrote: i also suggest you to start write some library. there is enough useful libs that are still bnot implemented because lack of time (and insterest in such simple code) on side of more experienced programmers. i once proposed you to write strings library, another interesting and useful thing will be gzip/bzip2-lib bindings Bulat, I would be happy to write a strings library, I just don't know that it is supposed to do... (I have no CS education, only math/economics). If you show me the specifications or documentation in another language, I would write one as practice. What about a library for interval arithmetic [1]? I'd imagine it could start something like: data Interval a = Interval !a !a deriving (Eq, Show) instance Num a => Num (Interval a) where Interval llow lhigh + Interval rlow rhigh = Interval (min llow rlow) (max lhigh rhigh) The Interval type would probably need to explicitly represent several kinds of intervals eg (-infinity, x] etc and there are some tricky issues about what to do with the operations whose result sometimes needs to be represented by more than one interval to be useful such as division by an interval containing zero eg you might want to use a list of intervals to deal with these cases: instance Num a => [Interval a] where ... ie [Interval 5 5] / [Interval -1 1] = [FromNegInfinityTo -5, ToPosInfinityFrom 5] though using a list may make things too slow (ideally it would be nice to have interval arithmetic that's as fast as normal floating point arithmetic - is this possible?) Alternatively, these cases could just be undefined though that might limit the usefulness of the lib. Another extremely useful thing would be a symbolic math library with a BSD (or LGPL) license... And yet another extremely useful thing would be a good library for numerical computations (there is GSLHaskell but that's licensed under GPL so there still seems to be a gap for something similar using LGPL or BSD). In general if you look at http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics there appear to be many extremely useful libs already written, but unfortunately a lot of them are not BSD compatible so I think there is a huge gap for math related libs that people can use for commercial projects. Anyway just an idea :-), Brian. [1] http://en.wikipedia.org/wiki/Interval_arithmetic -- 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] practice problems?
On Sun, Sep 03, 2006 at 12:47:45PM +0400, Bulat Ziganshin wrote: > Hello Tamas, > > Sunday, September 3, 2006, 12:15:48 PM, you wrote: > > > I am looking for small to medium sized practice problems, preferably > > with solutions. Hal Daume's tutorial had some good one-liners (eg > > rewrite something point-free) but I am looking for something which > > would take 1-3 hours for a newbie, and then I could look at a solution > > not exactly that you ask but i recommend you "hitchhikers guide" and > "implementing Scheme in 48 hours" as an interesting mini-books for > "advanced newbie". look at "books and tutorials" page > > i also suggest you to start write some library. there is enough useful > libs that are still bnot implemented because lack of time (and > insterest in such simple code) on side of more experienced > programmers. i once proposed you to write strings library, another > interesting and useful thing will be gzip/bzip2-lib bindings Bulat, I would be happy to write a strings library, I just don't know that it is supposed to do... (I have no CS education, only math/economics). If you show me the specifications or documentation in another language, I would write one as practice. Thanks, Tamas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] practice problems?
Hello Tamas, Sunday, September 3, 2006, 12:15:48 PM, you wrote: > I am looking for small to medium sized practice problems, preferably > with solutions. Hal Daume's tutorial had some good one-liners (eg > rewrite something point-free) but I am looking for something which > would take 1-3 hours for a newbie, and then I could look at a solution not exactly that you ask but i recommend you "hitchhikers guide" and "implementing Scheme in 48 hours" as an interesting mini-books for "advanced newbie". look at "books and tutorials" page i also suggest you to start write some library. there is enough useful libs that are still bnot implemented because lack of time (and insterest in such simple code) on side of more experienced programmers. i once proposed you to write strings library, another interesting and useful thing will be gzip/bzip2-lib bindings -- 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] Are associated types synonyms like type classes?
Hello Brian, Saturday, September 2, 2006, 10:19:17 PM, you wrote: > What is the practical difference between class A and class B? With > class A we can define instances so that f is overloaded (Int -> > Bool), (String -> Bool), (Bool -> Bool) by defining instances of A > for Int, String, and Bool, but we cannot overload it more (Int -> > String), (Int -> Int) because we can only have on "instance A Int". > The converse is true for class B. Is that the only difference? > If so, then why do we have "associated types" instance of "associated > classes" like this?: > > class A a where > class B b where > f :: a -> b > instance A Int where > instance B Bool where > f = (==0) class defines a set of types, type defines just one type. So, defining class inside class or using your hand-made syntax we will got just the same thing as MPTC: > The made-up syntax I presented in my previous message was just a > different way of writing the above (which is also made-up syntax): > class A a, B b where f :: a -> b > instance A Int, B Bool where f = (==0) using associated type inside class is a way to define many-to-one relationship, i.e. it's the same as MPTC+FD > class Elem elem, Collect collect where > empty :: collect > insert :: elem -> collect -> collect > toList :: collect -> [elem] your syntax differs from MPTC only in that we have two class names - Elem and Collect, but that is not that we need - we need type restrictions that joins collection with its element types: insertMany :: (Collection c e) => [e] -> c -> c if we will try to use different class names here, the requirement to insert into collection elements it can hold, will not be expressed: insertMany :: (Elem e, Collect c) => [e] -> c -> c -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] practice problems?
Hi, I am a Haskell newbie. Having read some tutorials (Yet Another, Gentle Introduction) and some papers/tutorials on monads, I would like to spend some time practicing what I have learned before embarking on more abstract/obscure things and/or using Haskell for everyday tasks. I am looking for small to medium sized practice problems, preferably with solutions. Hal Daume's tutorial had some good one-liners (eg rewrite something point-free) but I am looking for something which would take 1-3 hours for a newbie, and then I could look at a solution by a Haskell expert and discover what I could have done better/more elegantly. Online references (or even book suggestions) would be appreciated. If you are teaching Haskell and have problems with confidential solution sets (some instructors like it that way), I can promise not to disclose the latter ;-) Thanks, Tamas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: A free monad theorem?
On Sun, Sep 03, 2006 at 01:23:13AM +0200, [EMAIL PROTECTED] wrote: > Tomasz Zielonka: > > >Programmers define the >>= method for their monads because they want to > >use it to bind computations. They know how to pass result(s) from > >one computation in their Monad to another, and they put this algorithm > >in the implementation of >>=. If they didn't care about passing results > >from one computation to the next one, they wouldn't be using monads in > >the first place. > > Shrug. > If these programmers didn't care about passing results from one computation > to the next one, they wouldn't use functional programming at all. > Hm. > Would it still be "programming"?... I myself wanted to write that then they wouldn't be using a general purpose programming language, but something like HTML, etc. But then I thought that you may want to have "computations" that can't pass values between each other. One example is an algebraic datatype for describing tree-like structures - but you could argue that there is a bottom-up data flow. Anyway, I haven't thought about it too much... Best regards Tomasz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe