Hi Jeff

It sounds like maybe you just want an application that works a bit like 'cabal'.
So with cabal the first argument is taken as the 'command' and then the rest 
are based on that:

cabal build --some other --options --which may --or --may --not have --arguments

Yi has a simple template for a script which should get you started, please find 
it attached.

So here instead of processOptions, you might want, processCommand

processCommand :: [ String ] -> IO ()
processCommand ("build" : args) = processBuildCommand args
processCommand ("play" : args)  = processPlayCommand args
processCommand []               = putStrLn "You must supply a command"
processCommand _                = putStrLn "Sorry I don't understand your 
command" --Probably out put help here as well

processBuildCommand :: [ String ] -> IO ()
processBuildCommand = similar to the processOptions except now you are sure you 
are in a 'build' command

you *might* even have a separate set of option descreptions for each command.

hth
allan




Jeff Wheeler wrote:
> Hi,
> 
> I'm a slight Haskell newbie, but I'm trying to write a terminal-like
> application that accepts simple commands with optional arguments, and
> can then execute them. Most of these commands will need IO, as later I
> will want to communicate over USB for most of them.
> 
> I was hoping, though, that I could get some comments on the initial
> architecture I've been playing with [1].
> 
> I suspect I should be using some sort of monad to represent the
> commands, but I don't fully understand monads, and am not sure how it
> would apply in this context.
> 
> Should I be using a monad here, and if so, how?
> 
> Thanks in advance,
> Jeff Wheeler
> 
> [1] http://media.nokrev.com/junk/cli/
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


-- 
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

{-
-}
module Main
  ( main )
where

{- Standard Library Modules Imported -}
import System.Console.GetOpt
  ( getOpt
  , usageInfo
  , ArgOrder    ( .. )
  , OptDescr    ( .. )
  , ArgDescr    ( .. )
  )
import System.Environment
  ( getArgs
  , getProgName
  )
{- External Library Modules Imported -}
{- Local Modules Imported -}
{- End of Imports -}

data CliFlag =
    CliHelp
  | CliVersion
  deriving Eq


options :: [ OptDescr CliFlag ]
options =
  [ Option   "h"     [ "help" ]
    (NoArg CliHelp)
    "Print the help message to standard out and then exit"

  , Option   "v"     [ "version" ]
    (NoArg CliVersion)
    "Print out the version of this program"
  ]

helpMessage :: String -> String
helpMessage progName =
  usageInfo progName options

versionMessage :: String -> String
versionMessage progName = 
  progName ++ ": This is version 0.001"

-- | The main exported function
main :: IO ()
main = getArgs >>= processOptions

processOptions :: [ String ] -> IO ()
processOptions cliArgs =
  case getOpt Permute  options cliArgs of
    (flags, args, [])       -> 
      processArgs flags args
    (_flags, _args, errors) -> 
      do progName <- getProgName
         ioError $ userError (concat errors ++ helpMessage progName)

-- We assume all of the arguments are files to process
processArgs :: [ CliFlag ] -> [ String ] -> IO ()
processArgs flags files
  | elem CliHelp flags    = getProgName >>= (putStrLn . helpMessage)
  | elem CliVersion flags = getProgName >>= (putStrLn . versionMessage)
  | otherwise             = mapM_ processFile files

-- Our processing of a file is to simply count the words
-- in the file and output the number as a line.
processFile :: FilePath -> IO ()
processFile file =
  do contents <- readFile file
     putStrLn (show $ length $ words contents)

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to