[Haskell-cafe] Deriving instances with GADTs

2011-08-04 Thread Tim Cowlishaw
Hi all,

I've been writing a DSL to describe securities orders, and after a lot
of help from the kind folk of this list and #haskell have come up with
the following implementation, using generalised algebraic data types:

https://gist.github.com/1124621

Elsewhere in my application, I make use of the order type defined
therein in the following newtype declaration:

 newtype OrderListLevel s = OrderListLevel {orders :: [Order s Limit]}
deriving (Eq, Show)

However, the 'deriving' clause here fails:

src/Simulation/OrderList.hs:9:82:
No instance for (Eq (Order s Limit))
  arising from the 'deriving' clause of a data type declaration
   at src/Simulation/OrderList.hs:9:82-83

src/Simulation/OrderList.hs:9:86:
No instance for (Show (Order s Limit))
  arising from the 'deriving' clause of a data type declaration
   at src/Simulation/OrderList.hs:9:86-89



I don't fully understand this - the error is correct that there is no
instance of either Eq or Show for (Order s Limit), however, instances
are defined for Order Buy Limit and Order Sell Limit, and since these
are the only possible types that a value can be constructed with (the
type constructor is 'closed' over these types in some sense I guess),
it seems to me that this should provide enough information to derive
the Eq and Show instances. Am I making unreasonable expectations of
ghci's instance-deriving mechanism here, or missing something obvious?

Many thanks in advance,

Tim

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


Re: [Haskell-cafe] Deriving instances with GADTs

2011-08-04 Thread Tim Cowlishaw
2011/8/4 José Pedro Magalhães j...@cs.uu.nl:

 Here you seem to be using newtype deriving in particular, which behaves
 differently from standard deriving. Compiling with -ddump-deriv will show
 you the instances GHC is generating, which can help in debugging.

Aah - this is very useful, thanks!

 Note however that deriving instances for GADTs is not trivial, in general.
 In particular, you should not assume that GHC knows that `s` can only be
 instantiated with `Buy` and `Sell` since (because we lack a proper kind
 system) nothing prevents you from later using, say, `Order Int Limit`
 somewhere.

Aah - this is something like what I suspected (The type signature for
OrderListLevel doesn't preclude eg OrderListLevel Int which would need
an instance of (Eq|Show) for Order Int Limit, which does not exist.

 I describe the issue in more detail in the paper:

 José Pedro Magalhães and Johan Jeuring. Generic Programming for Indexed
 Datatypes.
 Color pdf: http://dreixel.net/research/pdf/gpid.pdf
 Greyscale pdf: http://dreixel.net/research/pdf/gpid_nocolor.pdf

Oh, brilliant, thank you! I'll take a look now.

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-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] XCode Dependency for HP on Mac

2011-07-27 Thread Tim Cowlishaw
On Wed, Jul 27, 2011 at 8:09 AM, Chris Smith cdsm...@gmail.com wrote:

 Alternatively, maybe it would it be easier to have the Mac users install
 VMWare's free version and I can just have them install Windows or Linux
 in that?  Or does it also have weird dependency issues like this, too?

(Perhaps wandering slightly O/T, but...) Having done some teaching in
similar circumstances before (although not with Haskell), I'd highly
recommend this approach. In fact, I'd probably have all the students,
regardless of OS install VMWare or VirtualBox, and then distribute a
VM image with the Haskell Platform and any other tools they need
preinstalled. It means a bit of extra preparation, but it'll allow you
to get to the interesting bit of the class more quickly and with less
frustration on the part of both yourself and your students.

Hope this helps.

Chers,

Tim

___
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 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] Cloud Haskell

2011-07-23 Thread Tim Cowlishaw
On Fri, Jul 22, 2011 at 4:11 PM, Tom Murphy amin...@gmail.com wrote:

 Is anyone using Cloud Haskell yet? I'm really excited by the
 possibilities.

Hello there! I'm currently looking at the possibility of incorporating
it into my masters thesis project (A Haskell EDSL for agent-based
simulation), but haven't yet implemented the part of the project
that'll use it. I'd also be interested in anyone else's experiences
with it as it seems like a fairly young project, and will try and
write up some of my own once I've got a bit further with it!

Thanks,

Tim

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