[Haskell-beginners] Type class vs. Record: How do I model an interface in Haskell?

Dimitri DeFigueiredo defigueiredo at ucdavis.edu
Thu May 29 00:26:18 UTC 2014


Hi All,

I have another modeling related question. This time is about how to 
model an interface in haskell.

(full code in https://github.com/defigueiredo/interfaces-in-haskell)

I have an interface that I want any Stock Exchange to follow. I can 
think of 3 different ways to do this in Haskell:

- write a type class and then instantiate it for 3 different types
- use a record and associate the appropriate function to each field
- use a module and define the appropriate function in each file

These options seem to go from most restrictive to least restrictive. In 
the sense that in the last solution I can make two functions calls:

         print $ NYSE.getPendingOrders
         print $ NASDAQ.getPendingOrders

and the getPendingOrders functions don't even need to have exactly the 
same types between the two modules. I can see how this could be useful 
sometimes.

Using record syntax is more restrictive as the type signatures for the 
functions have to match, but I am not sure what I get from having a type 
class here, rather than just the records. Comparing the model 
declarations, the type class solution has an extra parameter 'a' 
clobbering up the signatures:

model.hs
---------------------------------------------------------------------
module Model where

import Data.Time.Clock.POSIX

-- Units
type Volume  = Double
type Price   = Double

type OrderID   = Int
type Timestamp = POSIXTime

-- Orders
data OrderType = Buy | Sell deriving Show
data Order = Order { order::OrderType,
                      price  ::Price,
                      volume ::Volume,
                      confirmation :: Maybe (OrderID, Timestamp) }
               deriving Show

------ All versions identical until here ------

class Exchange a where
         sellAt :: a -> Price -> Volume -> Order
         buyAt  :: a -> Price -> Volume -> Order
         getPendingOrders :: a -> Maybe [Order] -- returns [Order] or 
Nothing if can't get that information
         cancelOrder :: a -> OrderID -> Order -> Maybe (Either Order 
Order) -- returns canceled order (right) or
-- what was still pending if already executed (left)
-- or Nothing, if has no connectivity (or other error).

---------------------------------------------------------------------
whereas the record solution is...

------ All versions identical until here ------

data Exchange = Exchange {
         sellAt :: Price -> Volume -> Order,
         buyAt  :: Price -> Volume -> Order,
         getPendingOrders :: Maybe [Order]
         cancelOrder :: OrderID -> Order -> Maybe (Either Order Order),
         }


---------------------------------------------------------------------
instances look pretty similar:

where's the type class solution...
---------------------------------------------------------------------
module NYSE where

import Model

data NYSE = NYSE

instance Exchange NYSE where

         sellAt = error "NYSE doesn't sell."

         getPendingOrders a = Just [Order Buy  50 100 Nothing]

         buyAt       = undefined
         cancelOrder = undefined

---------------------------------------------------------------------
here's the record solution...
---------------------------------------------------------------------
module NYSE where

import Model



nyse = Exchange {

         sellAt = error "NYSE doesn't sell.",

         getPendingOrders = Just [Order Buy  50 100 Nothing],

         buyAt       = undefined,
         cancelOrder = undefined
         }
---------------------------------------------------------------------

So, my questions are:
1) What do I get from making this a type class rather than using records?
2) Is there an even better solution I have overlooked?

(full code for 3 different solutions in 
https://github.com/defigueiredo/interfaces-in-haskell)


Thanks!

Dimitri






More information about the Beginners mailing list