[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


[Haskell-cafe] library-profiling default

2011-08-04 Thread Tom Doris
Hi
Is there a good reason that the default for library-profiling in
.cabal/config is set to False? It seems a lot of people hit the problem of
trying to profile for the first time, finding it doesn't work because
profiling libraries haven't been installed, then they have to walk the
dependencies reinstalling everything.

Is there a major cost or problem with just defaulting this to True?

Apologies if this is answered elsewhere, I saw various discussions on why it
is difficult to automatically build required libs with profiling on demand,
but nothing that discussed changing the default so that they are always
built.
Tom
___
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 José Pedro Magalhães
Hi Tim,

On Thu, Aug 4, 2011 at 08:57, Tim Cowlishaw t...@timcowlishaw.co.uk wrote:

 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?


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.

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.

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



Cheers,
Pedro



 Many thanks in advance,

 Tim

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

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


Re: [Haskell-cafe] library-profiling default

2011-08-04 Thread Ivan Lazar Miljenovic
On 4 August 2011 17:06, Tom Doris tomdo...@gmail.com wrote:
 Hi
 Is there a good reason that the default for library-profiling in
 .cabal/config is set to False? It seems a lot of people hit the problem of
 trying to profile for the first time, finding it doesn't work because
 profiling libraries haven't been installed, then they have to walk the
 dependencies reinstalling everything.
 Is there a major cost or problem with just defaulting this to True?
 Apologies if this is answered elsewhere, I saw various discussions on why it
 is difficult to automatically build required libs with profiling on demand,
 but nothing that discussed changing the default so that they are always
 built.

My guess is that this way, it reduces the build-time for users that
are just using cabal-install to get Haskell programs (darcs, pandoc,
etc.) or using Haskell for assignments but with no need/interest in
profiling.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

___
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


[Haskell-cafe] One place available at CamHac

2011-08-04 Thread Simon Marlow

Hi Folks,

There is a place available at CamHac next Friday-Sunday (12-14 August). 
 First come first served!  For instructions on how to register, see the 
wiki page:


http://www.haskell.org/haskellwiki/CamHac#Registration

Also a reminder, if you have already registered but won't be able to 
make it, please let us know so that we can reallocate your place.


Cheers,
Simon

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


Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Brent Yorgey
On Tue, Aug 02, 2011 at 05:08:33PM -0400, bob zhang wrote:
 hi, all
 testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3
 - t1 a1 t3 - t1 (a, a1) t
 testB f g h = proc (x,y) - do
 if (f x y)then g - x + 1 else h - y + 2
 
 it's very strange that the type of _f_ is (a-a1-t2) which I thought
 should be a - a1 - Bool,
 
 btw, is there any way to get the output of preprocessing using -XArrow
 extensions,
 
 Thanks a lot
 best, bob

Congratulations, you have definitely found a GHC bug!  Note there are
actually two things wrong with testB's type signature: first, t2 ought
to be Bool, as you note.  But even worse, notice that the return type
of the result arrow, t, has nothing to do with any of the other types!
This means that we can use testB along with the (-) instance for
Arrow to construct elements of arbitrary types:

  ghci let anythingYouWant = testB (\x y - False) (const 3) (const 2) (2,2)
  ghci :t anythingYouWant
  anythingYouWant :: t
  ghci anythingYouWant :: Integer
  2
  ghci anythingYouWant :: Int
  2
  ghci anythingYouWant :: Double
  1.0e-323
  ghci anythingYouWant :: Char
  '\STX'
  ghci (anythingYouWant :: (Double - Double) - [Double]) sqrt
  [
  [1]17391 segmentation fault  ghci

whoops!

I'm using GHC 7.0.3, but Daniel Wagner and I also tried it (with the
same results) on GHC 7.2.0rc1 and GHC HEAD.

I wasn't able to find a ticket for this on the GHC bug tracker, I
guess we should file one!

I tried to find a way to get the output of preprocessing using -XArrow
but wasn't able to find one (other than -ddump-ds which gives you the
unoptimized *GHC core* output, which is quite hard to read).

-Brent

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


Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
here is a reduced program that still segfaults:

