Translating perl -> haskell, string "fill ins" with an error on invalid input seems awfully complex. Is there a way to simplify?

I was translating some perl code to haskell as a learning exercise and wound up with the following. (below) Simple code that accepts some string arguments, and prints a string -- so, of type String -> String -> String -> String -> IO (). I like to be concise, but I get the feeling something went awry. What seems to be costing me the most is checking whether the various arguments are legitimate, and printing a helpful error message if not. I was able to achieve this by using Maybe and error on failed pattern match, but as said, seems kind of overly complicated. Is there a simpler way to do the following, eg for function gen_gnuplot_financial_script :: String -> String -> String -> String -> IO () ? By the way this is being used in http://code.google.com/p/gnuplotwebinterface/ ************** module Common where gnuplot_png_settings = "set terminal png transparent nocrop enhanced size 600,400\n" ++ "set pm3d implicit at s" gnuplot_math_settings = gnuplot_png_settings ++ "\n" ++ "set border 4095 \n\ \ set xlabel \"x\" \n\ \ set ylabel \"y\"" gnuplot_timeseries_settings = gnuplot_png_settings ++ "\n" ++ "set xdata time # The x axis data is time \n" ++ "set timefmt \"%d-%b-%y\" # The dates in the file look like 10-Jun-04 \n" ++ "set format x \"%b %d\" #On the x-axis, we want tics like Jun 10" gen_gnuplot_math_script :: String -> String -> IO () gen_gnuplot_math_script style function = let maybePlotCmd = lookup style style_to_plotcmd style_to_plotcmd = [("math-2d","plot"),("math-3d","splot")] in case maybePlotCmd of Just plotcmd -> putStrLn $ gnuplot_math_settings ++ "\n" ++ plotcmd ++ " " ++ function _ -> error $ "bad style: " ++ style gen_gnuplot_financial_script :: String -> String -> String -> String -> IO () gen_gnuplot_financial_script company displaymode startDate endDate = let maybeCompanyFile = lookup company company_to_companyfile maybeModeString = lookup displaymode displaymode_to_modestring maybeTitleEnd = lookup displaymode displaymode_to_titleend company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")] displaymode_to_modestring = [("points", "using 1:2 with linespoints"), ("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")] displaymode_to_titleend = [("points","daily prices"),("candles","opening prices")] in case ( maybeCompanyFile, maybeModeString, maybeTitleEnd ) of ( Just companyfile, Just modestring, Just titleEnd) -> putStrLn $ gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyfile ++ "'" ++ modestring ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\"" _ -> error $ "bad lookup. " ++ company ++ " -> company file: " ++ ( show maybeCompanyFile ) ++ "\n" ++ " " ++ displaymode ++ " -> displaymode: " ++ ( show maybeModeString ) ++ "\n" ++ " " ++ displaymode ++ " -> titleEnd: " ++ ( show maybeTitleEnd)

