Re: build failures when hiding non-visible imports

2012-08-18 Thread Carter Schonwald
meaning: flags for treating it as a warning vs as an error?  (pardon, i'm
over thinking ambiguity in phrasing).
if thats the desired difference, that sounds good to me!

-Carter

On Sat, Aug 18, 2012 at 5:29 PM, Dan Burton wrote:

> Sounds reasonable. We might want flags to go with it for silencing or
> enabling that particular warning.
>
> -- Dan Burton
>
>
> ___
> 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: build failures when hiding non-visible imports

2012-08-18 Thread Dan Burton
Sounds reasonable. We might want flags to go with it for silencing or
enabling that particular warning.

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


Re: build failures when hiding non-visible imports

2012-08-18 Thread Bertram Felgenhauer
Simon Peyton-Jones wrote:
> | 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?

+1 for a warning from me

Bertram

___
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-18 Thread Bertram Felgenhauer
Christopher Done wrote:
> On 18 August 2012 20:57, Bertram Felgenhauer
>  wrote:
> > The natural encoding as a GADT would be as follows:
> >
> > data Command result where
> > GetFoo :: Double -> Command Foo
> > PutFoo :: String -> Command Double
> >
> 
> Right, that's exactly what I wrote at the end of my email.

Sorry, I missed that.

> And then
> indeed dispatch would be `dispatch :: Command a -> Snap a`. But how do
> you derive an instance of Typeable and Read for this data type? The
> Foo and the Double conflict and give a type error.

Right. A useful Read instance can't be implemented at all for the
GADT. I'm unsure about Typeable. You have to provide the instances
for the existential wrapper (SerializableCommand) instead, which defeats
automatic deriving. And this wrapper almost isomorphic to the non-GADT
Command type that you ended up using.

So the trade-off is between some loss of type safety and having to
write boilerplate code.

The obvious question then is how to automate the boilerplate code
generation. In principle, Template Haskell is equipped to deal with
GADTs, but I see little existing work in this direction. There is
derive-gadt on hackage, but at a glance the code is a mess and the main
idea seems to be to provide separate instances for each possible
combination of type constructor and type argument. (So there would be
two Read instances for the type above, Read (Command Foo) and
Read (Command Double)), which is going in the wrong direction.
I suspect that the code will not be useful. Is there anything else?

Best regards,

Bertram

___
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-18 Thread Christopher Done
On 18 August 2012 20:57, Bertram Felgenhauer
 wrote:
> The natural encoding as a GADT would be as follows:
>
> data Command result where
> GetFoo :: Double -> Command Foo
> PutFoo :: String -> Command Double
>

Right, that's exactly what I wrote at the end of my email. And then
indeed dispatch would be `dispatch :: Command a -> Snap a`. But how do
you derive an instance of Typeable and Read for this data type? The
Foo and the Double conflict and give a type error.

___
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-18 Thread Bertram Felgenhauer
Christopher Done wrote:
> 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)
[snip]
> 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

The natural encoding as a GADT would be as follows:

data Command result where
GetFoo :: Double -> Command Foo
PutFoo :: String -> Command Double

For the client/server communication channel, the GADT poses a challenge:
serialisation and deserialisation. The easiest way to overcome that
problem is to use an existential.

data SerializableCommand = forall a. Cmd (Command a)

Ideally, dispatch becomes

dispatch :: Command a -> Snap a
dispatch cmd =
  case cmd of
GetFoo i -> return (Foo i "Sup?" True)
...

But you also have to transfer the result, and there is nothing you can
do with the result returned by 'dispatch'. This can be solved by adding
a suitable constraint to the Command type, say,

data SerializableCommand = forall a. Foreign a => Cmd (Command a)

The client code would use

call :: Foreign a => Command a -> (a -> Fay ()) -> Fay ()
call cmd g = ajaxCommand (Cmd cmd) g

and the server would basically run a loop

server :: (Command a -> Snap a) -> Snap ()
server dispatch = loop where
dispatch' (Cmd command) = do
result <- dispatch command
writeLBS $ encode . showToFay $ result
loop = do
cmd <- nextCommand
dispatch' cmd
loop

(All code is pseudo code, I have not even compiled it.)

Maybe this helps.

Best regards,

Bertram

P.S. The same idea of encoding commands in a GADT forms the basis of
'operational' and 'MonadPrompt' packages on Haskell, which allow to
define abstract monads (by declaring a 'Command' (aka 'Prompt') GADT
specifying the monad's builtin operations) and run them with as many
interpreters as one likes. The earliest work I'm aware of is
Chuan-kai Lin's "Programming monads operationally with Unimo" paper
at ICFP'06.

This usage of a 'Command' GADT can be viewed as a very shallow
application of the expression evaluator pattern, but it has quite a
different flavor in practice.

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