Dynamic choice of "reverse" implementation

Fellow Haskellers, I wanted to experiment a bit with lists and sequences (as in Data.List and Data.Sequence), and I got stuck. I wanted to dynamically select processing function depending on cmdline argument:
main = do args <- getArgs let reversor = case args of ["sequence"] -> reverseList ["list"] -> reverseSeq _ -> error "bad args" input <- getContents let output = reversor $ lines $ input mapM_ putStrLn output
In my oppinion reversor would have type
reversor :: (Foldable f) => [a] -> f b
but I couldn't get this to work. I've tried typeclass approach:
class (Foldable f) => Reversor f where reverse' :: [a] -> f a
instance Reversor ([]) where reverse' = Data.List.reverse
instance Reversor ViewR where reverse' = viewr . foldr (<|) empty
reverseList = reverse' :: (???) reverseSeq = reverse' :: (???)
but now in order to differentiate between "reverse'" functions I'd have to provide different type annotations, and then "reversor" won't typecheck... Similar problem surfaced with this try:
data Proc = SP | LP reverseList = reverse' LP reverseSeq = reverse' SP
reverse' :: (Foldable f) => Proc -> [a] -> f a reverse' LP = Data.List.reverse reverse' SP = viewr . foldr (<|) empty
So now I'm looking for some suggestions how should I approach the problem... Regards, -- Krzysztof Kościuszkiewicz Skype: dr.vee, Gadu: 111851, Jabber: kokr@jabberpl.org Mobile IRL: +353851383329, Mobile PL: +48783303040 "Simplicity is the ultimate sophistication" -- Leonardo da Vinci

Krzysztof Kościuszkiewicz wrote:
Fellow Haskellers,
I wanted to experiment a bit with lists and sequences (as in Data.List and Data.Sequence), and I got stuck. I wanted to dynamically select processing function depending on cmdline argument:
main = do args <- getArgs let reversor = case args of ["sequence"] -> reverseList ["list"] -> reverseSeq _ -> error "bad args" input <- getContents let output = reversor $ lines $ input mapM_ putStrLn output
In my oppinion reversor would have type
reversor :: (Foldable f) => [a] -> f b
No, this is the wrong type. To find the correct type, if you look at the type of the input argument in your code it will be the result of (lines), so from ghci: Prelude> :t lines lines :: String -> [String] Prelude> Therefore (reverseor) has type [String] -> ??? Now for the output type, you are using (output) as an input to (mapM_ putStrLn). (mapM_) takes a list and uses its argument to do something to each element of the list. So, since the input to (putStrLn) is (String), the input to (mapM_ putStrLn) is ([String]). Therefore reversor :: [String] -> [String] So reverseList is just Data.List.reverse as you've got it (though presumably you meant to write ["list"] -> reverseList and not reverseSeq). For using Data.Sequence to implement reversor, all you need to do is first convert [String] to Seq String, reverse the sequence, then convert back from Seq String to [String]. Hope this helps, Brian.
but I couldn't get this to work. I've tried typeclass approach:
class (Foldable f) => Reversor f where reverse' :: [a] -> f a
instance Reversor ([]) where reverse' = Data.List.reverse
instance Reversor ViewR where reverse' = viewr . foldr (<|) empty
reverseList = reverse' :: (???) reverseSeq = reverse' :: (???)
but now in order to differentiate between "reverse'" functions I'd have to provide different type annotations, and then "reversor" won't typecheck...
Similar problem surfaced with this try:
data Proc = SP | LP reverseList = reverse' LP reverseSeq = reverse' SP
reverse' :: (Foldable f) => Proc -> [a] -> f a reverse' LP = Data.List.reverse reverse' SP = viewr . foldr (<|) empty
So now I'm looking for some suggestions how should I approach the problem...
Regards,

On Fri, Sep 28, 2007 at 04:38:35PM +0100, Brian Hulley wrote:
In my oppinion reversor would have type
reversor :: (Foldable f) => [a] -> f b
No, this is the wrong type. To find the correct type, if you look at the type of the input argument in your code it will be the result of (lines), so from ghci:
Prelude> :t lines lines :: String -> [String] Prelude>
Therefore (reverseor) has type [String] -> ??? Now for the output type, you are using (output) as an input to (mapM_ putStrLn). (mapM_) takes a list and uses its argument to do something to each element of the list.
True. I forgot to mention imports in my code:
import Prelude hiding (foldr, foldr1, reverse, mapM_) import System.Environment import Data.List hiding (foldr, foldr1) import Data.Foldable import Data.Traversable import Data.Sequence
So the type of mapM_ used in the code is (Foldable t, Monad m) => (a -> m b) -> t a -> m () I'd like to keep the generic Foldable t there when "m" is specialized to IO. I thought this would allow type of "reversor" to be specialized to (Foldable f) => [String] -> f String
For using Data.Sequence to implement reversor, all you need to do is first convert [String] to Seq String, reverse the sequence, then convert back from Seq String to [String].
Yes, probably that's how it works under the hood, but the reason I mentioned Foldable is that I'd like to avoid [a] -> something -> [a], but keep the type of output value from "reversor" abstract... For no particular reason, just playing with this idea :) Regards, -- Krzysztof Kościuszkiewicz Skype: dr.vee, Gadu: 111851, Jabber: kokr@jabberpl.org Mobile IRL: +353851383329, Mobile PL: +48783303040 "Simplicity is the ultimate sophistication" -- Leonardo da Vinci

