[Haskell-cafe] Wrapping Turtle ls function to work with 0 or 1 arguments (polyvariadic)

Li-yao Xia lysxia at gmail.com
Sun Jul 16 16:33:27 UTC 2017


Try this instance instead.

instance (a ~ [Turtle.FilePath]) => PrintAllType (IO a) where

When you try to use `ls` at some type `IO a`, instance resolution won't instantiate `a`, and thus it will not match `IO [FilePath]`.
However, here, it will match `IO a`, and after having picked that instance, it gets to unify `a ~ [FilePath]`.

Li-yao



On 07/16/2017 03:52 AM, Cody Goodman wrote:
> I'm trying to get ls to work in ghci like it does in bash using variadiac
> arguments in Haskell. I'm stuck at the moment so I thought I'd send this to
> #haskell-cafe for some help. I'm not quite sure how to proceed.
>
> See the main function for what I want the end result to look like. Here is
> the code:
>
>
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE OverloadedStrings #-}
> -- | An example module.
> module Example (main) where
>
> import qualified Turtle as Turtle
> import Control.Foldl
> import Control.Monad.IO.Class
>
> lsDirEx :: MonadIO io => io [Turtle.FilePath]
> lsDirEx = do
>    Turtle.fold (Turtle.ls "/home") list
>
> class PrintAllType t where -- use PrintAllType from
> https://rosettacode.org/wiki/Variadic_function#Haskell
>      process :: [Turtle.FilePath] -> t
>
> -- instance MonadIO io => PrintAllType (io [Turtle.FilePath]) where
> instance PrintAllType (IO [Turtle.FilePath]) where
>    process [] = do -- ls received no args print current directory
>      Turtle.pwd >>= \fp -> Turtle.fold (Turtle.ls fp) list
>    process (filePath:[]) = do -- ls recieved one filePath
>      liftIO $ Turtle.fold (Turtle.ls filePath) list
>    process _ = error "multiple arguments not currently supported"
>
> -- instance (Show a, PrintAllType r) => PrintAllType (a -> r) where
> --     process args = \a -> process (args ++ [fmt a])
> --       where fmt thing = _ $ Turtle.format Turtle.w thing
>
> ls :: (PrintAllType t) => t
> ls = process []
>
> -- | An example function.
> main :: IO ()
> main = do
>    ls -- lists current directory
>    ls ("/home" :: String) -- lists /home directory
>
>
>
> Thanks,
>
> Cody
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



More information about the Haskell-Cafe mailing list