Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://www.haskell.org/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. Re: several questions: multi-param typeclasses, etc. (Michael Mossey) 2. Re: several questions: multi-param typeclasses, etc. (Michael Mossey) 3. I have created an ugly Haskell program.. (Philip Scott) 4. Multiple type numeric data (Didier Jacquemart) 5. Error Handling and case statements (i?fai) 6. Re: Multiple type numeric data (i?fai) 7. Re: Error Handling and case statements (Isaac Dupree) 8. Re: several questions: multi-param typeclasses, etc. (Chadda? Fouch?) 9. Re: Multiple type numeric data (David Virebayre) ---------------------------------------------------------------------- Message: 1 Date: Sun, 01 Nov 2009 11:22:19 -0800 From: Michael Mossey <m...@alumni.caltech.edu> Subject: Re: [Haskell-beginners] several questions: multi-param typeclasses, etc. To: beginners@haskell.org Message-ID: <4aeddfeb.5070...@alumni.caltech.edu> Content-Type: text/plain; charset=ISO-8859-1; format=flowed So if I understand correctly, when the compiler sees this class definition: > For example, throwError in in the MonadError class definition: > > class Monad m => MonadError e m | m -> e where > throwError :: e -> m a Then it sees this instance: > Instances: > > Error e => MonadError e (Either e) > Because (Either e) is a monad, it "fits with" the m in the class definition. (The m has the constraint Monad on it.) Knowing that, the compiler uses the functional dependency to conclude that the given instance is the only possible instance. Is that right? Another question: in Control.Monad.Error, I see the instance MonadError IOError IO which leads to the question: apparently I can throw errors in the IO monad using throwError. But there is also throw and throwIO. What is the difference? Thanks, Mike ------------------------------ Message: 2 Date: Sun, 01 Nov 2009 11:31:33 -0800 From: Michael Mossey <m...@alumni.caltech.edu> Subject: Re: [Haskell-beginners] several questions: multi-param typeclasses, etc. To: beginners <beginners@haskell.org> Message-ID: <4aede215.10...@alumni.caltech.edu> Content-Type: text/plain; charset=UTF-8; format=flowed Chaddaï Fouché wrote: > On Sun, Nov 1, 2009 at 5:32 PM, Michael Mossey <m...@alumni.caltech.edu> > wrote: >> On the other hand, if you added >> >> instance (Error e) => MonadError String (Either e) >> >> and didn't include the functional dependency, the compiler would still run >> into a problem with overlapping instances and have no way to decide, which I >> presume is still an error. > > Right, in this case it is true, but supposing the MonadError instance > for Either was rather : > >> instance (Error e) => MonadError (Maybe String) (Either e) > > There would be nothing a priori that would prevent you from writing > another instance : > >> instance (Error e) => MonadError String (Either e) I think I understand that you are saying it would create a messy situation to write this second instance, and the functional constraint causes the compiler to stop with an error if it sees that second instance. Is that true? Now I have a question that probably doesn't make sense, but what I'm really doing is picking your brain. I want to see how you would rephrase it: Let's assume for a moment that two different people are involved in this code. One of them writes the class definition. Another one writes an instance. In OO, which I am more familiar with, one person will write a class with a limited API in order to help put guarantees on the correct behavior of the class. In a sense, that person is saying: "I release my class to the world to do what it will, but before doing that I put some constraints on it so no one can distort my intentions." Is this functional dependency a similar situation? Does it make sense from the "point of view" of the author of the class definition? Or is it more a practical necessity? Thanks, Mike ------------------------------ Message: 3 Date: Sun, 1 Nov 2009 23:27:42 +0000 From: Philip Scott <haskell-beginn...@foo.me.uk> Subject: [Haskell-beginners] I have created an ugly Haskell program.. To: beginners@haskell.org Message-ID: <200911012327.43027.haskell-beginn...@foo.me.uk> Content-Type: Text/Plain; charset="us-ascii" .. and I am positive there must be a way of beautifying it, but I am struggling. I bet there is just some lovely way of making this all shrink to three lines.. So here's the problem. I have two lists of tuples: (timestamp, value) What I would like to do in do a kind of 'zip' on two of these lists to make a list of (timestamp, (value1, value2)) with the following rules: - If the timestamps are equal it's easy - make your new element an move on - If one of the lists has a timestamp that the other doesn't, repeat an old value from the other list - If we don't have an old value yet, then don't create an element in the new list. e.g. if I ran my algorithm on these two lists d1 = [ (1,"a"), (2,"b"), (3,"c") ] d2 = [ (2,"b'"), (4,"d'") ] I would like to get result = [ (2, (b,b')), (3, (c,b')), (4, (c,d')) ] e.g. there was no data in d2 for our first element so we skipped it. Okay, so here is my code.. It works, but makes me feel a bit dirty. To explain my nomenclature 't' is 'timestamp of', 'v' is 'value of'. vx' and vy' are the 'old' values from the previous iteration in case a repeat is needed. They are Maybes because at the beginning there may be no old value. d1 = [ (1,"a"), (2,"b"), (3,"c") ] d2 = [ (2,"b'"), (4,"d'") ] t (x,y) = x v (x,y) = y js vx' vy' (x:xs) (y:ys) | t x == t y = ( (t x), (v x, v y) ) : js (Just (v x)) (Just (v y)) xs ys | t x < t y = maybe (js (Just (v x)) Nothing xs (y:ys)) (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs (y:ys))) vy' | t x > t y = maybe (js Nothing (Just (v y)) (x:xs) ys) (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y)) (x:xs) ys)) vx' js vx' vy' (x:xs) [] = maybe [] (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs [])) vy' js vx' vy' [] (y:ys) = maybe [] (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y)) [] ys )) vx' js _ _ [] [] = [] You call it with the first two arguments as Nothing to kick it off (I have a trivial wrapper function to do this) It works fine: > :t js js :: (Ord t) => Maybe a1 -> Maybe a -> [(t, a1)] -> [(t, a)] -> [(t, (a1, a))] > js Nothing Nothing d1 d2 [(2,("b","b'")),(3,("c","b'")),(4,("c","d'"))] But it just feels gross. Any advice on how to tame this beast would be greatly appreciated :) All the best, Philip ------------------------------ Message: 4 Date: Sun, 01 Nov 2009 18:53:22 +0100 From: Didier Jacquemart <didier.jacquem...@free.fr> Subject: [Haskell-beginners] Multiple type numeric data To: beginners@haskell.org Message-ID: <4aedcb12.8010...@free.fr> Content-Type: text/plain; charset=ISO-8859-1; format=flowed Hello, I'm just learning Haskell and have problems with a simple calculation: Here is my code below : data Figure = Carre Int Int Int | Rond (Int, Int, Integer) -- i hope Integer allows fromInteger function for r surface_carre :: Figure -> Int surface_carre (Carre x y c)= c * c surface_rond :: Figure -> Float surface_rond (Rond (x, y, r))= 3.14 * r * r surface x = case x of Carre a b c -> surface_carre x Rond (a, b, c) -> surface_rond x a::Figure a=Carre 10 10 5 b::Figure b=Rond (20, 20, 3) When i load this program, i get the following error for the line 3.14 * r * r Couldn't match expected type Float against inferred type Integer In the expression : 3.14 *r * r ... Further, i think there's a problem with the surface function, since it's not typed. Thanks for your help. Didier. ------------------------------ Message: 5 Date: Sun, 01 Nov 2009 23:57:41 -0500 From: i?fai <iae...@me.com> Subject: [Haskell-beginners] Error Handling and case statements To: Beginners@haskell.org Message-ID: <a9c58ca1-9b5f-4cdf-beaa-0b2a7cdb0...@me.com> Content-Type: text/plain; charset=iso-8859-1; format=flowed; delsp=yes I have been trying to work out a problem for the last few hours with little success. In the following code, using ConfigFile, I obtain the results of the configuration file, but in the main function I am trying to get the Config type out of the case statement. I need to be able to generate that error, but it means the two branches of the case are not the same type. I am not particularly attached to this direction, I am quite willing to do any way that works. I might be adding more configuration in the future. Any ideas? iæfai -- import Network.Shed.Httpd import Network.URI import Data.Either import Data.ConfigFile as C import Control.Monad.Error import Control.Applicative import ChessBoard data Config = Config { documentRoot :: String } deriving (Read, Show) main :: IO () main = do opt <- getConf "./config" config <- case opt of Left (_, err) -> ioError (userError err) Right (config) -> config docPath <- documentRoot config putStrLn "Starting up httpd." server <- initServer 6666 request return () request :: Request -> IO Response request req = do putStrLn $ "Recieved " ++ (show $ uriPath $ reqURI req) return $ Response 404 [] "Not found." -- Mostly from Chris Done's Blog getConf :: FilePath -> IO (Either (C.CPErrorData, String) Config) getConf filePath = runErrorT $ do let cp = C.emptyCP { optionxform = id } contents <- liftIO $ readFile filePath config <- C.readstring cp contents let get = C.get config "DEFAULT" Config <$> get "Document-Root" ------------------------------ Message: 6 Date: Mon, 02 Nov 2009 00:04:03 -0500 From: i?fai <iae...@me.com> Subject: Re: [Haskell-beginners] Multiple type numeric data To: Didier Jacquemart <didier.jacquem...@free.fr> Cc: Beginners@haskell.org Message-ID: <06d51fe2-87d5-42f7-96bd-8c01a3cf4...@me.com> Content-Type: text/plain; charset=iso-8859-1; format=flowed; delsp=yes Didier, here is some code that improves your one function, it will almost compile with ghc. module Main where data Figure = Carre Int Int Int | Rond (Int, Int, Integer) -- i hope Integer allows fromInteger function for r surface_carre :: Figure -> Int surface_carre (Carre x y c)= c * c surface_rond :: Figure -> Float surface_rond (Rond (x, y, r))= 3.14 * (fromInteger (r * r)) surface x = case x of Carre a b c -> surface_carre x Rond (a, b, c) -> surface_rond x a::Figure a=Carre 10 10 5 b::Figure b=Rond (20, 20, 3) main :: IO () main = do putStrLn "Test" return () Note that surface has a problem because surface_carre returns an Int and surface_rond returns a Float. These types are incompatible. I don't think there is a more general type you can use. Can you get away with just using all the same type? - iæfai On 2009-11-01, at 12:53 PM, Didier Jacquemart wrote: > data Figure = Carre Int Int Int > | Rond (Int, Int, Integer) -- i hope Integer allows > fromInteger function for r > > surface_carre :: Figure -> Int > surface_carre (Carre x y c)= c * c > > surface_rond :: Figure -> Float > surface_rond (Rond (x, y, r))= 3.14 * r * r > > surface x = case x of > Carre a b c -> surface_carre x > Rond (a, b, c) -> surface_rond x > a::Figure > a=Carre 10 10 5 > b::Figure > b=Rond (20, 20, 3) ------------------------------ Message: 7 Date: Mon, 02 Nov 2009 00:04:00 -0500 From: Isaac Dupree <m...@isaac.cedarswampstudios.org> Subject: Re: [Haskell-beginners] Error Handling and case statements To: i?fai <iae...@me.com> Cc: Beginners@haskell.org Message-ID: <4aee6840.7090...@isaac.cedarswampstudios.org> Content-Type: text/plain; charset=ISO-8859-1; format=flowed iæfai wrote: > I have been trying to work out a problem for the last few hours with > little success. > ... > config <- case opt of > Left (_, err) -> ioError (userError err) > Right (config) -> config does changing the last line to Right (config) -> return config fix your type error? -Isaac ------------------------------ Message: 8 Date: Mon, 2 Nov 2009 10:15:34 +0100 From: Chadda? Fouch? <chaddai.fou...@gmail.com> Subject: Re: [Haskell-beginners] several questions: multi-param typeclasses, etc. To: Michael Mossey <m...@alumni.caltech.edu> Cc: beginners <beginners@haskell.org> Message-ID: <e9350eaf0911020115q458a5415n4c908c9645849...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Sun, Nov 1, 2009 at 8:31 PM, Michael Mossey <m...@alumni.caltech.edu> wrote: > In OO, which I am more familiar with, one person will write a class with a > limited API in order to help put guarantees on the correct behavior of the > class. In a sense, that person is saying: "I release my class to the world > to do what it will, but before doing that I put some constraints on it so no > one can distort my intentions." > > Is this functional dependency a similar situation? Does it make sense from > the "point of view" of the author of the class definition? > > Or is it more a practical necessity? In this particular case of MonadError, I think the constraint is more of the first variety but most functional constraints are more practical than moral... The case in point being when you want to put a method in the class that don't include all the type parameters of the class in its type : you NEED to have functional constraints for Haskell to accept that the correct method can be determined with this partial information (and determine it later on). It is worth noting that many case where multi-param classes are used with a mandatory practical functional constraint are better expressed by the new indexed type family extension and a single param type class (though this is not always the case) : For instance the classic Collection type class : > class Collection collection elt | collection -> elt where > add :: elt -> collection -> collection > merge :: collection -> collection -> collection > ... (merge is the function that makes the functional constraint a practical necessity) Can be better (or at least more cleanly, depending on who you ask) expressed as : > class Collection c where > type Elt c :: * > add :: Elt c -> c -> c > merge :: c -> c -> c > ... -- Jedaï ------------------------------ Message: 9 Date: Mon, 2 Nov 2009 10:49:34 +0100 From: David Virebayre <dav.vire+hask...@gmail.com> Subject: Re: [Haskell-beginners] Multiple type numeric data To: Didier Jacquemart <didier.jacquem...@free.fr> Cc: beginners@haskell.org Message-ID: <4c88418c0911020149l79af5733ld4cfd366136e7...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Sun, Nov 1, 2009 at 6:53 PM, Didier Jacquemart <didier.jacquem...@free.fr> wrote: > data Figure = Carre Int Int Int >     | Rond (Int, Int, Integer)   -- i hope Integer allows > fromInteger > surface_carre :: Figure -> Int > surface_carre (Carre x y c)= c * c > surface_rond :: Figure -> Float > surface_rond  (Rond (x, y, r))= 3.14  * r * r > surface x = case x of >  Carre a b c   -> surface_carre x >  Rond  (a, b, c) -> surface_rond x > a::Figure > a=Carre 10 10 5 > b::Figure > b=Rond (20, 20, 3) > When i load this program, i get the following error for the line 3.14 * r * > r > > Couldn't match expected type Float >      against inferred type Integer > In the expression : 3.14 *r * r > ... Salut, ton problème c'est que la valeur de retour de surface_rond est float, mais le rayon est integer. Le fait est que Haskell ne veut pas mixer des integer avec des floats sans explicitement lui demander de les convertir. donc surface_rond (Rond (x,y,r)) = 3.14 * ( fromIntegral r) * ( fromIntegral r) mais comme on veut éviter de calculer le fromIntegral r deux fois, il vaut mieux écrire surface_rond (Rond (x,y,r)) = let r' = fromIntegral r in 3.14 * r' * r' Ensuite, tu vas avoir un problème avec la fonction surface : la valeur de retour de surface est soit int, soit float, selon si surface_carre ou surface rond est appelée. Or, c'est invalide. Il te faut choisir un type. le plus général étant float, tu as deux solutions: 1) modifier surface_carre pour que cela retourne un float 2) convertir, dans la fonction surface, la valeur de retour de surface_carre en float. Cela donne : cas 1) modifier la fonction surface_carre mais pas la fonction surface surface_carre (Carre _ _ c) = let c' = fromIntegral c in c' * c' Note que comme tu n'utilise pas les paramètres x et y, tu peux indiquer au compilateur que tu n'en a pas besoin en utilisant un _ au lieu de les nommer. cas 2) modifier la fonction surface mais pas surface_carre surface x = case x of Carre _ _ _ -> fromIntegral $ surface_carre x Rond (_, _, _) -> surface_rond x A mon avis, tu n'a pas besoin des fonctions surface_carre et surface_rond, tu peux définir surface comme suit. surface (Carre _ _ c ) = let c' = fromIntegral c in c' * c' surface (Rond (_ _ r) = let r' = fromIntegral r in 3.14 * r' * r' D'ailleurs par curiosité, dans la définition de figure, pourquoi définis-tu Rond avec les paramètres entre parenthèses ( un triple ) alors que tu ne le fais pas pour Carre ? David. ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 17, Issue 2 ****************************************