Krzysztof Kościuszkiewicz wrote:
So the type of mapM_ used in the code is (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
I'd like to keep the generic Foldable t there when "m" is specialized to IO. I thought this would allow type of "reversor" to be specialized to (Foldable f) => [String] -> f String
... I'd like to avoid [a] -> something -> [a]
Yes this type should be fine. To implement reversor though you'd still need to first convert from the concrete list to whatever foldable you're using, before reversing the foldable, or implement something more general eg: reversor :: (Foldable f, Foldable g) :: f a -> g a Of course with lazy evaluation + compiler optimizations the lists in [a] -> something -> [a] should be erased at compile time... ;-) Regards, Brian.

Brian Hulley wrote:
Krzysztof Kościuszkiewicz wrote:
So the type of mapM_ used in the code is (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
I'd like to keep the generic Foldable t there when "m" is specialized to IO. I thought this would allow type of "reversor" to be specialized to (Foldable f) => [String] -> f String ... I'd like to avoid [a] -> something -> [a]
Yes this type should be fine.
I should have said though that in your code, because one arm of the case construct returns Data.List.reverse, the type of reversor is fixed to [a] -> [a]. The other arm of the case construct could make use of a more general function eg reverseFoldable :: (Foldable f, Foldable g) => f a -> g a but it would only be used at f == [], g == []. So in terms of the command line test harness, I think the only way is to explicitly choose the foldable you want to try out eg by using (Foldable.toList . Seq.reverse . Seq.fromList) etc. An alternative might be to just write some different implementations of reverse functions in a module then load the module into ghci to test them out interactively so their types don't get unified with each other. Brian.

On Fri, Sep 28, 2007 at 05:54:23PM +0100, Brian Hulley wrote:
Yes this type should be fine. To implement reversor though you'd still need to first convert from the concrete list to whatever foldable you're using, before reversing the foldable, or implement something more general eg:
reversor :: (Foldable f, Foldable g) :: f a -> g a
One cannot define such a function, as Foldable provides no way to build things. However one can define reversor :: Traversable f => f a -> f a which returns something of the same shape, but with the contents reversed.

On Friday 28 September 2007, David Benbennick wrote:
On 9/28/07, Ross Paterson
wrote: However one can define
reversor :: Traversable f => f a -> f a
which returns something of the same shape, but with the contents reversed.
How? Is it possible to define a version of foldl for Traversable?
At the very least, you can do this: {-# LANGUAGE FlexibleContexts #-} import Prelude hiding (mapM) import Control.Monad hiding (mapM) import Control.Monad.State hiding (mapM) import Data.Foldable (toList) import Data.Traversable (mapM, Traversable(..)) reversor :: Traversable t => t a -> t a reversor t = evalState (mapM (const pick) t) (reverse $ toList t) pick :: MonadState [a] m => m a pick = do (h:t) <- get ; put t ; return h There may be something nicer out there, though.

Here's the problem:
In my oppinion reversor would have type
reversor :: (Foldable f) => [a] -> f a
The type of reversor you state is equivalent to forall f a. (Foldable f) => [a] -> f a but reverseList has the type forall a. [a] -> [a] and reverseSeq has the type forall a. [a] -> Seq a What you mean instead is forall a. exists f. (Foldable f) => [a] -> f a but that type isn't directly supported in Haskell. Instead, you need to wrap it in an existential constructor:
{-# LANGUAGE ExistentialQuantification #-} module Main where import Prelude hiding (foldr, foldr1, reverse, mapM_) import System.Environment import Data.List hiding (foldr, foldr1) import Data.Foldable import Data.Traversable import Data.Sequence
data Rev a = forall f. Foldable f => Rev ([a] -> f a)
in this case, Rev :: forall f a. Foldable f => ([a] -> f a) -> Rev a Once you have this, the rest of the implementation is pretty simple:
mkReversor :: [String] -> Rev a mkReversor ["sequence"] = Rev reverseSeq mkReversor ["list"] = Rev reverseList mkReversor _ = error "bad args"
reverseList :: [a] -> [a] reverseList = Data.List.reverse
reverseSeq :: [a] -> Seq a reverseSeq = foldr (<|) empty
main = do args <- getArgs (Rev reversor) <- return (mkReversor args) input <- getContents let output = reversor $ lines $ input mapM_ putStrLn output
This line is particularily interesting: (Rev reversor) <- return (mkReversor args) Replacing it with the more obvious let reversor = mkReversor args causes the best error message in the history of compilers: My brain just exploded. I can't handle pattern bindings for existentially-quantified constructors. The reason why the "<- return" construct works is because it desugars differently (and more strictly): return (mkReversor args) >>= \r -> case r of (Rev reversor) -> do (rest of do block) _ -> fail "Pattern match failure" which binds the type of reversor in a case statement; Simon Peyton-Jones says it's not obvious how to write a typing rule for let-bindings. -- ryan
participants (6)
-
Brian Hulley
-
Dan Doel
-
David Benbennick
-
Krzysztof Kościuszkiewicz
-
Ross Paterson
-
Ryan Ingram