{-# LANGUAGE Arrows #-}

import Control.Arrow

main :: IO ()
main = print segfault

segfault :: [()]
segfault = anythingYouWant ()

anythingYouWant :: a
anythingYouWant = testB False (const ()) ()

testB :: ArrowChoice arrow
  = bool - arrow () () - arrow () anything
testB bool arrow =
  proc () -
do if bool then arrow - ()
   else arrow - ()

Sebastian

On Fri, Aug 5, 2011 at 6:20 AM, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Tue, Aug 02, 2011 at 05:08:33PM -0400, bob zhang wrote:
  hi, all
  testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3
  - t1 a1 t3 - t1 (a, a1) t
  testB f g h = proc (x,y) - do
  if (f x y)then g - x + 1 else h - y + 2
 
  it's very strange that the type of _f_ is (a-a1-t2) which I thought
  should be a - a1 - Bool,
 
  btw, is there any way to get the output of preprocessing using -XArrow
  extensions,
 
  Thanks a lot
  best, bob

 Congratulations, you have definitely found a GHC bug!  Note there are
 actually two things wrong with testB's type signature: first, t2 ought
 to be Bool, as you note.  But even worse, notice that the return type
 of the result arrow, t, has nothing to do with any of the other types!
 This means that we can use testB along with the (-) instance for
 Arrow to construct elements of arbitrary types:

  ghci let anythingYouWant = testB (\x y - False) (const 3) (const 2)
 (2,2)
  ghci :t anythingYouWant
  anythingYouWant :: t
  ghci anythingYouWant :: Integer
  2
  ghci anythingYouWant :: Int
  2
  ghci anythingYouWant :: Double
  1.0e-323
  ghci anythingYouWant :: Char
  '\STX'
  ghci (anythingYouWant :: (Double - Double) - [Double]) sqrt
  [
  [1]17391 segmentation fault  ghci

 whoops!

 I'm using GHC 7.0.3, but Daniel Wagner and I also tried it (with the
 same results) on GHC 7.2.0rc1 and GHC HEAD.

 I wasn't able to find a ticket for this on the GHC bug tracker, I
 guess we should file one!

 I tried to find a way to get the output of preprocessing using -XArrow
 but wasn't able to find one (other than -ddump-ds which gives you the
 unoptimized *GHC core* output, which is quite hard to read).

 -Brent

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

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


Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
I created a ticket with a slightly further simplified program:
http://hackage.haskell.org/trac/ghc/ticket/5380

On Fri, Aug 5, 2011 at 10:10 AM, Sebastian Fischer fisc...@nii.ac.jpwrote:

 here is a reduced program that still segfaults:

 {-# LANGUAGE Arrows #-}

 import Control.Arrow

 main :: IO ()
 main = print segfault

 segfault :: [()]
 segfault = anythingYouWant ()

 anythingYouWant :: a
 anythingYouWant = testB False (const ()) ()

 testB :: ArrowChoice arrow
   = bool - arrow () () - arrow () anything
 testB bool arrow =
   proc () -
 do if bool then arrow - ()
else arrow - ()

 Sebastian

 On Fri, Aug 5, 2011 at 6:20 AM, Brent Yorgey byor...@seas.upenn.eduwrote:

 On Tue, Aug 02, 2011 at 05:08:33PM -0400, bob zhang wrote:
  hi, all
  testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3
  - t1 a1 t3 - t1 (a, a1) t
  testB f g h = proc (x,y) - do
  if (f x y)then g - x + 1 else h - y + 2
 
  it's very strange that the type of _f_ is (a-a1-t2) which I thought
  should be a - a1 - Bool,
 
  btw, is there any way to get the output of preprocessing using -XArrow
  extensions,
 
  Thanks a lot
  best, bob

 Congratulations, you have definitely found a GHC bug!  Note there are
 actually two things wrong with testB's type signature: first, t2 ought
 to be Bool, as you note.  But even worse, notice that the return type
 of the result arrow, t, has nothing to do with any of the other types!
 This means that we can use testB along with the (-) instance for
 Arrow to construct elements of arbitrary types:

  ghci let anythingYouWant = testB (\x y - False) (const 3) (const 2)
 (2,2)
  ghci :t anythingYouWant
  anythingYouWant :: t
  ghci anythingYouWant :: Integer
  2
  ghci anythingYouWant :: Int
  2
  ghci anythingYouWant :: Double
  1.0e-323
  ghci anythingYouWant :: Char
  '\STX'
  ghci (anythingYouWant :: (Double - Double) - [Double]) sqrt
  [
  [1]17391 segmentation fault  ghci

 whoops!

 I'm using GHC 7.0.3, but Daniel Wagner and I also tried it (with the
 same results) on GHC 7.2.0rc1 and GHC HEAD.

 I wasn't able to find a ticket for this on the GHC bug tracker, I
 guess we should file one!

 I tried to find a way to get the output of preprocessing using -XArrow
 but wasn't able to find one (other than -ddump-ds which gives you the
 unoptimized *GHC core* output, which is quite hard to read).

 -Brent

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



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