> I'm not happy with any of these options. Why are you unhappy with the ImplicitParams option?
It's pretty much like resorting to a newtype, as it's been suggested before. 2012/6/27 Tillmann Rendel <ren...@informatik.uni-marburg.de> > Hi Rico, > > Rico Moorman wrote: > >> data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer) >>> >>> amount:: Tree -> Integer >>> amount (Leaf x) = x >>> amount (Branch t1 t2) = amountt1 + amountt2 >>> >>> [...] additional requirement: "If the command-line flag --multiply is >>> set, >>> >>> the function amount computes the product instead of the sum." >>> >>> How would you implement this requirement in Haskell without changing the >>> line "amount (Leaf x) = x"? >>> >> > The (for me at least) most obvious way to do this would be, to make the >> operation to be applied to determine the amount (+ or *) an explicit >> parameter in the function's definition. >> >> >> data Tree a = Leaf a >> | Branch (Tree a) (Tree a) >> amount :: (a -> a -> a) -> Tree a -> a >> amount fun (Leaf x) = x >> amount fun (Branch t1 t2) = amount fun t1 `fun` amount fun t2 >> > > I agree: This is the most obvious way, and also a very good way. I would > probably do it like this. > > Which drawbacks do you see besides increased verbosity? >> > > Well, you did change the equation "amount (Leaf x) = x" to "amount fun > (Leaf x) = x". In a larger example, this means that you need to change many > lines of many functions, just to get the the value of fun from the point > where it is known to the point where you need it. > > [...] I am wondering which ways of doing this in Haskell you mean. >> > > I thought of the following three options, but see also Nathan Howells > email for another alternative (that is related to my option (1) below): > > > (1) Implicit parameters: > > {-# LANGUAGE ImplicitParams #-} > data Tree = Leaf Integer | Branch Tree Tree > > amount :: (?fun :: Integer -> Integer -> Integer) => Tree -> Integer > > amount (Leaf x) = x > amount (Branch t1 t2) = ?fun (amount t1) (amount t2) > > > (2) Lexical Scoping: > > data Tree = Leaf Integer | Branch Tree Tree > > amount :: (Integer -> Integer -> Integer) -> Tree -> Integer > amount fun = amount where { > > amount (Leaf x) = x > ; amount (Branch t1 t2) = fun (amount t1) (amount t2) } > > > (3) UnsafePerformIO: > > import System.IO.Unsafe (unsafePerformIO) > > data Tree = Leaf Integer | Branch Tree Tree > > > amount :: Tree -> Integer > amount (Leaf x) = x > amount (Branch t1 t2) = fun (amount t1) (amount t2) > where fun = unsafePerformIO ... > > > I'm not happy with any of these options. Personally, I would probably go > ahead and transform the whole program just to get the value of fun to where > it is needed. Nevertheless, having actually done this before, I understand > why Martin Odersky doesn't like doing it :) > > > Tillmann > > ______________________________**_________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe> >
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe