
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)

On 26.04 11:29, Anton Kulchitsky wrote:
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????
One solution is to have a datatype for configuration:
data Config = Config { mode :: Mode, infile :: Maybe FilePath, outfile :: Maybe FilePath } nullConfig = Config Normal "-" "-" data Mode = Normal | Version | Help
and handle options as functions from Config to Config:
Option ['i'] ["input"] (ReqArg (\x c -> c { infile = Just x }) "file") "input file name"
and then handle the parsed options like:
case conf of Config Normal (Just i) (Just o) -> ... Config Normal _ _ -> both input and output must be specified Config Help _ _ -> help message
- Einar Karttunen

On Thu, Apr 27, 2006 at 02:26:22AM +0300, Einar Karttunen wrote:
On 26.04 11:29, Anton Kulchitsky wrote:
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????
One solution is to have a datatype for configuration:
data Config = Config { mode :: Mode, infile :: Maybe FilePath, outfile :: Maybe FilePath } nullConfig = Config Normal "-" "-" data Mode = Normal | Version | Help
and handle options as functions from Config to Config:
Option ['i'] ["input"] (ReqArg (\x c -> c { infile = Just x }) "file") "input file name"
I find this approach very convenient, but I push it a bit further. Some time ago I wrote a small article about this: http://www.haskell.org/pipermail/haskell/2004-January/013412.html I was not the first one to use the approach but I felt that it should be made more popular. Perhaps I should make a wiki page from it, but I seem to never do such things and can't promise to do it this time :-/
and then handle the parsed options like:
case conf of Config Normal (Just i) (Just o) -> ... Config Normal _ _ -> both input and output must be specified Config Help _ _ -> help message
You can eliminate this pattern matching by using functions and IO-actions as fields of Config, for example:
data Config = Config { input :: IO String, -- or (Handle -> IO a) -> IO a output :: String -> IO () }
This way it is easy to read from stdin and write to stdout by default. We eliminate Version and Help modes by using IO functions as option handlers, which enables us to finish the execution in the middle of option processing.
Option ['h'] ["help"] (NoArg (\_ -> printHelp >> exitWith ExitSuccess)) "show help"
Your main function could look like this:
main = do args <- getArgs let (optsActions, rest, errors) = getOpt RequireOrder options args mapM_ (hPutStrLn stderr) errors config <- foldl (>>=) (return initialConfig) optsActions cs <- input config ... output config result
Best regards Tomasz

Tomasz Zielonka wrote:
On Thu, Apr 27, 2006 at 02:26:22AM +0300, Einar Karttunen wrote:
and handle options as functions from Config to Config:
Option ['i'] ["input"] (ReqArg (\x c -> c { infile = Just x }) "file") "input file name"
I find this approach very convenient, but I push it a bit further. Some time ago I wrote a small article about this:
http://www.haskell.org/pipermail/haskell/2004-January/013412.html
I was not the first one to use the approach but I felt that it should be made more popular. Perhaps I should make a wiki page from it, but I seem to never do such things and can't promise to do it this time :-/
You are dealing with more convenient option handling, validating and defaulting on top of Sven Pannes famous GetOpt module. Nice stuff but there is another important point: Your approach still needs a central definition of an option list (or record) in the main (user) program. But suppose you write some libraries that are used by a couple of user programs. It becomes tedious and error prone to define the same lists of options with descriptions and validating functions in all user programs just to give it to the library. Moreover the user program in general even don't know about the right validating function or option description. So it would be much better to define the options in the library and to provide this definitions to the user program somehow. I tought about this topic several times and came up with a solution that works for me but is far from being perfect. It uses existentials and a main disadvantage is the need of explicit traversing. Moreover some new boilerplate code is necessary. You can find the interface in http://liinwww.ira.uka.de/~rahn/src/Util/Option.hs Sample library definitions of options are in http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Env.hs http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Description.hs These definitions are combined in http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Auto.hs and finally used for example in the user programs http://liinwww.ira.uka.de/~rahn/src/Prog/Eval.hs http://liinwww.ira.uka.de/~rahn/src/Prog/Interesting.hs Note, that the user programs just define options that are specific for the program, e.g. both programs have options to define some search bounds without definition. As stated: Far from being perfect. Looking forward to get some new ideas! Best regards, Mirko Rahn -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

On 27.04 12:32, Mirko Rahn wrote:
So it would be much better to define the options in the library and to provide this definitions to the user program somehow. I tought about this topic several times and came up with a solution that works for me but is far from being perfect. It uses existentials and a main disadvantage is the need of explicit traversing. Moreover some new boilerplate code is necessary.
HAppS has a typeclass for this kind of thing also: http://test.happs.org/auto/apidoc/HAppS-Util-StdMain-Config.html http://test.happs.org/HAppS/src/HAppS/Util/StdMain/Config.hs and for an example instance see: http://test.happs.org/HAppS/src/HAppS/Protocols/SimpleHTTP.hs - Einar Karttunen

I wrote an option parser that infers everything about the options from the types of what you pull out of it so there is no need to specify redundant information and you can write very concise code (especially when combined with the overloaded regex module!) like for instance main = do (args,(verb,output_name)) <- getOptions ("v|verbose", "o") putStrLn $ if verb then "verbose mode" else "not verbose" case output_name of Nothing -> putStrLn "no output" Just fn -> putStrLn $ "output file is: " ++ fn will just work, infering from the type that '-v' and '-verbose' are simple flags, while '-o' takes a string argument. you can even set help messages with the (??) operator "o" ?? "output file name" and default values with the (==>) operator. "o" ==> "out.txt" it can be gotten here: http://repetae.net/john/recent/out/GetOptions.html and help is at: http://repetae.net/john/recent/src/hsdocs//GetOptions.html John -- John Meacham - ⑆repetae.net⑆john⑈

my favorite example is the featureful yet short grep, supporting quite a few non-trivial options as well as a detailed '--help' message. :) this is a great example for anyone that says strong typing clutters code :) Haskell can be much more concise as well as safer than perl given the right libraries. main = do (fs,(verb,c,e,o,q)) <- getOptions ( "v|verbose" ?? "set verbose mode" "c" ?? "count occurances", "e" ==> "." ?? "the pattern to match", "o" ?? "show just the match rather than the line"' "q" ?? "just tell whether it matches" ) when verb $ putStrLn ("reading " ++ show fs) ls <- fmap (lines . concat) $ mapM readFiles fs when q $ if any (=~ e) ls then exit 0 else exit 1 when c $ print $ sum (map (fromEnum . (=~ e)) ls) flip mapM ls $ \l -> case (l =~ e) of Nothing -> return () Just xs -> putStrLn $ if o then xs else l John -- John Meacham - ⑆repetae.net⑆john⑈

On 27/04/06, John Meacham
my favorite example is the featureful yet short grep, supporting quite a few non-trivial options as well as a detailed '--help' message. :)
Does getOptions really take an arbitrary n-tuple? Why? That seems a very odd way of doing things. The only advantage I can think of over lists is that tuples don't have to be typically homogeneous, but I would have thought that you could get your ?? and ==> operators to spit out the correct types. -- -David House, dmhouse@gmail.com, http://xmouse.ithium.net

On Fri, Apr 28, 2006 at 08:47:40AM +0100, David House wrote:
On 27/04/06, John Meacham
wrote: my favorite example is the featureful yet short grep, supporting quite a few non-trivial options as well as a detailed '--help' message. :)
Does getOptions really take an arbitrary n-tuple? Why? That seems a very odd way of doing things. The only advantage I can think of over lists is that tuples don't have to be typically homogeneous, but I would have thought that you could get your ?? and ==> operators to spit out the correct types.
Because the entire point of the module is to not only be type-safe, but to infer your intent from the type. if everything conformed to the same type, you wouldn't be able to ensure you lined up your arguments and your options properly and worse, you wouldn't be able to use the results directly as youd have to wrap them in some container. each of the return values is of a different type. So, the entire point of the module was to not use a list. unlike the other options out there. :) that is what makes it neat and enables very concise, very typesafe, code. tuples arn't particularly special, you can use HLists with the appropriate instances for instance. John -- John Meacham - ⑆repetae.net⑆john⑈

I find this approach very convenient, but I push it a bit further. Some time ago I wrote a small article about this:
http://www.haskell.org/pipermail/haskell/2004-January/013412.html
I was not the first one to use the approach but I felt that it should be made more popular. Perhaps I should make a wiki page from it, but I seem to never do such things and can't promise to do it this time :-/
Thank you so much!!! That is great! Anton Kulchitsky

