[Haskell-cafe] Re: how would this be done? type classes? existentialtypes?

Matthias Fischmann fis at wiwi.hu-berlin.de
Sat Mar 18 08:52:57 EST 2006


On Fri, Mar 17, 2006 at 04:53:42PM +0000, Ben Rudiak-Gould wrote:
>
> Matthias Fischmann wrote:
> >and now it gets interesting: i need instances for Rs on Show, Read,
> >Eq, Ord.  Show is very simple, but Read?
> 
> I think you're right: it's impossible to implement Read for Rs in an 
> extensible way, because there's no way to obtain the necessary Resource 
> dictionary at runtime. I've wished in the past for a family of functions, 

With all the suggestions on this list I figured something out that
compiles, though.  It requires extension of the Read instance of Rx,
but that's ok because it is an issue local to the module.  Here is the
code:

class (Show a, Read a) => Resource a where
    rsName      :: a -> String
    rsAdvance   :: a -> a
    rsStarved   :: a -> Bool

data Rs = forall a . (Resource a) => Rs a

instance Resource Rs where
    rsName    (Rs a)   =     rsName a
    rsAdvance (Rs a)   = Rs (rsAdvance a)
    rsStarved (Rs a)   =     rsStarved a

instance Show Rs where
    show (Rs r) = "Rs " ++ rsName r ++ " (" ++ show r ++ ")"

instance Read Rs where
  readsPrec pred = readConstructor
    where
    readConstructor ('R':'s':' ':'"':s) = readResourceType "" s
    readConstructor s = []

    readResourceType acc ('"':' ':'(':s) = readResource (reverse acc) s
    readResourceType acc (x:s) | isAlpha x = readResourceType (x:acc) s
    readResourceType _ s = []

    readResource "Rice" s =
        case readsPrec 0 s of
          [(r :: RsRice,       s')] -> readClosingParen (Rs r) s'; _ -> []
    readResource "CrudeOil" s =
        case readsPrec 0 s of
          [(r :: RsCrudeOil,   s')] -> readClosingParen (Rs r) s'; _ -> []

    readResource _ s = assert False (error "no instance.")

    readClosingParen r (')':s) = case readsPrec pred s of rs -> (r, s) : rs
    readClosingParen _ _ = []

(Is there a better way to match list prefixes?  If I had read a paper
on monadic parsing or two, this might look more elegant, but it seems
to me to be sufficient for this simple application.  Feel free to post
the true thing.  :-)

I am more convinced yet that Eq and Ord are impossible: Which specific
resource type is hidden in the Rs constructor is, well: hidden.  But
there is a dirty trick if you have enough time and memory to waste,
and it doesn't even require extention for each new instance:

instance Eq Rs where r == r' = show r == show r'
instance Ord Rs where compare r r' = compare (show r) (show r')

And here are the resource instances:

data RsRice = RsRice
    {
     rsRiceName :: String,       -- an intuitive and descriptive name of the resource
     rsRiceProduction :: Int,
     rsRiceConsumption :: Int,
     rsRiceReserve :: Int        -- available for consumption or trading
    }
                deriving (Show, Read, Eq, Ord)

instance Resource RsRice where
    rsName _ = "Rice"
    rsAdvance r = r { rsRiceReserve = rsRiceReserve r + rsRiceProduction r - rsRiceConsumption r }
    rsStarved = (== 0) . rsRiceReserve
    rsReserve (RsRice _ _ _ res) = res
    rsSpend = rsRiceTrade (-)
    rsEarn = rsRiceTrade (+)

rsRiceTrade :: (Int -> Int -> Int) -> RsRice -> Int -> RsRice
rsRiceTrade (+) r amount = r { rsRiceReserve = rsRiceReserve r + amount }

data RsCrudeOil = RsCrudeOil
    {
     rsCrudeOilName :: String,
     rsCrudeOilProduction :: Int,
     rsCrudeOilConsumption :: Int,
     rsCrudeOilReserve :: Int,
     rsCrudeOilReserveSize :: Int  -- any water unit above this number is discarded immediately.
    }
                deriving (Show, Read, Eq, Ord)

instance Resource RsCrudeOil where
   -- ...

Btw, I am tempted to implemente crude oil as an incremental extension
to rice, by adding a record field 'rice'.  Would this increase the
number of indirections for basic operations on resources, or would ghc
be capable of optimizing that away entirely?

Thanks again to all, I am following the thread, even if I won't answer
any more.



m.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20060318/5e3c8f38/attachment.bin


More information about the Haskell-Cafe mailing list