Re: [Haskell-cafe] Terminal-like Application Design

2008-10-17 Thread allan
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


Re: [Haskell-cafe] Terminal-like Application Design

2008-10-17 Thread Magnus Therning
2008/10/17 allan [EMAIL PROTECTED]:
 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.

I wanted to throw in another idea, something I didn't come up with
myself but used in omnicodec[1].  Now I don't remember where I picked
up the idea:

1. Keep all option values as members of a type T
2. Define an instance of T with default values, dT
3. When using getOpt let the type of the options be something like
[OptDescr (T - IO T)]
4. To get the final set of values fold (=) over all the list of
arguments returned from getOpt and using dT as the start value.
Something like 'effectiveT - foldl (=) dT arguments'

In a tool I recently started working on I decided not to work in IO
and instead I ended up with something like 'effectiveT = (foldl (.) id
arguments) dT'.

/M

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/omnicodec

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Terminal-like Application Design

2008-10-17 Thread Dougal Stanton
2008/10/17 Magnus Therning [EMAIL PROTECTED]:

 I wanted to throw in another idea, something I didn't come up with
 myself but used in omnicodec[1].  Now I don't remember where I picked
 up the idea:

This method is described in
http://www.haskell.org/haskellwiki/High-level_option_handling_with_GetOpt.

I have used it in the past and eventually end up with huge Config data
structures and not much separation of unrelated parts of the
computation. Of course, this is probably just me ;-)

Alternatively (and this is where I have had more success) you can take
several passes over the command arguments, using different parsers.
Each parser just ignores what it doesn't recognise:

parseArgs names = do
args - getArgs
let info = parseWith infoOptions []
let options = parseWith argOptions defaultOptArgs
let query = parseWith queryOptions defaultQuery
return (info, options, query)
 where parseWith os z = case getOpt Permute os args of
(o,_,_) - foldr id z o

Note that this method tends to ignore user error at the command line,
but I'm sure a hybrid could be constructed that was more chatty but
still quite clean at the back end.

See http://www.dougalstanton.net/code/buses/ for this code in its
wider context.

Cheers,


D

-- 
Dougal Stanton
[EMAIL PROTECTED] // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Terminal-like Application Design

2008-10-16 Thread Arnar Birgisson
Hi Jeff,

On Fri, Oct 17, 2008 at 01:29, Jeff Wheeler [EMAIL PROTECTED] wrote:
 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.

Do you mean a terminal application that runs a session, accepting
commands interactively? If so, check out Shellac [1].

[1] http://www.cs.princeton.edu/~rdockins/shellac/home/

cheers,
Arnar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Terminal-like Application Design

2008-10-16 Thread Jason Dusek
Jeff Wheeler [EMAIL PROTECTED] wrote:
 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?

  At risk of stating the obvious, you will need to us the IO
  monad...

  When you say use a monad to represent the commands, that is
  perhaps not necessary. You can represent the commands as data,
  for example:

data MyLanguage = Go | Stop | Left | Right

runMyLanguage :: MyLanguage - IO ()

  The `runMyLanguage` function serves to transform commands
  as pure data into real IO actions.

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