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

Reply via email to