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

Dan Mead d.w.mead at gmail.com
Thu Apr 12 10:57:31 EDT 2007


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 <tphyahoo at gmail.com> wrote:
>
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070412/29507b16/attachment-0001.htm


More information about the Haskell-Cafe mailing list