Announcement: Real World Haskell - Reading Group

We are organizing a reading group for O'Reilly's - Real World Haskell We will start with Chapter 1 on August 8, 2010 and then cover additional chapters at two week intervals. If interested: http://linuxagora.com This is an all volunteer web site - no advertising, no fees Thank you, Jeff -- http://linuxagora.com

On Fri, 30 Jul 2010 14:18:56 -0500
"Jeff" == Jeff Greer
wrote:
Jeff> We are organizing a reading group for O'Reilly's - Real World Jeff> Haskell Cool. Nice opportunity to (finally) learn it. Jeff> We will start with Chapter 1 on August 8, 2010 and then cover Jeff> additional chapters at two week intervals. Hmmm...28 chapters ---> ~14 months :-) Sincerely, Gour -- Gour | Hlapicina, Croatia | GPG key: CDBF17CA ----------------------------------------------------------------

class Show parType => MuscleCapable parType where -- | This could be a list or a tuple, etc. Whatever way of implementing it, it -- contains all necessary parameters to make the muscle produce a resource. -- Notice that this definition forces the type of ALL the
-- the wrapped up muscle to be the same. data Parameters parType
-- | A way to obtain the values of a @Parameters a@, for printing
listOfParams :: Parameters parType -> [parType]
-- | This wrapper around the muscle function will allow me to
I desperately need help with this little predicament I got myself into. I thought It'd be nice to write a piece of code that would wrap around an older function, which given a bunch of parameters produces a plot (a file) in the working directory. This new code receives the parameters first, and only if the plot is not already present in the directory, should pass the parameters to (and run) the wrapped function. With that in mind I've defined the following type class. The older function is treated as an anonymous 'muscle', capable of taking its parameters ordered in some structure unknown. parameters of purposes produce a
-- resource on demand. muscle :: Parameters parType -> IO FilePath
But when trying to use that, I get different errors at compile time related to my (mis)use of type families, most of which are above my head. I use this dummy code to test the mechanism:
data ThreeTuple a = T3 a a a
listFromThreeTuple :: ThreeTuple a -> [a] listFromThreeTuple (T3 x y z) = [x,y,z]
fun (T3 x y z) = do withFile "output.out" WriteMode $ flip hPutStrLn (concatMap show [x,y,z]) return "output.out"
instance MuscleCapable Int where data Parameters Int = ThreeTuple Int listOfParams = listFromThreeTuple muscle = fun
This fires the following error in GHC (I do add the TypeFamilies LANGUAGE pragma): """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple Int' NB: `Parameters' is a type function """ If I use a similar data type without type parameters:
data ThreeTuple = T3 Int Int Int
And modify the above snippet accordingly, I get the same thing: """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple' NB: `Parameters' is a type function In the expression: listFromThreeTuple In the definition of `listOfParams': """ Whatever alternative I try (and I have gone far along the trial-error path) inevitably yields those errors for both lines implementing 'listOfParams' and 'muscle'. Could somebody help me understand what's going on? I'm really lost at this point. PS: My first attempt at the class used 'type' to define the associated type. I had to switch to 'data' due to problems regarding the chosen type not being _injective_. GHC error messages and the paper "Fun with type functions" helped on that.

