
Hi all, I just started to study Haskell and it is my almost first big experience with functional languages (except Emacs Lisp and Python). I enjoyed all small exercises and started a bigger business writing a general utility. However, I have a problem from the beginning. The utility get some file and convert it to another format. It is a kind of small compiler. It also accepts many parameters and behaves depending on them. The problem is how to do this neat! How should I write my program to accept and neatly work with options???? Please, could you suggest an example of code how to do this properly in Haskell. No book or tutorial discuss this topic. It is really sad because the problem is very unclear. Indeed, what I do in C. I make a struct settings and set its fields. Then, the program uses this parameters easily. However, what can I do in Haskell? I imagine the program as a composite function that take some input and produce the output. I decided that now I should consider my program options as an additional variable(s) of the input. Well, it is still hard to implement. Below is an example of what I did first. However, it is just not enough and looks ugly for me. Please, HELP!!!: -------------------------CODE IS BELOW------------------------- module Main where -- std import System.IO import System.Console.GetOpt import System.Environment ( getArgs ) import System.Exit import Char -- data import Data.Maybe ( fromMaybe ) -- local -- main program: options, maybe in file >> out file main :: IO () main = do -- program info genInfo -- options processing args <- getArgs case check_filter args of (WrongOpts,strLst) -> usage ("Error: Wrong option list\n" ++ (concat strLst)) >> exitWith (ExitFailure 1) (ForHelp,strLst) -> usage [] >> exitWith ExitSuccess (ForVersion,strLst) -> version >> exitWith ExitSuccess --strLst contains 3 strings: input file name, output, and parameters (OK,strLst) -> do inputstr <- readFile infile --get the content writeFile outfile (pgnjs inputstr params) --write the result exitWith ExitSuccess --exit where infile = (strLst !! 0) outfile = (strLst !! 1) params = (strLst !! 2) --(_,_) -> version >> exitWith (ExitFailure (-1)) ---------------- OPTIONS DESCRIPTION ---------------- -- OptionFlag is data OptionFlag = Version | Help | Output String | Input String deriving (Show, Eq) -- description of all options options :: [OptDescr OptionFlag] options = [ Option ['h', '?'] ["help"] (NoArg Help) ("show this help"), Option ['V'] ["version"] (NoArg Version) ("show version number"), Option ['i'] ["input"] (ReqArg Input "file") ("input file name"), Option ['o'] ["output"] (ReqArg Output "file") ("output file name") ] ------------------------------------------------------ -- this data describes the result of program work data ErrKey = OK | ForHelp | ForVersion | WrongOpts deriving (Show, Eq) ----------------------------------------------------------------------- -- input is a string of options and output is the result of the -- program. Actually, this is only a filter which filter all -- exceptional situation in option lists and then call a real function -- if list is good check_filter :: [String] -> ( ErrKey, [String] ) check_filter args = case (getOpt Permute options args) of (os, [], []) -> if (elem Help os) then (ForHelp,[]) else if (elem Version os) then (ForVersion, []) else if (not ((elem "-i" args) && (elem "-o" args)) ) then (WrongOpts, ["both -i and -o must be specified\n"]) -- we filtered now all exceptional situation else (OK, ["in.tmp","out.tmp",[]]) (os, fs, ers) -> (WrongOpts, []) -------------- OPTIONS EXCEPTIONAL FUNCTIONS ----------------- -- Version info version :: IO () version = putStrLn $ "Version 0.1.1a of October-November 2005" -- Usage short info: Output error line and usage usage :: String -> IO () usage errLine = putStr $ errLine ++ (usageInfo "Usage: shipgnjs [option...]" options) -- General info string genInfo :: IO () genInfo = putStrLn "shipgnjs (c) 2005 Anton Kulchitsky" {- This is the main function that operates on correct string: input: the first element is input pgn, the second line are parameters the output is html text for the result file -} pgnjs :: String -> String -> String pgnjs pgnstr params = map toUpper pgnstr ---- Thank you in advance, Anton Kulchitsky (a.k.a. atoku)