Tomasz Zielonka wrote:
and handle options as functions from Config to Config:
I find this approach very convenient, but I push it a bit further. Some time ago I wrote a small article about this:
http://www.haskell.org/pipermail/haskell/2004-January/013412.html
[from there]
-- Here we thread startOptions through all supplied option actions opts <- foldl (>>=) (return startOptions) actions
So the order in actions is important and therefore the order of options on the commandline is important. But how to handle dependencies between options using this technique? I can image two solutions: 1: Every dependency 'a implies b' has to be checked in both functions, the one for a and the one for b. 2: An order for the actions has to be specified, maybe by decorating the option list with priorities. But both solutions seems to be tedious and error prone. In contrast the sum-type technique first reads all options and then post-processes the complete set. Here the order of options on the commandline has no impact on the final result. Regards, Mirko Rahn -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

On Tue, May 02, 2006 at 02:27:28PM +0200, Mirko Rahn wrote:
But how to handle dependencies between options using this technique? I can image two solutions: 1: Every dependency 'a implies b' has to be checked in both functions, the one for a and the one for b. 2: An order for the actions has to be specified, maybe by decorating the option list with priorities. 3: Handle some (not all) options in a sum-type fashion
In contrast the sum-type technique first reads all options and then post-processes the complete set. Here the order of options on the commandline has no impact on the final result.
I forgot to show that you can still use old style option handling for some options. This way you can gradually move from sum-type style to product-type style. Best regards Tomasz

Hello Anton, Wednesday, April 26, 2006, 11:29:16 PM, you wrote:
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.
you are my ideal client because we both speak Russian (but not here :) ) and both interested in large "real-world" applications :) download the http://freearc.narod.ru/FreeArc-sources.tar.gz and enjoy - it's a full of Russian comments and it's a real-world program that solves many problems that you yet foresee :) in particular, i also started with vision of my program (it's a RAR-like archiver) as a sequence of transformations: 1) first, a command line translated into the program "job" - it's actually business of GetOpt and not very differ from other language's implementations 2) second, this job plus information about files on disk is translated into the record of structure of archive being created 3) third, archive structure translated into the sequence of I/O operations but when i started to do the actual implementation, i realized that such pure functional approach is nor appropriate and at the last end i wrote the straight imperative program, just using the power of Haskell language. moreover, in this process i added to the language many imperative constructs that make imperative programming easier
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????
you can see my solution in Cmdline module - it's one of largest module in my program. i don't like the GetOpt interface (it returns a list of options what is unusable for high-speed application) so i implemented my own option-processing routines, it's just about 50 lines long (great demonstration of Haskell power!). all processed options are record in one large record that is passed around all the program. if you get accustomed to global variables, it's using in Haskell is possible but that is not the best way. you can also use implicit parameters (at least in hugs and ghc), but this again makes data dependencies somewhat non-understandable btw, i suggest you to use WinHugs for debugging program and ghc for final compilation. this makes faster development time together with faster final executable. moreover, making your program compatible with both environments is almost ensure that it will be compatible with coming Haskell standard, Haskell-prime returning back to options parsing - there is an interesting alternative to GetOpt (which is just mimics corresponding C module) - it's a PescoCmd: http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.tgz http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.pdf http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-man-2.0.pdf i also recommend you to read several other real-world Haskell program where you can steal more code and ideas: http://postmaster.cryp.to/postmaster-2005-02-14.tar.gz ftp://ftp.cse.unsw.edu.au/pub/users/dons/yi/yi-0.1.0.tar.gz darcs (darcs get --partial http://www.abridgegame.org/repos/darcs/) happs (darcs get --partial http://happs.org/HAppS) and one more interesting source of real-world approach to Haskell programming: http://www.haskell.org/haskellwiki/Hitchhikers_Guide_to_the_Haskell -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Thu, Apr 27, 2006 at 03:10:32PM +0400, Bulat Ziganshin wrote:
i don't like the GetOpt interface (it returns a list of options what is unusable for high-speed application)
This got me interested. I assume that you measured performace and it wasn't fast enough. How many command line args you had to handle? How many options? I don't know how well System.GetOpt works with many possible options. It doesn't seem to use any sophisticated algorithm for searching options, so the cost of getOpt can be proportional to N*M, where N = numer of option descriptions, M = number of program args. If this was improved, it might become usable for you. Best regards Tomasz