I believe there is a library which lets you do do perl style REGEX matching
maybe you should check that out
On 4/12/07, Thomas Hartman
I was translating some perl code to haskell as a learning exercise and wound up with the following. (below) Simple code that accepts some string arguments, and prints a string -- so, of type String -> String -> String -> String -> IO ().
I like to be concise, but I get the feeling something went awry. What seems to be costing me the most is checking whether the various arguments are legitimate, and printing a helpful error message if not.
I was able to achieve this by using Maybe and error on failed pattern match, but as said, seems kind of overly complicated.
Is there a simpler way to do the following, eg for function
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO ()
?
By the way this is being used in
http://code.google.com/p/gnuplotwebinterface/
**************
module Common where
gnuplot_png_settings = "set terminal png transparent nocrop enhanced size 600,400\n" ++ "set pm3d implicit at s"
gnuplot_math_settings = gnuplot_png_settings ++ "\n" ++ "set border 4095 \n\ \ set xlabel \"x\" \n\ \ set ylabel \"y\""
gnuplot_timeseries_settings = gnuplot_png_settings ++ "\n" ++ "set xdata time # The x axis data is time \n" ++ "set timefmt \"%d-%b-%y\" # The dates in the file look like 10-Jun-04 \n" ++ "set format x \"%b %d\" #On the x-axis, we want tics like Jun 10"
gen_gnuplot_math_script :: String -> String -> IO () gen_gnuplot_math_script style function = let maybePlotCmd = lookup style style_to_plotcmd style_to_plotcmd = [("math-2d","plot"),("math-3d","splot")] in case maybePlotCmd of Just plotcmd -> putStrLn $ gnuplot_math_settings ++ "\n" ++ plotcmd ++ " " ++ function _ -> error $ "bad style: " ++ style
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO () gen_gnuplot_financial_script company displaymode startDate endDate = let maybeCompanyFile = lookup company company_to_companyfile maybeModeString = lookup displaymode displaymode_to_modestring maybeTitleEnd = lookup displaymode displaymode_to_titleend company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")] displaymode_to_modestring = [("points", "using 1:2 with linespoints"), ("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")] displaymode_to_titleend = [("points","daily prices"),("candles","opening prices")] in case ( maybeCompanyFile, maybeModeString, maybeTitleEnd ) of ( Just companyfile, Just modestring, Just titleEnd) -> putStrLn $ gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyfile ++ "'" ++ modestring ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\"" _ -> error $ "bad lookup. " ++ company ++ " -> company file: " ++ ( show maybeCompanyFile ) ++ "\n" ++ " " ++ displaymode ++ " -> displaymode: " ++ ( show maybeModeString ) ++ "\n" ++ " " ++ displaymode ++ " -> titleEnd: " ++ ( show maybeTitleEnd) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Answering my own plea for help, I now have the following, which seems
neater to me.
company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")]
displaymode_to_modestring = [("points", "using 1:2 with linespoints"),
("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")]
displaymode_to_titleend = [("points","daily
prices"),("candles","opening prices")]
financial_output_wrapper :: String -> String -> String -> String -> IO ()
financial_output_wrapper company displaymode startDate endDate =
do
let maybeCompanyFile = lookup company company_to_companyfile
case maybeCompanyFile of Nothing -> error $ "no company file for "
++ company
_ -> return ()
let maybeModeString = lookup displaymode displaymode_to_modestring
case maybeModeString of Nothing -> error $ "no mode string for "
++ displaymode
_ -> return ()
let maybeTitleEnd = lookup displaymode displaymode_to_titleend
case maybeTitleEnd of Nothing -> error $ "no title end for " ++ displaymode
_ -> return ()
let maybeScript = gen_gnuplot_financial_script company
( maybeCompanyFile )
( maybeModeString )
( maybeTitleEnd )
startDate endDate
case maybeScript of
Just script -> putStrLn script
_ -> error $ "bad script"
gen_gnuplot_financial_script :: String -> Maybe String -> Maybe String
-> Maybe String -> String -> String -> Maybe String
gen_gnuplot_financial_script company (Just companyfile ) ( Just
modestring) ( Just titleEnd ) startDate endDate
= Just $ gnuplot_timeseries_settings ++ "\n" ++
"plot [\"" ++ startDate ++ "\":\"" ++
endDate ++ "\"]"
++ " '" ++ companyfile ++ "'"
++ modestring
++ " title \"" ++ company ++ " " ++
titleEnd ++ "\""
2007/4/12, Thomas Hartman
I was translating some perl code to haskell as a learning exercise and wound up with the following. (below) Simple code that accepts some string arguments, and prints a string -- so, of type String -> String -> String -> String -> IO ().
I like to be concise, but I get the feeling something went awry. What seems to be costing me the most is checking whether the various arguments are legitimate, and printing a helpful error message if not.
I was able to achieve this by using Maybe and error on failed pattern match, but as said, seems kind of overly complicated.
Is there a simpler way to do the following, eg for function
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO ()
?
By the way this is being used in
http://code.google.com/p/gnuplotwebinterface/
**************
module Common where
gnuplot_png_settings = "set terminal png transparent nocrop enhanced size 600,400\n" ++ "set pm3d implicit at s"
gnuplot_math_settings = gnuplot_png_settings ++ "\n" ++ "set border 4095 \n\ \ set xlabel \"x\" \n\ \ set ylabel \"y\""
gnuplot_timeseries_settings = gnuplot_png_settings ++ "\n" ++ "set xdata time # The x axis data is time \n" ++ "set timefmt \"%d-%b-%y\" # The dates in the file look like 10-Jun-04 \n" ++ "set format x \"%b %d\" #On the x-axis, we want tics like Jun 10"
gen_gnuplot_math_script :: String -> String -> IO () gen_gnuplot_math_script style function = let maybePlotCmd = lookup style style_to_plotcmd style_to_plotcmd = [("math-2d","plot"),("math-3d","splot")] in case maybePlotCmd of Just plotcmd -> putStrLn $ gnuplot_math_settings ++ "\n" ++ plotcmd ++ " " ++ function _ -> error $ "bad style: " ++ style
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO () gen_gnuplot_financial_script company displaymode startDate endDate = let maybeCompanyFile = lookup company company_to_companyfile maybeModeString = lookup displaymode displaymode_to_modestring maybeTitleEnd = lookup displaymode displaymode_to_titleend company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")] displaymode_to_modestring = [("points", "using 1:2 with linespoints"), ("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")] displaymode_to_titleend = [("points","daily prices"),("candles","opening prices")] in case ( maybeCompanyFile, maybeModeString, maybeTitleEnd ) of ( Just companyfile, Just modestring, Just titleEnd) -> putStrLn $ gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyfile ++ "'" ++ modestring ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\"" _ -> error $ "bad lookup. " ++ company ++ " -> company file: " ++ ( show maybeCompanyFile ) ++ "\n" ++ " " ++ displaymode ++ " -> displaymode: " ++ ( show maybeModeString ) ++ "\n" ++ " " ++ displaymode ++ " -> titleEnd: " ++ ( show maybeTitleEnd)

And this mess can be simplified further by something like
financial_output_wrapper company displaymode startDate endDate =
do
let maybeCompanyFile = lookup company company_to_companyfile
validate_arg "company" company maybeCompanyFile
........
validate_arg argname arg maybeTransformedArg =
case maybeTransformedArg of
Nothing -> error $ "no transformed " ++ argname ++ " arg for " ++ arg
_ -> return ()
Summary: I like being able to check the validity of user input on an
arg-by-arg basis, and now I guess I can.
2007/4/13, Thomas Hartman
Answering my own plea for help, I now have the following, which seems neater to me.
company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")] displaymode_to_modestring = [("points", "using 1:2 with linespoints"), ("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")] displaymode_to_titleend = [("points","daily prices"),("candles","opening prices")]
financial_output_wrapper :: String -> String -> String -> String -> IO () financial_output_wrapper company displaymode startDate endDate = do let maybeCompanyFile = lookup company company_to_companyfile case maybeCompanyFile of Nothing -> error $ "no company file for " ++ company _ -> return () let maybeModeString = lookup displaymode displaymode_to_modestring case maybeModeString of Nothing -> error $ "no mode string for " ++ displaymode _ -> return () let maybeTitleEnd = lookup displaymode displaymode_to_titleend case maybeTitleEnd of Nothing -> error $ "no title end for " ++ displaymode _ -> return () let maybeScript = gen_gnuplot_financial_script company ( maybeCompanyFile ) ( maybeModeString ) ( maybeTitleEnd ) startDate endDate case maybeScript of Just script -> putStrLn script _ -> error $ "bad script"
gen_gnuplot_financial_script :: String -> Maybe String -> Maybe String -> Maybe String -> String -> String -> Maybe String gen_gnuplot_financial_script company (Just companyfile ) ( Just modestring) ( Just titleEnd ) startDate endDate = Just $ gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyfile ++ "'" ++ modestring ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\""
2007/4/12, Thomas Hartman
: I was translating some perl code to haskell as a learning exercise and wound up with the following. (below) Simple code that accepts some string arguments, and prints a string -- so, of type String -> String -> String -> String -> IO ().
I like to be concise, but I get the feeling something went awry. What seems to be costing me the most is checking whether the various arguments are legitimate, and printing a helpful error message if not.
I was able to achieve this by using Maybe and error on failed pattern match, but as said, seems kind of overly complicated.
Is there a simpler way to do the following, eg for function
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO ()
?
By the way this is being used in
http://code.google.com/p/gnuplotwebinterface/
**************
module Common where
gnuplot_png_settings = "set terminal png transparent nocrop enhanced size 600,400\n" ++ "set pm3d implicit at s"
gnuplot_math_settings = gnuplot_png_settings ++ "\n" ++ "set border 4095 \n\ \ set xlabel \"x\" \n\ \ set ylabel \"y\""
gnuplot_timeseries_settings = gnuplot_png_settings ++ "\n" ++ "set xdata time # The x axis data is time \n" ++ "set timefmt \"%d-%b-%y\" # The dates in the file look like 10-Jun-04 \n" ++ "set format x \"%b %d\" #On the x-axis, we want tics like Jun 10"
gen_gnuplot_math_script :: String -> String -> IO () gen_gnuplot_math_script style function = let maybePlotCmd = lookup style style_to_plotcmd style_to_plotcmd = [("math-2d","plot"),("math-3d","splot")] in case maybePlotCmd of Just plotcmd -> putStrLn $ gnuplot_math_settings ++ "\n" ++ plotcmd ++ " " ++ function _ -> error $ "bad style: " ++ style
gen_gnuplot_financial_script :: String -> String -> String -> String -> IO () gen_gnuplot_financial_script company displaymode startDate endDate = let maybeCompanyFile = lookup company company_to_companyfile maybeModeString = lookup displaymode displaymode_to_modestring maybeTitleEnd = lookup displaymode displaymode_to_titleend company_to_companyfile = [("ibm","data/ibm.dat"),("cisco","data/cisco.dat")] displaymode_to_modestring = [("points", "using 1:2 with linespoints"), ("candles","using 1:($2+$3+$4+$5)/4:4:3 with yerrorbars")] displaymode_to_titleend = [("points","daily prices"),("candles","opening prices")] in case ( maybeCompanyFile, maybeModeString, maybeTitleEnd ) of ( Just companyfile, Just modestring, Just titleEnd) -> putStrLn $ gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyfile ++ "'" ++ modestring ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\"" _ -> error $ "bad lookup. " ++ company ++ " -> company file: " ++ ( show maybeCompanyFile ) ++ "\n" ++ " " ++ displaymode ++ " -> displaymode: " ++ ( show maybeModeString ) ++ "\n" ++ " " ++ displaymode ++ " -> titleEnd: " ++ ( show maybeTitleEnd)

Answering my own plea for help, I now have the following, which seems neater to me.
checking Maybes is best done in the Maybe Monad, or if you need specific error messages, using maybe. that, in turn can be abstracted out into a lookup with error message. once the checking is done in the wrapper, there is no need to repeat it in the generator. also, the interface to the generator is too wide for the small amount of extra functionality it provides, so it is probably best inlined, and there seems to be no need to commit to IO so early. i also tend to use [String], with a final unlines before output, but that is a matter of opinion, i guess. financial_output :: String -> String -> String -> String -> String financial_output company displaymode startDate endDate = financial_script where financial_script = gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyFile ++ "'" ++ modeString ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\"" companyFile = lookupWith (error $ "no company file for " ++ company) company company_to_companyfile modeString = lookupWith (error $ "no mode string for " ++ displaymode) displaymode displaymode_to_modestring titleEnd = lookupWith (error $ "no title end for " ++ displaymode) displaymode displaymode_to_titleend lookupWith error key assocs = maybe error id $ lookup key assocs hth, claus

financial_script = gnuplot_timeseries_settings ++ "\n" ++ "plot [\"" ++ startDate ++ "\":\"" ++ endDate ++ "\"]" ++ " '" ++ companyFile ++ "'" ++ modeString ++ " title \"" ++ company ++ " " ++ titleEnd ++ "\""
Also note the existence of Text.Printf if you like that style better.

by utilizing Text.Printf.printf, extracting some more common functionality for the lookups, and changing the error handling (check for errors before giving results, but use throwError instead of error, letting the caller decide whether errors are fatal or not), we arrive at something like: financial_output :: (Functor m, MonadError String m) => String -> String -> String -> String -> m String financial_output company displaymode startDate endDate = fmap financial_script $ mapM lookupWith lookups where financial_script [companyFile,modeString,titleEnd] = gnuplot_timeseries_settings ++ "\n" ++ printf "plot [\"%s\":\"%s\"] '%s'%s title \"%s %s\"" startDate endDate companyFile modeString company titleEnd lookups = [ ("no company file for ", company, company_to_companyfile) , ("no mode string for ", displaymode, displaymode_to_modestring) , ("no title end for ", displaymode, displaymode_to_titleend) ] lookupWith (msg,key,assocs) = maybe (throwError $ msg ++ key) return $ lookup key assocs which perhaps isn't all that bad? the main thing i miss in Haskell for this kind of code generators are here-documents. there are workarounds (Hugs has a form of here docs, string interpolation isn't difficult to hack up, unlines gets rid of ++ and "\n"), and for more complex code generators, use of Text.PrettyPrint may be more appropriate, but for everyday scripting with code generation, nothing is as simple, readable, or portable as good old here-documents. hth, claus ps. calling the modified function: Main> either error putStrLn $ financial_output "ibm" "point" "start" "end" Program error: no mode string for point Main> either error putStrLn $ financial_output "ibm" "points" "start" "end" set terminal png transparent nocrop enhanced size 600,400 set pm3d implicit at s set xdata time # The x axis data is time set timefmt "%d-%b-%y" # The dates in the file look like 10-Jun-04 set format x "%b %d" #On the x-axis, we want tics like Jun 10 plot ["start":"end"] 'data/ibm.dat'using 1:2 with linespoints title "ibm daily prices"
participants (4)
-
Claus Reinke
-
Dan Mead
-
Evan Laforge
-
Thomas Hartman