RE: build failures when hiding non-visible imports

2012-08-17 Thread Simon Peyton-Jones
| Would it be reasonable to change ghc's behavior to treat this 
| (ie an 'import' statement that hides something that isn't exported) as a
| warning instead of an error?

Yes, that would be easy if it's what everyone wants. Any other opinions?

Simon


| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-
| haskell-users-boun...@haskell.org] On Behalf Of John Lato
| Sent: 17 August 2012 02:13
| To: glasgow-haskell-users@haskell.org
| Subject: build failures when hiding non-visible imports
| 
| Hello,
| 
| One of the issues I've noticed with ghc-7.6 is that a number of
| packages fail due to problematic import statements.  For example, any
| module which uses
| 
|  import Prelude hiding (catch)
| 
| now fails to build with the error
| 
| Module `Prelude' does not export `catch'
| 
| Of course fixing this example is relatively straightforward, but that
| isn't always the case.
| 
| Would it be reasonable to change ghc's behavior to treat this as a
| warning instead of an error?
| 
| Cheers,
| John L.
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADTs in the wild

2012-08-17 Thread Christian Maeder

Am 15.08.2012 23:13, schrieb Yitzchak Gale:

But in my opinion, by far the best solution, using only
GADTs, was submitted by Eric Mertens:

http://hpaste.org/44469/software_stack_puzzle

Eric's solution could now be simplified even further
using data kinds.