Hello Tomasz, Thursday, April 27, 2006, 4:45:45 PM, you wrote:
On Thu, Apr 27, 2006 at 03:10:32PM +0400, Bulat Ziganshin wrote:
i don't like the GetOpt interface (it returns a list of options what is unusable for high-speed application)
This got me interested. I assume that you measured performace and it wasn't fast enough.
no, i abandoned this without testing :) you misunderstood me, though - i mean speed of using this list. if some internal function need option "foo", it should scan the entire list to find it's value. so i (like you, i think) save the result of option parsing in the structure. and because i anyway need the way to extract options from list and store them into structure - i implemented my own set of functions to recognize options too. ultimately, the main problem of all options-parsing stuff i ever seen, is requirement to repeat option definition many times. if i have, say, 40 options, then i need to maintain 3 to 5 program fragments that deal with each option. something like this: data Options = Options { r :: Bool, x :: Int .... } options = { "r", "description" .... } main = do list <- getOpts options cmdline let options = Options { r = findBoolOption list "r", x = findIntOption list "x", .... } each change in options list mean that i should find all these places and correct them. PescoCmd may be does something against this problem, i don't remember why i was pleased by this library as far as i see, solving of this problem is impossible in Haskell itself, we need some form of preprocessing, probably with TH. this should allow us to write something like this: $(optionProcessor [("r", "description", `Bool, .....) ,("x", ..... ... ] ) what will generate all the stuff above as i already said, you can find module Cmdline in my program, that is not ultimate solution, but at least it somewhat simplified my work -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Tomasz, [snip] ultimately, the main problem of all options-parsing stuff i ever seen, is requirement to repeat option definition many times. if i have, say, 40 options, then i need to maintain 3 to 5 program fragments that deal with each option. something like this:
data Options = Options { r :: Bool, x :: Int .... }
options = { "r", "description" .... }
main = do list <- getOpts options cmdline let options = Options { r = findBoolOption list "r", x = findIntOption list "x", .... }
If it is not necessary to specify a specific command letter for each option, then perhaps options could be composed by something like (following code untested): class OptionClass a where setOption :: a -> String -> IO () getOptionDescription :: a -> String -> String data Option = forall a. OptionClass a => Option a instance OptionClass Option where setOption (Option a) = setOption a getOptionDescription (Option a ) opt = getOptionDescription a opt data ComposedOption = ComposedOption _ [Option] instance OptionClass ComposedOption where setOption (ComposedOption _ os) (c:cs) = setOption (os !! (fromEnum c - fromEnum 'a')) cs getOptionDescription (ComposedOption description os) (c:cs)= description ++ "." ++ getOptionDescription (os !! (fromEnum x - fromEnum 'a')) cs Then each element in a module that needs an option makes its own instance of the existential eg data ModOption1 = ModOption1 data ModOption2 = ModOption2 instance OptionClass ModOption1 where setOption ModOption1 s = case s of [] -> do -- set default value s -> do -- parse s and set accordingly getOptionDescription ModOption1 optvalue = -- description of this option, possibly clarified to the specific example of optvalue -- "would read from the file 'foo.txt'" if optvalue == " foo.txt" moduleOptions = ComposedOption "My module" [ModOption1, ModOption2] Then in main, do: allOptions = ComposedOption "Name of program" [Module1.moduleOptions, Module2.moduleOptions, ...] A disadvantage would be that the options would involve multiple letters in general eg -aaaab -aba etc when there is a lot of nesting, but an advantage is that it allows libraries requiring options and code using such libraries to be written in a modular way. Best regards, Brian.

Brian Hulley wrote:
moduleOptions = ComposedOption "My module" [ModOption1, ModOption2] moduleOptions = Option $ ComposedOption "My module" [ModOption1, ModOption2]
allOptions = ComposedOption "Name of program" [Module1.moduleOptions,
allOptions = Option $ ComposedOption "Name of program" [Module1.moduleOptions, Thinking more about it, it would be better to change the type of ComposedOption to: data ComposedOption = ComposedOption [(String, Option)] since an option by itself can't tell what it's name should be because any name specified might conflict with other option names, but the parent can assign different names safely. Also, many different schemes for composing options could be devised, so that some subsets of options would be indexed by a number instead of a letter etc. Regards, Brian. PS: this is definitely a good case for the use of augmented IO since the fact that a particular module needs to store option state should be completely invisible to the rest of the program...

Hi Bulat, thank you very much for such a detailed reply!
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.
you are my ideal client because we both speak Russian (but not here :) )
Da! :) Spasibo.
and both interested in large "real-world" applications :) download the http://freearc.narod.ru/FreeArc-sources.tar.gz and enjoy - it's a full of Russian comments and it's a real-world program that solves many problems that you yet foresee :)
in particular, i also started with vision of my program (it's a RAR-like archiver) as a sequence of transformations:
1) first, a command line translated into the program "job" - it's actually business of GetOpt and not very differ from other language's implementations
2) second, this job plus information about files on disk is translated into the record of structure of archive being created
3) third, archive structure translated into the sequence of I/O operations
but when i started to do the actual implementation, i realized that such pure functional approach is nor appropriate and at the last end i wrote the straight imperative program, just using the power of Haskell language. moreover, in this process i added to the language many imperative constructs that make imperative programming easier
I really trying to avoid imperative approach. I do have a terribly big experience in imperative programming (by the way, you might know one application that I made about 3 years ago. It is Uni-K Sensei for windows). Now, I am breaking my previous habits just to think wider and more effective.
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????
you can see my solution in Cmdline module - it's one of largest module in my program. i don't like the GetOpt interface (it returns a list of options what is unusable for high-speed application) so i implemented
Well, I do not care too much about high-speed. My main goal is to write a prototype of the language that I am creating. It is a kind of Domain-Specific language. I decided to start from a simple thing. A converter of pgn files with chess notation to javascript to visualize it. Just to have some practice.
my own option-processing routines, it's just about 50 lines long (great demonstration of Haskell power!). all processed options are record in one large record that is passed around all the program. if you get accustomed to global variables, it's using in Haskell is possible but that is not the best way. you can also use implicit parameters (at least in hugs and ghc), but this again makes data dependencies somewhat non-understandable
Thank you very much. I will see this approach as well. I am still pretty concern of using records instead of lists.
btw, i suggest you to use WinHugs for debugging program and ghc for final compilation. this makes faster development time together with faster final executable. moreover, making your program compatible with both environments is almost ensure that it will be compatible with coming Haskell standard, Haskell-prime
Thanks again. I do not use Windows any more. I use Mac or different Unices. I do use ghc everywhere I work with Haskell. For debugging I use ghci. Well, and everything within GNU Emacs.
returning back to options parsing - there is an interesting alternative to GetOpt (which is just mimics corresponding C module) - it's a PescoCmd:
http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.tgz http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.pdf http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-man-2.0.pdf
Thanks! Very interesting
i also recommend you to read several other real-world Haskell program where you can steal more code and ideas:
http://postmaster.cryp.to/postmaster-2005-02-14.tar.gz ftp://ftp.cse.unsw.edu.au/pub/users/dons/yi/yi-0.1.0.tar.gz darcs (darcs get --partial http://www.abridgegame.org/repos/darcs/) happs (darcs get --partial http://happs.org/HAppS)
Darcs was a little too complicated for me. Thank you for other links.
and one more interesting source of real-world approach to Haskell programming:
http://www.haskell.org/haskellwiki/Hitchhikers_Guide_to_the_Haskell
Thank you very much, Bulat. Now I see why people say that haskell-cafe is the best mail-list! :) Anton Kulchitsky

Hello Anton, Friday, April 28, 2006, 12:54:44 AM, you wrote:
I really trying to avoid imperative approach. I do have a terribly big experience in imperative programming (by the way, you might know one application that I made about 3 years ago. It is Uni-K Sensei for
no. but may be you are heard about ARJZ? :)
windows). Now, I am breaking my previous habits just to think wider and more effective.
yes, yes. but you should know that haskell still are perfect imperative language and when pure functional approach will be not enough for your program, you can combine both ways
Well, I do not care too much about high-speed. My main goal is to write a prototype of the language that I am creating. It is a kind of Domain-Specific language. I decided to start from a simple thing. A converter of pgn files with chess notation to javascript to visualize it. Just to have some practice.
if you don't care about speed and write text-conversion program, pure functional approach may be enough. just use results of GetOpt as argument to all the routines that depends on any program options
my own option-processing routines, it's just about 50 lines long (great demonstration of Haskell power!). all processed options are record in one large record that is passed around all the program. if you get accustomed to global variables, it's using in Haskell is possible but that is not the best way. you can also use implicit parameters (at least in hugs and ghc), but this again makes data dependencies somewhat non-understandable
Thank you very much. I will see this approach as well. I am still pretty concern of using records instead of lists.
what you mean?
btw, i suggest you to use WinHugs for debugging program and ghc for final compilation. this makes faster development time together with faster final executable. moreover, making your program compatible with both environments is almost ensure that it will be compatible with coming Haskell standard, Haskell-prime
Thanks again. I do not use Windows any more. I use Mac or different Unices. I do use ghc everywhere I work with Haskell. For debugging I use ghci. Well, and everything within GNU Emacs.
you can use hugs, it works with many environments. according to my tests, it loads programs 10 times faster than ghci -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (8)
-
Anton Kulchitsky
-
Brian Hulley
-
Bulat Ziganshin
-
David House
-
Einar Karttunen
-
John Meacham
-
Mirko Rahn
-
Tomasz Zielonka