Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-27 Thread Tim Cowlishaw
On Tue, Jul 26, 2011 at 11:14 PM, Alexander Solla alex.so...@gmail.com wrote:

 data OrderType = Market Size | Limit LimitPrice Expiration Size | Stop
 (Either Percent Price)
 newtype Sell = Sell OrderType
 newtype Buy = Buy OrderType
 newtype Order = Order (Either Buy Sell)

 size :: Order - Int
 size (Order (Left (Buy (Market s))) = s
 size (Order (Left (Buy (Limit _ _ s))) = s
 etc.

Aah, thank you - this is really neat. So now, I can write (for
instance) an Eq instance for OrderType and use deriving (Eq) on the
newtypes that wrap it, and my Order can be a concrete type, but still
encapsulates all the different types of order.

Thank you!

Tim

Thank you

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


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-27 Thread Alexander Solla
On Tue, Jul 26, 2011 at 11:58 PM, Tim Cowlishaw t...@timcowlishaw.co.ukwrote:

 On Tue, Jul 26, 2011 at 11:14 PM, Alexander Solla alex.so...@gmail.com
 wrote:

  data OrderType = Market Size | Limit LimitPrice Expiration Size | Stop
  (Either Percent Price)
  newtype Sell = Sell OrderType
  newtype Buy = Buy OrderType
  newtype Order = Order (Either Buy Sell)

  size :: Order - Int
  size (Order (Left (Buy (Market s))) = s
  size (Order (Left (Buy (Limit _ _ s))) = s
  etc.

 Aah, thank you - this is really neat. So now, I can write (for
 instance) an Eq instance for OrderType and use deriving (Eq) on the
 newtypes that wrap it, and my Order can be a concrete type, but still
 encapsulates all the different types of order.

 Thank you!


No problem.  This is more-or-less how type classes work internally, with
fewer restrictions (but some more implicit passing around of stuff).  Notice
that my Order type corresponds with your Order typeclass.  My OrderType
type value constructors correspond to all your Order types.  In other words,
a typeclass is a fancy open union type.  I never use type classes unless
I need that openness property.

The problem with this approach is that it can become verbose very quickly.
 It can be mitigated some by defining accessors for the newtypes, and using
function composition.

So instead of:
 newtype Sell = Sell OrderType
 newtype Buy = Buy OrderType
 newtype Order = Order (Either Buy Sell)

I would personally use
 newtype Sell = Sell { unSell :: OrderType }
 newtype Buy = Buy { unBuy :: OrderType }
 newtype Order = Order { unOrder :: Either Buy Sell }

where un should be read like unwrap.  These unwrappers can help cut down
on the size of pattern matches.  I'll give an example shortly.

I suggested using Maybe to deal with nonsense semantics/undefinedness.  All
orders have a size/quantity, but not all have a limit price.  So we might
write an accessor like:

limitPrice' :: OrdeType - Maybe Price
limitPrice'  (Limit l _ _) = Just l
limitPrice' _ = Nothing

We have turned a partial function into a total function by embedding it
in (Order - Maybe Price).  This cuts down on bugs.

Now that easy accessor for all orders:

limitPrice :: Order - Maybe Price
limitPrice = limitPrice' . either (unBuy) (unSell) . unOrder

We might even want to stick limitPrice' in a where clause for limitPrice,
depending on whether you expect reuse or not.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Tim Cowlishaw
Hi all,

I'm currently embarking on my first major project in Haskell, after
dabbling with it for several years, and seem to keep finding myself in
situations where I create a typeclass that seems to be some sort of
specialisation of another, more general typeclass. Given that this is
the case, I've then decided that all instances of the specific class
should therefore also be instances of the general class, and arrived
at the following method of doing so, using the FlexibleInstances and
UndecidableInstances extensions to GHC:

{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

class Max a where
  maximum :: a - a - a

instance (Ord a) = Max a where
  maximum = max


(Obviously, this is a very trivial, and rather silly example - I'm not
really trying to implement a class called 'Max').

However, I'd be curious to know if (a) There are better or more
idiomatic ways of achieving the same effect, and (b) Whether or not I
should be doing this at all; It did occur to me that this seems rather
trying to re-implement OOP-style inheritance with typeclasses, and
therefore perhaps not a very Haskellish approach to designing
software. Therefore - are there better ways to achieve this, or should
I not be doing this at all, and, if the latter, what would be the best
means of achieving a similar result (i.e. a typeclass that implements
all the functionality of one or more others, optionally with some
additional specialism)?

Many thanks,

Tim

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


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Stephen Tetley
For:

instance (Ord a) = Max a where
 maximum = max

The same could more simply be achieved with a function:

maximum :: Ord a = a
maximum = max

Now, you probably wanted both a base-case using max and type specific,
special cases:

instance Max Int where
  maximum = 2^16

If you have both instances defined in the same module, GHC should
always pick the special case for Int if overlapping instances is
turned on. However, I've never found a description of how it resolves
instance selection if you have the specialized cases in different
modules. Unspecified [*] behaviour is not something I'd want to rely
on, so I always avoid Overlapping Instances.


[*] Of course, the multiple module behaviour might be specified somewhere...

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


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Evan Laforge
 However, I'd be curious to know if (a) There are better or more
 idiomatic ways of achieving the same effect, and (b) Whether or not I
 should be doing this at all; It did occur to me that this seems rather
 trying to re-implement OOP-style inheritance with typeclasses, and
 therefore perhaps not a very Haskellish approach to designing

Could you give a specific example of the problem you're trying to solve?

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


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Tim Cowlishaw
On Tue, Jul 26, 2011 at 7:46 PM, Evan Laforge qdun...@gmail.com wrote:

 Could you give a specific example of the problem you're trying to solve?

Sorry, yes, that'd be useful :-)

So, the project I'm working on involves developing a simulation of a
securities market. I have a type which models an order book, on which
orders can be placed or removed (and later filled):

eg.

placeOrder :: (Order e) - e - OrderBook - OrderBook
deleteOrder :: (Order e) - e - OrderBook - OrderBook

Now, i've chosen to model orders as a typeclass, as there are various
semantic differences between different types of order that I can model
as different types implementing this typeclass (limit orders vs market
orders, buy side vs sell side), and these differences can be specified
in the type's implementation of the class. However, there are a number
of other typeclasses that all orders should also be instances of (and
in terms of which their semantics don't differ, eg Eq or Ord.

For instance, for a typeclass representing the interface that any
Order type should implement:

class Order o where
  price :: o - Int
  size :: o - Int

I'd like to be able to specify an Eq instance for all types of class
Order in a manner similar to this:

instance (Order o) = Eq o where
  o1 == o2 = (price o1 == price o2)  (size o1 == size o2)

I hope this clarifies my query - I'd be interested to know if this is
possible, and whether or not it's a recommended approach, and if not,
how else I could achieve something similar.

Many thanks,

Tim

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


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Alexander Solla
On Tue, Jul 26, 2011 at 1:52 PM, Tim Cowlishaw t...@timcowlishaw.co.ukwrote:

 On Tue, Jul 26, 2011 at 7:46 PM, Evan Laforge qdun...@gmail.com wrote:

  Could you give a specific example of the problem you're trying to solve?

 Sorry, yes, that'd be useful :-)

 So, the project I'm working on involves developing a simulation of a
 securities market. I have a type which models an order book, on which
 orders can be placed or removed (and later filled):

 eg.

 placeOrder :: (Order e) - e - OrderBook - OrderBook
 deleteOrder :: (Order e) - e - OrderBook - OrderBook

 Now, i've chosen to model orders as a typeclass, as there are various
 semantic differences between different types of order that I can model
 as different types implementing this typeclass (limit orders vs market
 orders, buy side vs sell side), and these differences can be specified
 in the type's implementation of the class.


Use Maybe to demarcate nonsense semantics/undefinedness.


 However, there are a number
 of other typeclasses that all orders should also be instances of (and
 in terms of which their semantics don't differ, eg Eq or Ord.


data OrderType = Market Size | Limit LimitPrice Expiration Size | Stop
(Either Percent Price)

newtype Sell = Sell OrderType
newtype Buy = Buy OrderType

newtype Order = Order (Either Buy Sell)


 class Order o where
  price :: o - Int
  size :: o - Int


size :: Order - Int
size (Order (Left (Buy (Market s))) = s
size (Order (Left (Buy (Limit _ _ s))) = s
etc.


 I'd like to be able to specify an Eq instance for all types of class
 Order in a manner similar to this:

 instance (Order o) = Eq o where
  o1 == o2 = (price o1 == price o2)  (size o1 == size o2)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Idiomatic ways to make all instances of a certain class also instances of another?

2011-07-26 Thread Henning Thielemann


On Tue, 26 Jul 2011, Tim Cowlishaw wrote:


For instance, for a typeclass representing the interface that any
Order type should implement:

class Order o where
 price :: o - Int
 size :: o - Int

I'd like to be able to specify an Eq instance for all types of class
Order in a manner similar to this:

instance (Order o) = Eq o where
 o1 == o2 = (price o1 == price o2)  (size o1 == size o2)


You may define once:

orderEq :: Order o = o - o - Bool
orderEq o1 o2 = (price o1 == price o2)  (size o1 == size o2)

and then define instances like

instance Order A where ...
instance Eq A where (==) = orderEq

instance Order B where ...
instance Eq B where (==) = orderEq


I don't think there is an easier and still predictable way of defining the 
Eq instances.


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