On Fri, Jul 30, 2010 at 5:06 PM, MAN
I desperately need help with this little predicament I got myself into. I thought It'd be nice to write a piece of code that would wrap around an older function, which given a bunch of parameters produces a plot (a file) in the working directory. This new code receives the parameters first, and only if the plot is not already present in the directory, should pass the parameters to (and run) the wrapped function.
With that in mind I've defined the following type class. The older function is treated as an anonymous 'muscle', capable of taking its parameters ordered in some structure unknown.
class Show parType => MuscleCapable parType where -- | This could be a list or a tuple, etc. Whatever way of implementing it, it -- contains all necessary parameters to make the muscle produce a resource. -- Notice that this definition forces the type of ALL the parameters of -- the wrapped up muscle to be the same. data Parameters parType
-- | A way to obtain the values of a @Parameters a@, for printing purposes listOfParams :: Parameters parType -> [parType]
-- | This wrapper around the muscle function will allow me to produce a -- resource on demand. muscle :: Parameters parType -> IO FilePath
But when trying to use that, I get different errors at compile time related to my (mis)use of type families, most of which are above my head. I use this dummy code to test the mechanism:
data ThreeTuple a = T3 a a a
listFromThreeTuple :: ThreeTuple a -> [a] listFromThreeTuple (T3 x y z) = [x,y,z]
fun (T3 x y z) = do withFile "output.out" WriteMode $ flip hPutStrLn (concatMap show [x,y,z]) return "output.out"
instance MuscleCapable Int where data Parameters Int = ThreeTuple Int listOfParams = listFromThreeTuple muscle = fun
This fires the following error in GHC (I do add the TypeFamilies LANGUAGE pragma): """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple Int' NB: `Parameters' is a type function """
If I use a similar data type without type parameters:
data ThreeTuple = T3 Int Int Int
And modify the above snippet accordingly, I get the same thing: """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple' NB: `Parameters' is a type function In the expression: listFromThreeTuple In the definition of `listOfParams': """
Whatever alternative I try (and I have gone far along the trial-error path) inevitably yields those errors for both lines implementing 'listOfParams' and 'muscle'.
Could somebody help me understand what's going on? I'm really lost at this point.
PS: My first attempt at the class used 'type' to define the associated type. I had to switch to 'data' due to problems regarding the chosen type not being _injective_. GHC error messages and the paper "Fun with type functions" helped on that.
The error is with your data instance declaration:
data Parameters Int = ThreeTuple Int
You're treating a data declaration as if it were a type declaration - a data declaration needs to have a constructor, something like:
data Paramter Int = ParamInt (ThreeTuple Int)
would be more likely to type check. Then you'd have to pattern match on the constructor to deconstruct it. Type errors aside, all of this looks really really complicated, and from what you're describing I'm not sure it needs to be. Why not just have two functions, one which wraps around the first? Or if you want to write code in a reusable manner, ordinary higher-order functions work well:
writeToFileIfNonExistent :: FilePath -> (FilePath -> IO ()) -> IO () writeToFileIfNonExistent path action = do exists <- doesFileExist path unless exists $ action path return ()
coreFileWritingFunction :: Param1 -> Param2 -> Param3 -> FilePath -> IO () coreFileWritingFunction p1 p2 p3 path = withFile path WriteMode $ \handle -> ...
slickNewWrapper :: Param1 -> Param2 -> Param3 -> FilePath -> IO () slickNewWrapper p1 p2 p3 = writeToFileIfNonExistent $ coreFileWritingFunction p1 p2 p3
I've chosen silly names for my functions, but I hope you get the idea. Don't hesitate to respond if you have any questions. Antoine

