Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-18 Thread Thomas Hartman

Without the flag:

[EMAIL 
PROTECTED]:~/websites/gnuplotwebinterface/cgi-bin/gnuplot-scripts>./financial2.hs
cisco candles 31-May-04 11-Jun-04

./financial2.hs:58:0:
   Illegal instance declaration for `MyString (Either String String)'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
   In the instance declaration for `MyString (Either String String)'

./financial2.hs:61:0:
   Illegal instance declaration for `MyString String'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
   In the instance declaration for `MyString String'

[EMAIL PROTECTED]:~/websites/gnuplotwebinterface/cgi-bin/gnuplot-scripts>cat
--number financial2.hs | tail
   58  instance MyString (Either String String)
   59 where mystr = id
   60
   61  instance MyString String
   62 where mystr = Right
   63
   64  x <++> y = do xv <- mystr x
   65yv <- mystr y
   66return $ xv ++ yv
   67




2007/4/18, Thomas Hartman <[EMAIL PROTECTED]>:

Looks like this needs to be run with

#!/usr/lib/ghc-6.6/bin/runghc
{-# OPTIONS_GHC -fglasgow-exts #-}

to get

instance MyString (Either String String)
   where mystr = id

instance MyString String
   where mystr = Right

to work.

I'm curious if there is a community feeling on whether glasgow-exts is
sort of a de-facto standard now? Or is it common to try to get things
to work without this, for maximum portability?

Is there an easy way to get the above to work without the compiler flag?


2007/4/16, jeff p <[EMAIL PROTECTED]>:
> {
>
> Hello,
>
>   Here is a variation on Claus' code which returns an Either type
> rather than fails with error. This could be further generalized to use
> any instance of MonadError, rather than Either.
>
> -Jeff
>
> }
>
> import Control.Monad.Error
>
> financial_output :: String -> String -> String -> String -> Either 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 ("no company file for " ++ company)
> company company_to_companyfile
>
>   modeString  = lookupWith ("no mode string for " ++ displaymode)
> displaymode displaymode_to_modestring
>
>   titleEnd= lookupWith ("no title end for " ++ displaymode)
> displaymode displaymode_to_titleend
>
> lookupWith :: (Eq a) => String -> a -> [(a,String)] -> Either String String
> lookupWith error key assocs = maybe (Left error) Right $ lookup key assocs
>
> class MyString a
> where mystr :: a -> Either String String
> instance MyString (Either String String)
> where mystr = id
> instance MyString String
> where mystr = Right
>
> x <++> y = do xv <- mystr x
>   yv <- mystr y
>   return $ xv ++ yv
>


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


Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-18 Thread Thomas Hartman

Looks like this needs to be run with

#!/usr/lib/ghc-6.6/bin/runghc
{-# OPTIONS_GHC -fglasgow-exts #-}

to get

instance MyString (Either String String)
  where mystr = id

instance MyString String
  where mystr = Right

to work.

I'm curious if there is a community feeling on whether glasgow-exts is
sort of a de-facto standard now? Or is it common to try to get things
to work without this, for maximum portability?

Is there an easy way to get the above to work without the compiler flag?


2007/4/16, jeff p <[EMAIL PROTECTED]>:

{

Hello,

  Here is a variation on Claus' code which returns an Either type
rather than fails with error. This could be further generalized to use
any instance of MonadError, rather than Either.

-Jeff

}

import Control.Monad.Error

financial_output :: String -> String -> String -> String -> Either 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 ("no company file for " ++ company)
company company_to_companyfile

  modeString  = lookupWith ("no mode string for " ++ displaymode)
displaymode displaymode_to_modestring

  titleEnd= lookupWith ("no title end for " ++ displaymode)
displaymode displaymode_to_titleend

lookupWith :: (Eq a) => String -> a -> [(a,String)] -> Either String String
lookupWith error key assocs = maybe (Left error) Right $ lookup key assocs

class MyString a
where mystr :: a -> Either String String
instance MyString (Either String String)
where mystr = id
instance MyString String
where mystr = Right

x <++> y = do xv <- mystr x
  yv <- mystr y
  return $ xv ++ yv


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


Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-16 Thread Thomas Hartman

With regards to the variable interpolation in strings problem, it's
probably worth watching

http://groups.google.de/group/fa.haskell/browse_thread/thread/34741c2a5c311a17/286dbd62748ef1c1?lnk=st&q=%22haskell+cafe%22+%22template+system%22&rnum=1&hl=en#286dbd62748ef1c1

which mentions some perl/python-like template systems in the works for haskell.

2007/4/16, jeff p <[EMAIL PROTECTED]>:

{

Hello,

  Here is a variation on Claus' code which returns an Either type
rather than fails with error. This could be further generalized to use
any instance of MonadError, rather than Either.

-Jeff

}

import Control.Monad.Error

financial_output :: String -> String -> String -> String -> Either 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 ("no company file for " ++ company)
company company_to_companyfile

  modeString  = lookupWith ("no mode string for " ++ displaymode)
displaymode displaymode_to_modestring

  titleEnd= lookupWith ("no title end for " ++ displaymode)
displaymode displaymode_to_titleend

lookupWith :: (Eq a) => String -> a -> [(a,String)] -> Either String String
lookupWith error key assocs = maybe (Left error) Right $ lookup key assocs

class MyString a
where mystr :: a -> Either String String
instance MyString (Either String String)
where mystr = id
instance MyString String
where mystr = Right

x <++> y = do xv <- mystr x
  yv <- mystr y
  return $ xv ++ yv


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


Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-15 Thread jeff p

{

Hello,

 Here is a variation on Claus' code which returns an Either type
rather than fails with error. This could be further generalized to use
any instance of MonadError, rather than Either.

-Jeff

}

import Control.Monad.Error

financial_output :: String -> String -> String -> String -> Either 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 ("no company file for " ++ company)
   company company_to_companyfile

 modeString  = lookupWith ("no mode string for " ++ displaymode)
   displaymode displaymode_to_modestring

 titleEnd= lookupWith ("no title end for " ++ displaymode)
   displaymode displaymode_to_titleend

lookupWith :: (Eq a) => String -> a -> [(a,String)] -> Either String String
lookupWith error key assocs = maybe (Left error) Right $ lookup key assocs

class MyString a
   where mystr :: a -> Either String String
instance MyString (Either String String)
   where mystr = id
instance MyString String
   where mystr = Right

x <++> y = do xv <- mystr x
 yv <- mystr y
 return $ xv ++ yv
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-15 Thread Thomas Hartman

Claus and Evan ++; that was very helpful.

FWIW, my gut feeling is that Claus's first version was easier to
understand than the revision with printf, which seems to me to involve
a lot more monadic wizardry (Functor, MonadError, fmap, mapm). The
first version, which just used maybe, was clear to me within seconds.

But again, I learned a lot. Thanks.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Translating perl -> haskell, string "fill ins" with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-14 Thread Claus Reinke
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"

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