
I'm not sure that it is possible to do that, as you need to return a result. I am no expert on this, though. My solution sidesteps that problem by putting all the magic into the 't' in 'process :: [Turtle.FilePath] -> t [Turtle.FilePath]', composing the types into a single functor. In order to supply arguments, you now have to unpack that functor again. Anton {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} module Example (main) where import qualified Turtle as Turtle import Control.Foldl import Control.Monad.IO.Class -- | Composition of unary type constructors as found in TypeCompose -- https://hackage.haskell.org/package/TypeCompose-0.9.12/ newtype (g :. f) a = Compose { (!) :: g (f a)} instance (Functor g, Functor f) => Functor (g :. f) where fmap f (Compose c) = Compose $ fmap (fmap f) c -- | This is the variadic type class used to implement 'ls' -- See https://rosettacode.org/wiki/Variadic_function#Haskell class (Functor t) => PrintAllType t where process :: [Turtle.FilePath] -> t [Turtle.FilePath] instance PrintAllType IO where process [] = do fp <- Turtle.pwd Turtle.fold (Turtle.ls fp) list process xs = do concat <$> mapM (\filePath -> Turtle.fold (Turtle.ls filePath) list) xs -- Use "a ~ FilePath" instead of simply 'FilePath' to avoid problems -- with OverloadedStrings instance (a ~ Turtle.FilePath, PrintAllType r) => PrintAllType ((->) a :. r) where process args = Compose $ \a -> process (a:args) ls :: (PrintAllType t) => t [Turtle.FilePath] ls = process [] main :: IO () main = do inThisDir <- ls print inThisDir inHomeOptDir <- ls ! "/home" ! "/opt" print inHomeOptDir On 16.07.2017 09:52, 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.