Find attached a version (based on Eric's solution) that uses only 
ExistentialQuantification.


data Fun a c = First (a - c)
  | forall b . Serializable b = Fun b c :. (a - b)

instead of:

data Fun :: * - * - * where
   Id   :: Fun a a
   (:.) :: Serializable b = Fun b c - (a - b) - Fun a c

The main problem seems to be to create a dependently typed list of 
functions (the type of the next element depends on the previous one)
For such a list the element type depends on the index, therefore it 
seems not possible to define take and drop over Fun a c and compose it 
like


  serialize . flatten (take n fs) . deserialize

(as would be easily possible with functions of type a - a)

Cheers Christian



Yitz



{-# LANGUAGE ExistentialQuantification #-}
module Puzzle where

import Data.ByteString (ByteString, singleton)

class Serializable a where
  serialize :: a - ByteString
  deserialize :: ByteString - a

data Fun a c = First (a - c)
  | forall b . Serializable b = Fun b c :. (a - b)

infixl 9 :.

-- Simple conversion
flatten :: Fun a b - a - b
flatten (First f) = f
flatten (fs :. f) = flatten fs . f

-- Layering example
runLayers :: (Serializable a, Serializable b)
   = Int - Int - Fun a b - ByteString - ByteString
runLayers n m f = case f of
  fs :. _ | n  1 - runLayers (n - 1) (m - 1) fs
  _ - runLayers' m f . deserialize

runLayers' :: (Serializable a, Serializable b)
  = Int - Fun a b - a - ByteString
runLayers' m f = if m = 1 then serialize else case f of
  fs :. g - runLayers' (m - 1) fs . g
  First g - serialize . g

data Layer1 = Layer1
data Layer2 = Layer2
data Layer3 = Layer3
data Layer4 = Layer4

softwareStack :: Fun Layer1 Layer4
softwareStack =
  First (\ Layer3 - Layer4) :. (\ Layer2 - Layer3) :. (\ Layer1 - Layer2)

example1 = runLayers 2 4 softwareStack (singleton 2)  ==  singleton 4
example2 = runLayers 1 3 softwareStack (singleton 1)  ==  singleton 3

-- Boring serialization instances
instance Serializable Layer1 where
  serialize Layer1 = singleton 1
  deserialize bs | bs == singleton 1 = Layer1
instance Serializable Layer2 where
  serialize Layer2 = singleton 2
  deserialize bs | bs == singleton 2 = Layer2
instance Serializable Layer3 where
  serialize Layer3 = singleton 3
  deserialize bs | bs == singleton 3 = Layer3
instance Serializable Layer4 where
  serialize Layer4 = singleton 4
  deserialize bs | bs == singleton 4 = Layer4
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADTs in the wild

2012-08-17 Thread Christopher Done
Funny, I just solved a problem with GADTs that I couldn't really see how
to do another way.


The context
===

In a fat-client web app (like GMail) you have the need to send requests
back to the server to notify the server or get information back, this is
normally transported in JSON format. For a Haskell setup, it would be:

JavaScript (Client) → JSON → Haskell (Server)

I made Fay, a Haskell subset that compiles to JavaScript to displace
JavaScript in this diagram and now it's:

Haskell (Client) → JSON → Haskell (Server)


Three problems to solve
===

There are three problems that I wanted to solve:

1. Make serialization just work, no writing custom JSON instances or
whatnot. That problem is solved. So I can just write:

get some-request $ \(Foo bar mu) - …

2. Share data type definitions between the client and server code. That
problem is solved, at least I have a solution that I like. It's like
this:

module SharedTypes where
… definitions here …

module Client where
import SharedTypes

module Server where
import SharedTypes

Thus, after any changes to the data types, GHC will force the programmer
to update the server AND the client. This ensures both systems are in
sync with one-another. A big problem when you're working on large
applications, and a nightmare when using JavaScript.

3. Make all requests to the server type-safe, meaning that a given
request type can only have one response type, and every command which is
possible to send the server from the client MUST have a response. I have
a solution with GADTs that I thing is simple and works.


The GADTs part
==

module SharedTypes where

I declare my GADT of commands, forcing the input type and the return
type in the parameters. The Foreign instance is just for Fay to allow
things to be passed to foreign functions.

-- | The command list.
data Command where
  GetFoo :: Double - Returns Foo - Command
  PutFoo :: String - Returns Double - Command
  deriving Read
instance Foreign Command

Where `Returns' is a simple phantom type. We'll see why this is
necessary in a sec.

-- | A phantom type which ensures the connection between the command
-- and the return value.
data Returns a = Returns
  deriving Read

And let's just say Foo is some domain structure of interest:

-- | A foobles return value.
data Foo = Foo { field1 :: Double, field2 :: String, field3 :: Bool }
  deriving Show
instance Foreign Foo

Now in the Server module, I write a request dispatcher:

-- | Dispatch on the commands.
dispatch :: Command - Snap ()
dispatch cmd =
  case cmd of
GetFoo i r - reply r (Foo i Sup? True)

Here is the clever bit. I need to make sure that the response Foo
corresponds to the GetFoo command. So I make sure that any call to
`reply` must give a Returns value. That value will come from the nearest
place; the command being dispatched on. So this, through GHC's pattern
match exhaustion checks, ensures that all commands are handled.

-- | Reply with a command.
reply :: (Foreign a,Show a) = Returns a - a - Snap ()
reply _ = writeLBS . encode . showToFay

And now in the Client module, I wanted to make sure that GetFoo can only
be called with Foo, so I structure the `call` function to require a
Returns value as the last slot in the constructor:

-- | Call a command.
call :: Foreign a = (Returns a - Command) - (a - Fay ()) - Fay ()
call f g = ajaxCommand (f Returns) g

The AJAX command is a regular FFI, no type magic here:

-- | Run the AJAX command.
ajaxCommand :: Foreign a = Command - (a - Fay ()) - Fay ()
ajaxCommand =
  ffi jQuery.ajax({url: '/json', data: %1,\
  dataType: 'json', success : %2 })

And now I can make the call:

-- | Main entry point.
main :: Fay ()
main = call (GetFoo 123) $ \(Foo _ _ _) - return ()


Summary
===

So in summary I achieved these things:

* Automated (no boilerplate writing) generation of serialization for
  the types.
* Client and server share the same types.
* The commands are always in synch.
* Commands that the client can use are always available on the server
  (unless the developer ignored an incomplete-pattern match warning, in
  which case the compiler did all it could and the developer deserves
  it).

I think this approach is OK. I'm not entirely happy about reply r. I'd
like that to be automatic somehow.


Other approaches / future work
==

I did try with:

data Command a where
  GetFoo :: Double - Command Foo
  PutFoo :: String - Command Double

But that became difficult to make an automatic decode instance. I read
some suggestions by Edward Kmett:
http://www.haskell.org/pipermail/haskell-cafe/2010-June/079402.html

But it looked rather hairy to do in an automatic way. If anyone has any
improvements/ideas to achieve this, please let me know.


Re: GADTs in the wild

2012-08-17 Thread Christopher Done
Oh, I went for a walk and realised that while I started with a GADT, I
ended up with a normal Haskell data type in a fancy GADT dress. I'll
get back to you if I get the GADT approach to work.

On 17 August 2012 15:14, Christopher Done chrisd...@gmail.com wrote:
 Funny, I just solved a problem with GADTs that I couldn't really see how
 to do another way.


 The context
 ===

 In a fat-client web app (like GMail) you have the need to send requests
 back to the server to notify the server or get information back, this is
 normally transported in JSON format. For a Haskell setup, it would be:

 JavaScript (Client) → JSON → Haskell (Server)

 I made Fay, a Haskell subset that compiles to JavaScript to displace
 JavaScript in this diagram and now it's:

 Haskell (Client) → JSON → Haskell (Server)


 Three problems to solve
 ===

 There are three problems that I wanted to solve:

 1. Make serialization just work, no writing custom JSON instances or
 whatnot. That problem is solved. So I can just write:

 get some-request $ \(Foo bar mu) - …

 2. Share data type definitions between the client and server code. That
 problem is solved, at least I have a solution that I like. It's like
 this:

 module SharedTypes where
 … definitions here …

 module Client where
 import SharedTypes

 module Server where
 import SharedTypes

 Thus, after any changes to the data types, GHC will force the programmer
 to update the server AND the client. This ensures both systems are in
 sync with one-another. A big problem when you're working on large
 applications, and a nightmare when using JavaScript.

 3. Make all requests to the server type-safe, meaning that a given
 request type can only have one response type, and every command which is
 possible to send the server from the client MUST have a response. I have
 a solution with GADTs that I thing is simple and works.


 The GADTs part
 ==

 module SharedTypes where

 I declare my GADT of commands, forcing the input type and the return
 type in the parameters. The Foreign instance is just for Fay to allow
 things to be passed to foreign functions.

 -- | The command list.
 data Command where
   GetFoo :: Double - Returns Foo - Command
   PutFoo :: String - Returns Double - Command
   deriving Read
 instance Foreign Command

 Where `Returns' is a simple phantom type. We'll see why this is
 necessary in a sec.

 -- | A phantom type which ensures the connection between the command
 -- and the return value.
 data Returns a = Returns
   deriving Read

 And let's just say Foo is some domain structure of interest:

 -- | A foobles return value.
 data Foo = Foo { field1 :: Double, field2 :: String, field3 :: Bool }
   deriving Show
 instance Foreign Foo

 Now in the Server module, I write a request dispatcher:

 -- | Dispatch on the commands.
 dispatch :: Command - Snap ()
 dispatch cmd =
   case cmd of
 GetFoo i r - reply r (Foo i Sup? True)

 Here is the clever bit. I need to make sure that the response Foo
 corresponds to the GetFoo command. So I make sure that any call to
 `reply` must give a Returns value. That value will come from the nearest
 place; the command being dispatched on. So this, through GHC's pattern
 match exhaustion checks, ensures that all commands are handled.

 -- | Reply with a command.
 reply :: (Foreign a,Show a) = Returns a - a - Snap ()
 reply _ = writeLBS . encode . showToFay

 And now in the Client module, I wanted to make sure that GetFoo can only
 be called with Foo, so I structure the `call` function to require a
 Returns value as the last slot in the constructor:

 -- | Call a command.
 call :: Foreign a = (Returns a - Command) - (a - Fay ()) - Fay ()
 call f g = ajaxCommand (f Returns) g

 The AJAX command is a regular FFI, no type magic here:

 -- | Run the AJAX command.
 ajaxCommand :: Foreign a = Command - (a - Fay ()) - Fay ()
 ajaxCommand =
   ffi jQuery.ajax({url: '/json', data: %1,\
   dataType: 'json', success : %2 })

 And now I can make the call:

 -- | Main entry point.
 main :: Fay ()
 main = call (GetFoo 123) $ \(Foo _ _ _) - return ()


 Summary
 ===

 So in summary I achieved these things:

 * Automated (no boilerplate writing) generation of serialization for
   the types.
 * Client and server share the same types.
 * The commands are always in synch.
 * Commands that the client can use are always available on the server
   (unless the developer ignored an incomplete-pattern match warning, in
   which case the compiler did all it could and the developer deserves
   it).

 I think this approach is OK. I'm not entirely happy about reply r. I'd
 like that to be automatic somehow.


 Other approaches / future work
 ==

 I did try with:

 data Command a where
   GetFoo :: Double - Command Foo

Re: GADTs in the wild

2012-08-17 Thread Felipe Almeida Lessa
Christopher, did you ever take a look at acid-state [1]?  It seems to
me that it solves the same problem you have but, instead of

  Client - JSON - Server (going through the web)

it solves

  Server - Storage - Server (going through time)

Cheers,

[1] http://hackage.haskell.org/package/acid-state

-- 
Felipe.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


+RTS -S heap reporting oddity

2012-08-17 Thread Wolfram Kahl
During one of my long Agda runs (with GHC-7.4.2), I observed the following
output, with run-time options

   +RTS -S -H11G -M11G -K256M

:

7694558208  30623864 3833166176  0.11  0.11  234.75  234.7900  (Gen:  0)
7678904688  29295168 3847737784  0.11  0.11  242.04  242.0900  (Gen:  0)
7662481840  29195736 3861451856  0.11  0.11  249.31  249.3500  (Gen:  0)
7647989280  26482704 3872463688  0.12  0.12  256.64  256.6800  (Gen:  0)
4609865360  25764016 3886000448  0.09  0.09  261.04  261.0900  (Gen:  0)
4581294920  19435032 3891512272  0.07  0.07  265.37  265.4200  (Gen:  0)
4568757088  21095864 3902286000  0.08  0.08  269.70  269.7400  (Gen:  0)
4546421608  21618856 3913923976  0.09  0.09  274.04  274.0900  (Gen:  0)
452151 2894668056 3484748224  7.63  7.63  285.94  285.9800  (Gen:  
1)
8085358392  23776128 3499185336  0.11  0.11  293.49  293.5300  (Gen:  0)
8064630856  32055112 3515876576  0.13  0.13  300.91  300.9500  (Gen:  0)
8040500112  31477608 3528105088  0.12  0.12  308.37  308.4100  (Gen:  0)
8031456296  29641328 3540632456  0.11  0.11  315.83  315.8700  (Gen:  0)
8018447264  30187208 3554339600  0.12  0.12  323.26  323.3100  (Gen:  0)

To my untrained eye, this seems to be saying the following:
In the first 4 lines, the heap runs (almost) full before (minor) collections.
In lines 5 to 9 it apparently leaves 3G empty before collection,
but ``those 3G'' then appear on line 9 in the ``amount of data copied during 
(major) collection''
column, and after that it runs up to fill all 11G again before the next few 
minor collections.

What is really going on here?
(Previously I had never seen such big numbers in the second column on major 
collections.)


Wolfram


P.S.: Same effect again, but more dramatic, later during the same Agda run:

448829488   4864536 5710435424  0.02  0.02 1422.80 1422.9000  (Gen:  0)
445544064   3251712 5710248752  0.01  0.01 1423.23 1423.3200  (Gen:  0)
450236784   4148864 5712696848  0.02  0.02 1423.68 1423.7700  (Gen:  0)
445240152   3828120 5713606328  0.02  0.02 1424.10 1424.1900  (Gen:  0)
443285616   5906448 5717731864  0.02  0.02 1424.52 1424.6100  (Gen:  0)
430698248 4773500032 5363214440  9.30  9.30 1434.21 1434.3000  (Gen:  1)
6148455592  13490304 5374609848  0.07  0.07 1439.83 1439.9200  (Gen:  0)
6185350848  27419744 5389326896  0.11  0.11 1445.50 1445.5900  (Gen:  0)
6168805736  23069072 5398725784  0.11  0.11 1451.22 1451.3200  (Gen:  0)
6157744328  23451872 5408370152  0.09  0.09 1456.93 1457.0300  (Gen:  0)
6151715272  25739584 5421044592  0.11  0.11 1462.62 1462.7200  (Gen:  0)
6132589488  24541688 5428809632  0.10  0.10 1468.26 1468.3700  (Gen:  0)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


funny type inference error with ghc7.6rc1

2012-08-17 Thread Carter Schonwald
Hey All,

When playing with the current hackage versions of Epic and Idris to make
them play nice with ghc7.6rc1

http://hackage.haskell.org/package/idris-0.9.2.1
and
http://hackage.haskell.org/package/epic-0.9.3(current version on github
now builds on ghc 7.6, https://github.com/edwinb/EpiVM)

I ran into some funny type inference problems. Namely, using
the idris-0.9.2.1  source and iteratively seeing how ghc complains,
I repeated found that ghc would infer extraneous class constraints with
variables that don't appear in the function type!

eg (Num a, Ord a) = PArg - Doc, when the *correct* type to infer
would  be PArg - Doc.
heres some gists with links to more info
https://gist.github.com/3365312
https://gist.github.com/3365073
https://gist.github.com/3364775

Anyways, I'm not sure what to make of this, is this a reasonable artifact
of  type inference getting confused on functions with a large number of
case analyses when various typeclass extensions are enabled? Or  Is this a
bug in terms of what inference should be able to handle?

Just to be clear, when I add the infererred type ascriptions without the
type class constraint, everything type checks in those modules. So my
confusion is why the inference adding those unused class constraint
variables!

thanks all,
-Carter
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users