[Haskell-cafe] Dynamic choice of "reverse" implementation

Brian Hulley brianh at metamilk.com
Fri Sep 28 11:38:35 EDT 2007


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,
>   


More information about the Haskell-Cafe mailing list