Thank you, Antoine! I hadn't picked up on that. It worked perfectly. You are right about this solution being too complex, too. It is. But I admit to be more stubborn than allowed :D El vie, 30-07-2010 a las 22:05 -0500, Antoine Latter escribió:
On Fri, Jul 30, 2010 at 5:06 PM, MAN
wrote: I desperately need help with this little predicament I got myself into. I thought It'd be nice to write a piece of code that would wrap around an older function, which given a bunch of parameters produces a plot (a file) in the working directory. This new code receives the parameters first, and only if the plot is not already present in the directory, should pass the parameters to (and run) the wrapped function.
With that in mind I've defined the following type class. The older function is treated as an anonymous 'muscle', capable of taking its parameters ordered in some structure unknown.
class Show parType => MuscleCapable parType where -- | This could be a list or a tuple, etc. Whatever way of implementing it, it -- contains all necessary parameters to make the muscle produce a resource. -- Notice that this definition forces the type of ALL the parameters of -- the wrapped up muscle to be the same. data Parameters parType
-- | A way to obtain the values of a @Parameters a@, for printing purposes listOfParams :: Parameters parType -> [parType]
-- | This wrapper around the muscle function will allow me to produce a -- resource on demand. muscle :: Parameters parType -> IO FilePath
But when trying to use that, I get different errors at compile time related to my (mis)use of type families, most of which are above my head. I use this dummy code to test the mechanism:
data ThreeTuple a = T3 a a a
listFromThreeTuple :: ThreeTuple a -> [a] listFromThreeTuple (T3 x y z) = [x,y,z]
fun (T3 x y z) = do withFile "output.out" WriteMode $ flip hPutStrLn (concatMap show [x,y,z]) return "output.out"
instance MuscleCapable Int where data Parameters Int = ThreeTuple Int listOfParams = listFromThreeTuple muscle = fun
This fires the following error in GHC (I do add the TypeFamilies LANGUAGE pragma): """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple Int' NB: `Parameters' is a type function """
If I use a similar data type without type parameters:
data ThreeTuple = T3 Int Int Int
And modify the above snippet accordingly, I get the same thing: """ Couldn't match expected type `Parameters Int' against inferred type `ThreeTuple' NB: `Parameters' is a type function In the expression: listFromThreeTuple In the definition of `listOfParams': """
Whatever alternative I try (and I have gone far along the trial-error path) inevitably yields those errors for both lines implementing 'listOfParams' and 'muscle'.
Could somebody help me understand what's going on? I'm really lost at this point.
PS: My first attempt at the class used 'type' to define the associated type. I had to switch to 'data' due to problems regarding the chosen type not being _injective_. GHC error messages and the paper "Fun with type functions" helped on that.
The error is with your data instance declaration:
data Parameters Int = ThreeTuple Int
You're treating a data declaration as if it were a type declaration - a data declaration needs to have a constructor, something like:
data Paramter Int = ParamInt (ThreeTuple Int)
would be more likely to type check.
Then you'd have to pattern match on the constructor to deconstruct it.
Type errors aside, all of this looks really really complicated, and from what you're describing I'm not sure it needs to be.
Why not just have two functions, one which wraps around the first? Or if you want to write code in a reusable manner, ordinary higher-order functions work well:
writeToFileIfNonExistent :: FilePath -> (FilePath -> IO ()) -> IO () writeToFileIfNonExistent path action = do exists <- doesFileExist path unless exists $ action path return ()
coreFileWritingFunction :: Param1 -> Param2 -> Param3 -> FilePath -> IO () coreFileWritingFunction p1 p2 p3 path = withFile path WriteMode $ \handle -> ...
slickNewWrapper :: Param1 -> Param2 -> Param3 -> FilePath -> IO () slickNewWrapper p1 p2 p3 = writeToFileIfNonExistent $ coreFileWritingFunction p1 p2 p3
I've chosen silly names for my functions, but I hope you get the idea. Don't hesitate to respond if you have any questions.
Antoine

Jeff Greer
We are organizing a reading group for O'Reilly's - Real World HaskellWe will start with Chapter 1 on August 8, 2010 and then cover additional chapters at two week intervals.If interested: http://linuxagora.com This is an all volunteer web site - no advertising, no feesThank you,Jeff-- http://linuxagora.com
This is a great idea! Here is a link to the sub-forum for the _Real World Haskell_ reading group: Real World Haskell - Introduction - Linux Agora Forums http://www.linuxagora.com/vbforum/showthread.php?s=8c990bc26f3825f73a695273481dc42e&t=1207 I was surprised to find Japanese and Spanish translations of Justin Bailey's Haskell cheatsheet [1]. Have you considered creating a mailing list gateway for the Web forum? Most users here prefer a mailing list or newsgroup interface to that of a Web forum. Ideally, you could set up a mailing list first, and then have the mailing list mirrored on a Web site. For example, this mailing list is mirrored on Gmane at the following site: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell () http://blog.gmane.org/gmane.comp.lang.haskell.beginners -- Benjamin L. Russell [1] Bailey, Justin. "The Haskell Cheatsheet." _CODESLOWER.COM,_ n.d. Web. 31 Jul. 2010. http://cheatsheet.codeslower.com/. -- Benjamin L. Russell / DekuDekuplex at Yahoo dot com http://dekudekuplex.wordpress.com/ Translator/Interpreter / Mobile: +011 81 80-3603-6725 "Furuike ya, kawazu tobikomu mizu no oto." -- Matsuo Basho^
participants (5)
-
Antoine Latter
-
DekuDekuplex@Yahoo.com
-
Gour D.
-
Jeff Greer
-
MAN