Re: Newtype wrappers

2013-01-22 Thread Gábor Lehel
On Tue, Jan 22, 2013 at 7:41 AM, wren ng thornton w...@freegeek.org wrote:
 On 1/21/13 1:40 AM, Shachaf Ben-Kiki wrote:

 For example:

  {-# LANGUAGE TypeFamilies #-}
  import Unsafe.Coerce

  newtype Id a = MkId { unId :: a }

  {-# RULES fmap unId fmap unId = unsafeCoerce #-}

  data family Foo x y a
  data instance Foo x y (Id a) = FooI x
  data instance Foo x y Bool   = FooB { unB :: y }

  instance Functor (Foo x y) where fmap = undefined


 You can define instances for type functions? Eek!


Only for data families / instances.

-- 
Your ship was destroyed in a monadic eruption.

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


Re: Newtype wrappers

2013-01-21 Thread wren ng thornton

On 1/21/13 1:40 AM, Shachaf Ben-Kiki wrote:

For example:

 {-# LANGUAGE TypeFamilies #-}
 import Unsafe.Coerce

 newtype Id a = MkId { unId :: a }

 {-# RULES fmap unId fmap unId = unsafeCoerce #-}

 data family Foo x y a
 data instance Foo x y (Id a) = FooI x
 data instance Foo x y Bool   = FooB { unB :: y }

 instance Functor (Foo x y) where fmap = undefined


You can define instances for type functions? Eek!

--
Live well,
~wren

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


Re: Newtype wrappers

2013-01-20 Thread wren ng thornton

On 1/14/13 1:09 PM, Simon Peyton-Jones wrote:

Friends

I'd like to propose a way to promote newtypes over their enclosing type.  
Here's the writeup
   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

Any comments?  Below is the problem statement, taken from the above page.

I'd appreciate

* A sense of whether you care. Does this matter?


I care. So far I've gotten around some of the problems by defining 
rewrite rules which take (fmap NT), (fmap unNT), etc into unsafeCoerce. 
I haven't run into the eta problems that I'm aware of, but the 
non-constant-time maps are something that shows up quite a lot.


I'd prefer the second approach since it's cleaner to programmers: No new 
syntax; no namespace pollution. The one problem I could see is that 
there's no way to restrict export of the NTC instance, which may be 
necessary for correctness when the constructors aren't exported due to 
invariants...



* Improvements to the design I propose


I'd suggest the name newtypeCoerce (to match unsafeCoerce) rather than 
newtypeCast. The casting terminology isn't terribly common in Haskell 
(I don't think).


--
Live well,
~wren

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


Re: Newtype wrappers

2013-01-20 Thread wren ng thornton

On 1/14/13 2:47 PM, Stephen Paul Weber wrote:

Somebody claiming to be Simon Peyton-Jones wrote:

 *   For x1 we can write map MkAge x1 :: [Age]. But this does not
follow  the newtype cost model: there will be runtime overhead from
executing the  map at runtime, and sharing will be lost too. Could GHC
optimise the map  somehow?


My friend pointed out something interesting:

If GHC can know that MkAge is just id (in terms of code, not in terms of
type), which seems possible, and if the only interesting case is a
Functor, which seems possible, then a RULE fmap id = id would solve
this.  No?


The problem is precisely that the types don't line up, so that rule 
won't fire. A more accurate mental model is that when we write:


newtype Foo = MkFoo { unFoo :: Bar }

the compiler generates the definitions:

MkFoo :: Bar - Foo
MkFoo = unsafeCoerce

unFoo :: Foo - Bar
unFoo = unsafeCoerce

(among others). So the rule we want is:

fmap unsafeCoerce = unsafeCoerce

Except, there are functions other than fmap which behave specially on 
identity functions. Another major one is (.) where newtypes (but not id) 
introduce an eta-expansion that can ruin performance.


It strikes me that the cleanest solution would be to have GHC explicitly 
distinguish (internally) between identity functions and other 
functions, so that it can ensure that it treats all identity functions 
equally. Where that equality means rewrite rules using id, special 
optimizations about removing id, etc, all carry over to match on other 
identity functions as well.


--
Live well,
~wren

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


Re: Newtype wrappers

2013-01-20 Thread wren ng thornton

On 1/14/13 9:15 PM, Iavor Diatchki wrote:

It looks like what we need is a different concept: one that talks about the
equality of the representations of types, rather then equality of the types
themselves.


+1.

In fact, this distinction is one of the crucial ones I had in mind when 
working on the language I abandoned when I discovered Haskell.  It's 
also something that came up when working on the Dyna language. And now 
it's coming up here. There's a big difference between semantic types and 
representation types; and it sounds like it's high time for working that 
distinction into the compiler (painful though it may be).


--
Live well,
~wren

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


Re: Newtype wrappers

2013-01-20 Thread Shachaf Ben-Kiki
On Sun, Jan 20, 2013 at 8:13 PM, wren ng thornton w...@freegeek.org wrote:
 I care. So far I've gotten around some of the problems by defining rewrite
 rules which take (fmap NT), (fmap unNT), etc into unsafeCoerce. I haven't
 run into the eta problems that I'm aware of, but the non-constant-time maps
 are something that shows up quite a lot.

1. As far as I can tell, the (fmap NT) rewrite rule won't ever fire.
At least, I haven't figured out a way to do it, because newtype
constructors (though not selectors) get turned into unsafeCoerces too
early, before any rewrite rules have a change to fire. See
http://hackage.haskell.org/trac/ghc/ticket/7398.

2. This might not be relevant in your case, but this rule isn't safe
in general -- you can derive unsafeCoerce from it using an invalid
Functor instance.

For example:

{-# LANGUAGE TypeFamilies #-}
import Unsafe.Coerce

newtype Id a = MkId { unId :: a }

{-# RULES fmap unId fmap unId = unsafeCoerce #-}

data family Foo x y a
data instance Foo x y (Id a) = FooI x
data instance Foo x y Bool   = FooB { unB :: y }

instance Functor (Foo x y) where fmap = undefined

coerce :: a - b
coerce = unB . fmap unId . FooI

Even without extensions, this would let you break invariants in types
like Data.Set by defining an invalid Functor instance. This is a
bigger deal than it might seem, given SafeHaskell -- you can't export
this sort of rule from a Trustworthy library.

Shachaf

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


Re: Newtype wrappers

2013-01-15 Thread Gábor Lehel
On Tue, Jan 15, 2013 at 3:15 AM, Iavor Diatchki
iavor.diatc...@gmail.com wrote:
 In general, I was never comfortable with GHC's choice to add an axiom
 equating a newtype and its representation type, because it looks unsound to
 me (without any type-functions or newtype deriving).
 For example, consider:

 newtype T a = MkT Int

 Now, if this generates an axiom asserting that `froall a. T a ~ Int`, then
 we can derive a contradiction:

 T Int ~ Int ~ T Char, and hence `Int ~ Char`.

 It looks like what we need is a different concept: one that talks about the
 equality of the representations of types, rather then equality of the types
 themselves.

 -Iavor

This is what Simon's paper[1] referenced from the wiki is about,
except he uses the terminology the representations of types -
types, the types themselves - codes. (IMHO talking about
representations and types, respectively, would be more
accessible.)

[1] http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/
Generative Type Abstraction and Type-level Computation


-- 
Your ship was destroyed in a monadic eruption.

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


RE: Newtype wrappers

2013-01-15 Thread Simon Peyton-Jones
| If you as the library writer don't want to allow unsafe things, then
| don't export the constructor.  Then no one can break your invariants,
| even with newtype malarky.  If you as the the library user go and
| explicitly import the bare Set constructor from (theoretical)
| Data.Set.Unsafe, then you are in the position to break Set's internal
| invariants anyway, and have already accepted the great power / great
| responsibility tradeoff.

I think that there are two separate things going on here, and that's why the 
discussion is confusing.

Suppose we have

module Map( ... ) where
  data Map a b = ...blah blah...

module Age( ... ) where
  newtype Age = MkAge Int

Now suppose we want a newtype wrapper like this

import Map
import Age

newtype wrap foo :: Map Int Bool - Map Age Bool

Could we write 'foo' by hand? (This is a good criterion, I think.) Only if we 
could see the data constructors of *both* Map *and* Age. In my earlier brief 
message I was only thinking about the 'Age' type, and forgetting about 'Map'.

- If we can't see the data constructor of 'Age' we might miss an invariant that 
Ages are supposed to have.   For example, they might be guaranteed positive.

- If we can't see the data constructors of 'Map', we might miss an invariant of 
Maps. For example, maybe Map is represented as a list of pairs, ordered by the 
keys.  Then, if 'Age' orders in the reverse way to 'Int', it would obviously be 
bad to substitute.

Invariants like these are difficult to encode in the type system, so we use 
exporting the constructors as a proxy for I trust the importer to maintain 
invariants.  The Internals module name convention is a signal that you must 
be particularly careful when importing this module; runtime errors may result 
if you screw up.

One possible conclusion: if we have them at all, newtype wrappers should only 
work if you can see the constructors of *both* the newtype, *and* the type you 
are lifting over.  

But that's not very satisfactory either.  

* There are some times (like IO) where it *does* make perfect sense 
  to lift newtypes, but where we really don't want to expose 
  the representation. 

* Actually 'Map' is also a good example: while Map Age Bool should 
  not be converted to Map Int Bool, it'd be perfectly fine to convert 
  Map Int Age to Map Int Int.

* The criterion must be recursive.  For example if we had
 data Map a b = MkMap (InternalMap a b)
  it's no good being able to see the data constructor MkMap; you need to
  see the constructors of InternalMap too.

The right thing is probably to use kinds, and all this is tantalisingly close 
to the system suggested in Generative type abstraction and type-level 
computation 
(http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/).  Maybe 
we should be able to *declare* Map to be indexed (rather than parametric) in 
its first parameter.

Interesting stuff.

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


Re: Newtype wrappers

2013-01-15 Thread Joachim Breitner
Hi,

Am Montag, den 14.01.2013, 18:09 + schrieb Simon Peyton-Jones:
 I’d appreciate
 
 ·A sense of whether you care. Does this matter?
 ·Improvements to the design I propose

I do care (but that is no news, given my pestering on #2110 :-)) and
obviously I am happy that things are moving.

What I am still missing here is a way for a container library writer to
say:
map Age may be compiled to a noop if foo is known to be a
newtype constructor or deconstructor

With the current proposal, the _user_ of a library has to 
 * know that types Age and Int are actually equivalent
 * introduce and give a name to the [Age] - [Int] wrapper
 * use it wherever map Age is used

The last step can probably replaced by a RULE. But note that all three
steps are a burden on the _user_ of the newtype and the container type
(which most likely come from different libraries). Also, the first step
is a clear breach of abstraction: The user should not have to know
whether Age is a newtype or not, at least not until he wants to actively
work on performance problems, and even then code should not break if a
library switches from newtype to data.

Maybe it is possible to implement this it on top of the current
proposal: How can the author of a container tell the compiler that map
Foo or map unFoo are safe to be replaced by coercions.

One might argue that this yields unpredictable performance. But it is no
different than other successful tools like list fusion: There, as well,
only the authors of different components need to set up the
corresponding RULES. The user can combine independently developed
functions and they will possibly fuse. And the user does not really know
when and where fusion happens, or what list fusion is, but he knows that
generally, good things happen (just as he expects newtypes to be
generally free) and if he needs to know more, he’ll have to read the
core.

But maybe what I am looking for is not a language feature but a core
compiler pass, analyzing the actual code of functions like map and
discovering that map Age = [AgeNTC] is a safe rule.

Greetings,
Joachim


-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Newtype wrappers

2013-01-14 Thread Simon Peyton-Jones
Friends

I'd like to propose a way to promote newtypes over their enclosing type.  
Here's the writeup
  http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

Any comments?  Below is the problem statement, taken from the above page.

I'd appreciate

* A sense of whether you care. Does this matter?

* Improvements to the design I propose

Simon



The problem

Suppose we have

newtype Age = MkAge Int

Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age. Moreover, 
this conversion is a type conversion only, and involves no runtime instructions 
whatsoever. This cost model -- that newtypes are free -- is important to 
Haskell programmers, and encourages them to use newtypes freely to express type 
distinctions without introducing runtime overhead.

Alas, the newtype cost model breaks down when we involve other data structures. 
Suppose we have these declarations

data T a   = TLeaf a | TNode (Tree a) (Tree a)

data S m a = SLeaf (m a) | SNode (S m a) (S m a)

and we have these variables in scope

x1 :: [Int]

x2 :: Char - Int

x3 :: T Int

x4 :: S IO Int

Can we convert these into the corresponding forms where the Int is replaced by 
Age? Alas, not easily, and certainly not without overhead.

  *   For x1 we can write map MkAge x1 :: [Age]. But this does not follow the 
newtype cost model: there will be runtime overhead from executing the map at 
runtime, and sharing will be lost too. Could GHC optimise the map somehow? This 
is hard; apart from anything else, how would GHC know that map was special? And 
it it gets worse.

  *   For x2 we'd have to eta-expand: (\y - MkAge (x2 y)) :: Char - Age. But 
this isn't good either, because eta exapansion isn't semantically valid (if x2 
was bottom, seq could distinguish the two). See 
#7542http://hackage.haskell.org/trac/ghc/ticket/7542 for a real life example.

  *   For x3, we'd have to map over T, thus mapT MkAge x3. But what if mapT 
didn't exist? We'd have to make it. And not all data types have maps. S is a 
harder one: you could only map over S-values if m was a functor. There's a lot 
of discussion abou this on 
#2110http://hackage.haskell.org/trac/ghc/ticket/2110.

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


Re: Newtype wrappers

2013-01-14 Thread Stephen Paul Weber

Somebody claiming to be Simon Peyton-Jones wrote:
I'd like to propose a way to promote newtypes over their enclosing type.  
Here's the writeup

 http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers


The high-level idea, I love.  I always wondered about `map MkAge blah`.


Any comments?  Below is the problem statement, taken from the above page.


-1 to the unsoundness, but as you say, this is an existing problem.

Also, instead of:

newtype wrap somefun :: [Int] - [Age]
foo = somefun [12,14]

Maybe:

foo = ([12, 14] :: newtype wrap [Age])

I don't know how feasible this syntax is, but I like it a lot better, and it 
makes it more clear (to me) that this is purely type-level syntax.


--
Stephen Paul Weber, @singpolyma
See http://singpolyma.net for how I prefer to be contacted
edition right joseph


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


Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
Many of us definitely care. =)

The main concern that I would have is that the existing solutions to this
problem could be implemented while retaining SafeHaskell, and I don't see
how a library that uses this can ever recover its SafeHaskell guarantee.

Here is a straw man example of a solution that permits SafeHaskell in the
resulting code that may be useful in addition to or in lieu of your
proposed approach:

We could extend Data.Functor with an fmap# operation that was only, say,
exposed via Data.Functor.Unsafe:

{-# LANGUAGE Unsafe, MagicHash #-}
module Data.Functor.Unsafe where
class Functor f where
  fmap# :: (a - b) - f a - f b
  fmap :: (a - b) - f a - f b
  ($) :: b - f a - f b
  fmap# = \f - \fa - fa `seq` fmap f p

Then we flag Data.Functor as Trustworthy and export just the safe subset:

{-# LANGUAGE Trustworthy #-}
module Data.Functor (Functor(fmap,($))) where
import Data.Functor.Unsafe

then fmap# from Data.Functor.Unsafe is allowed to be fmap# _ = unsafeCoerce
for any Functor that doesn't perform GADT-like interrogation of its
argument (this could be assumed automatically in DeriveFunctor, which can't
handle those cases anyways!)

Then any user who wants to enable a more efficient fmap for fmapping over
his data type with a newtype instantiates fmap# for his Functor. They'd
have to claim Trustworthy (or use the enhanced DeriveFunctor), to discharge
the obligation that they aren't introducing an unsafeCoerce that is visible
to the user. (After all the user has to import another Unsafe module to get
access to fmap# to invoke it.)

Finally then code that is willing to trust other trustworthy code can claim
to be Trustworthy in turn, import Data.Functor.Unsafe and use fmap# for
newtypes and impossible arguments:

{-# LANGUAGE Trustworthy #-}
module Data.Void where

import Data.Functor.Unsafe

newtype Void = Void Void deriving Functor

absurd :: Void - a
absurd (Void a) = absurd a

vacuous :: Functor f = f Void - f a
vacuous = fmap# absurd

This becomes valuable when data types like Void are used to mark the
absence of variables in a syntax tree, which could be quite large.

Currently we have to fmap absurd over the tree, paying an asymptotic cost
for not using (forall a. Expr a) or some newtype wrapped equivalent as our
empty-expression type.

This would dramatically improve the performance of libraries like bound
which commonly use constructions like Expr Void.

Its safety could be built upon by making another class for tracking
newtypes etc so we can know whats safe to pass to fmap#, and you might be
able to spot opportunities to rewrite an explicit fmap of something that is
a `cast` in the core to a call to fmap#.

-Edward

On Mon, Jan 14, 2013 at 1:09 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Friends

 ** **

 I’d like to propose a way to “promote” newtypes over their enclosing
 type.  Here’s the writeup

   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

 ** **

 Any comments?  Below is the problem statement, taken from the above page.*
 ***

 ** **

 I’d appreciate

 **· **A sense of whether you care. Does this matter?

 **· **Improvements to the design I propose

 ** **

 Simon

 ** **

 ** **

 ** **

 *The problem*

 Suppose we have 

 newtype Age = MkAge Int

 Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age.
 Moreover, this conversion is a type conversion only, and involves no
 runtime instructions whatsoever. This cost model -- that newtypes are free
 -- is important to Haskell programmers, and encourages them to use newtypes
 freely to express type distinctions without introducing runtime overhead.
 

 Alas, the newtype cost model breaks down when we involve other data
 structures. Suppose we have these declarations 

 data T a   = TLeaf a | TNode (Tree a) (Tree a)

 data S m a = SLeaf (m a) | SNode (S m a) (S m a)

 and we have these variables in scope 

 x1 :: [Int]

 x2 :: Char - Int

 x3 :: T Int

 x4 :: S IO Int

 Can we convert these into the corresponding forms where the Int is
 replaced by Age? Alas, not easily, and certainly not without overhead. ***
 *

- For x1 we can write map MkAge x1 :: [Age]. But this does not follow
the newtype cost model: there will be runtime overhead from executing the
map at runtime, and sharing will be lost too. Could GHC optimise the
map somehow? This is hard; apart from anything else, how would GHC
know that map was special? And it it gets worse. 


- For x2 we'd have to eta-expand: (\y - MkAge (x2 y)) :: Char - Age.
But this isn't good either, because eta exapansion isn't semantically valid
(if x2 was bottom, seq could distinguish the two). See 
 #7542http://hackage.haskell.org/trac/ghc/ticket/7542for a real life example.



- For x3, we'd have to map over T, thus mapT MkAge x3. But what if 
 mapTdidn't exist? We'd have to make it. And not all data types 

Re: Newtype wrappers

2013-01-14 Thread Herbert Valerio Riedel
Simon Peyton-Jones simo...@microsoft.com writes:

[...]

 x1 :: [Int]

 x2 :: Char - Int

 x3 :: T Int

 x4 :: S IO Int

 Can we convert these into the corresponding forms where the Int is
 replaced by Age? Alas, not easily, and certainly not without overhead

Maybe a stupid question: Can unsafeCoerce accomplish (albeit in an
unsafe way) the desired Int-to-Age type conversion for x1,x2,x3,x4
already now? How does unsafeCoerce relate to the proposal at hand?

Cheers,
  hvr

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


Re: Newtype wrappers

2013-01-14 Thread Roman Cheplyaka
* Simon Peyton-Jones simo...@microsoft.com [2013-01-14 18:09:50+]
 Friends
 
 I'd like to propose a way to promote newtypes over their enclosing type.  
 Here's the writeup
   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers
 
 Any comments?

Why not just have a pseudo-function 'coerce'?

By pseudo-function I mean something that can be used anywhere (or almost
anywhere?) where a function can, but is a keyword and doesn't have a
type. (It'd be similar to ($) as implemented by GHC, I figure.)

The static semantics would be to compute the inner and outer types
to the extent possible, and then behave as if the function was defined
as a wrapper or unwrapper function for those types. In case when it is
ambiguous, an error is issued, and the standard tricks can be used to
refine the type (including annotation coerce itself with a type).

I realise the implementation may be not as simple as it sounds to
me... If the inference part is hard, then just always require a type
annotation.

Benefits:

* very lightweight syntax, doesn't require additional declarations

* anonymous (doesn't require making up a new name)

* removes the strange distinction between wrap and unwrap
  (aren't the types equivalent anyway?)

Roman

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


Re: Newtype wrappers

2013-01-14 Thread Andrea Vezzosi
On Mon, Jan 14, 2013 at 7:09 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Friends

 ** **

 I’d like to propose a way to “promote” newtypes over their enclosing
 type.  Here’s the writeup

   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

 ** **

 Any comments?  Below is the problem statement, taken from the above page.


Have you considered the effect on types like Data.Set that use the
uniqueness of typeclass instances to maintain invariants? e.g. even when we
have newtype X = X Y coercing Set X to Set Y can produce a tree with
the wrong shape for the Ord instance of Y.



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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 11:14 AM, Andrea Vezzosi sanzhi...@gmail.com wrote:
 Have you considered the effect on types like Data.Set that use the
 uniqueness of typeclass instances to maintain invariants? e.g. even when we
 have newtype X = X Y coercing Set X to Set Y can produce a tree with
 the wrong shape for the Ord instance of Y.

I was just going to say that. Changing newtypes changes instances,
which isn't safe in the general case.

-- Johan

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


Re: Newtype wrappers

2013-01-14 Thread Stephen Paul Weber

Somebody claiming to be Simon Peyton-Jones wrote:
 *   For x1 we can write map MkAge x1 :: [Age]. But this does not follow 
 the newtype cost model: there will be runtime overhead from executing the 
 map at runtime, and sharing will be lost too. Could GHC optimise the map 
 somehow?


My friend pointed out something interesting:

If GHC can know that MkAge is just id (in terms of code, not in terms of 
type), which seems possible, and if the only interesting case is a Functor, 
which seems possible, then a RULE fmap id = id would solve this.  No?


--
Stephen Paul Weber, @singpolyma
See http://singpolyma.net for how I prefer to be contacted
edition right joseph


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


Re: Newtype wrappers

2013-01-14 Thread Mikhail Glushenkov
Hello,

On Mon, Jan 14, 2013 at 8:14 PM, Andrea Vezzosi sanzhi...@gmail.com wrote:

 Have you considered the effect on types like Data.Set that use the
 uniqueness of typeclass instances to maintain invariants? e.g. even when we
 have newtype X = X Y coercing Set X to Set Y can produce a tree with
 the wrong shape for the Ord instance of Y.

But isn't this already possible via GeneralizedNewtypeDeriving?


-- 
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: Newtype wrappers

2013-01-14 Thread Gershom Bazerman

On 1/14/13 2:42 PM, Johan Tibell wrote:

On Mon, Jan 14, 2013 at 11:14 AM, Andrea Vezzosi sanzhi...@gmail.com wrote:

Have you considered the effect on types like Data.Set that use the
uniqueness of typeclass instances to maintain invariants? e.g. even when we
have newtype X = X Y coercing Set X to Set Y can produce a tree with
the wrong shape for the Ord instance of Y.

I was just going to say that. Changing newtypes changes instances,
which isn't safe in the general case.



Perhaps it would be useful for data structures that need to remain 
opaque/abstract to be allowed to declare such explicitly, either with 
special syntax, or a distinguished pragma?


Also, I'm fond of Roman's coerce proposal, because I can imagine cases 
where explicit declaration of wrap/unwrap functions might not 
necessarily make sense. My understanding of the lens library, for 
example, is that it builds up chains of coercions compositionally. In 
such a case, even if we've eliminated the eta issue for a *single* 
coercion, we'd still have it across a chain of them? Meanwhile, a single 
coerce whose semantics were like unsafeCoerce (but only when it's 
safe!) would do the job just fine at any level.


That said, I think the general direction of this proposal is great, and 
I hope we can work out the kinks and get it implemented.


--Gershom

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


RE: Newtype wrappers

2013-01-14 Thread Simon Peyton-Jones
If you are worrying about #1496, don’t worry; we must fix that, and the fix 
will apply to newtype wrappers.

If you are worrying about something else, can you articulate what the something 
else is?

I don’t want to involve type classes, nor Functor.  We don’t even have a good 
way to say “is a functor of its second type argument” for a type constructor of 
three arguments.

Simon



From: Edward Kmett [mailto:ekm...@gmail.com]
Sent: 14 January 2013 18:39
To: Simon Peyton-Jones
Cc: GHC users
Subject: Re: Newtype wrappers

Many of us definitely care. =)

The main concern that I would have is that the existing solutions to this 
problem could be implemented while retaining SafeHaskell, and I don't see how a 
library that uses this can ever recover its SafeHaskell guarantee.

Here is a straw man example of a solution that permits SafeHaskell in the 
resulting code that may be useful in addition to or in lieu of your proposed 
approach:

We could extend Data.Functor with an fmap# operation that was only, say, 
exposed via Data.Functor.Unsafe:

{-# LANGUAGE Unsafe, MagicHash #-}
module Data.Functor.Unsafe where
class Functor f where
  fmap# :: (a - b) - f a - f b
  fmap :: (a - b) - f a - f b
  ($) :: b - f a - f b
  fmap# = \f - \fa - fa `seq` fmap f p

Then we flag Data.Functor as Trustworthy and export just the safe subset:

{-# LANGUAGE Trustworthy #-}
module Data.Functor (Functor(fmap,($))) where
import Data.Functor.Unsafe

then fmap# from Data.Functor.Unsafe is allowed to be fmap# _ = unsafeCoerce for 
any Functor that doesn't perform GADT-like interrogation of its argument (this 
could be assumed automatically in DeriveFunctor, which can't handle those cases 
anyways!)

Then any user who wants to enable a more efficient fmap for fmapping over his 
data type with a newtype instantiates fmap# for his Functor. They'd have to 
claim Trustworthy (or use the enhanced DeriveFunctor), to discharge the 
obligation that they aren't introducing an unsafeCoerce that is visible to the 
user. (After all the user has to import another Unsafe module to get access to 
fmap# to invoke it.)

Finally then code that is willing to trust other trustworthy code can claim to 
be Trustworthy in turn, import Data.Functor.Unsafe and use fmap# for newtypes 
and impossible arguments:

{-# LANGUAGE Trustworthy #-}
module Data.Void where

import Data.Functor.Unsafe

newtype Void = Void Void deriving Functor

absurd :: Void - a
absurd (Void a) = absurd a

vacuous :: Functor f = f Void - f a
vacuous = fmap# absurd

This becomes valuable when data types like Void are used to mark the absence of 
variables in a syntax tree, which could be quite large.

Currently we have to fmap absurd over the tree, paying an asymptotic cost for 
not using (forall a. Expr a) or some newtype wrapped equivalent as our 
empty-expression type.

This would dramatically improve the performance of libraries like bound which 
commonly use constructions like Expr Void.

Its safety could be built upon by making another class for tracking newtypes 
etc so we can know whats safe to pass to fmap#, and you might be able to spot 
opportunities to rewrite an explicit fmap of something that is a `cast` in the 
core to a call to fmap#.

-Edward

On Mon, Jan 14, 2013 at 1:09 PM, Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
Friends

I’d like to propose a way to “promote” newtypes over their enclosing type.  
Here’s the writeup
  http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

Any comments?  Below is the problem statement, taken from the above page.

I’d appreciate

• A sense of whether you care. Does this matter?

• Improvements to the design I propose

Simon



The problem

Suppose we have

newtype Age = MkAge Int

Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age. Moreover, 
this conversion is a type conversion only, and involves no runtime instructions 
whatsoever. This cost model -- that newtypes are free -- is important to 
Haskell programmers, and encourages them to use newtypes freely to express type 
distinctions without introducing runtime overhead.

Alas, the newtype cost model breaks down when we involve other data structures. 
Suppose we have these declarations

data T a   = TLeaf a | TNode (Tree a) (Tree a)

data S m a = SLeaf (m a) | SNode (S m a) (S m a)

and we have these variables in scope

x1 :: [Int]

x2 :: Char - Int

x3 :: T Int

x4 :: S IO Int

Can we convert these into the corresponding forms where the Int is replaced by 
Age? Alas, not easily, and certainly not without overhead.

  *   For x1 we can write map MkAge x1 :: [Age]. But this does not follow the 
newtype cost model: there will be runtime overhead from executing the map at 
runtime, and sharing will be lost too. Could GHC optimise the map somehow? This 
is hard; apart from anything else, how would GHC know that map was special? And 
it it gets worse.

  *   For x2 we'd have to eta-expand: (\y - MkAge (x2 y

RE: Newtype wrappers

2013-01-14 Thread Simon Peyton-Jones
Have you considered the effect on types like Data.Set that use the uniqueness 
of typeclass instances to maintain invariants? e.g. even when we have newtype 
X = X Y coercing Set X to Set Y can produce a tree with the wrong shape 
for the Ord instance of Y.

Good point. I should add this.  The wrapper should only work if the relevant 
data constructors are in scope; rather like GHC's existing auto-unwrapping on 
foreign calls 
(http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html#ffi-newtype-io)

So then hiding the data constructor maintains the abstraction as indeed it 
should.

Simon

From: Andrea Vezzosi [mailto:sanzhi...@gmail.com]
Sent: 14 January 2013 19:15
To: Simon Peyton-Jones
Cc: GHC users
Subject: Re: Newtype wrappers

On Mon, Jan 14, 2013 at 7:09 PM, Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
Friends

I'd like to propose a way to promote newtypes over their enclosing type.  
Here's the writeup
  http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

Any comments?  Below is the problem statement, taken from the above page.

Have you considered the effect on types like Data.Set that use the uniqueness 
of typeclass instances to maintain invariants? e.g. even when we have newtype 
X = X Y coercing Set X to Set Y can produce a tree with the wrong shape 
for the Ord instance of Y.



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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 1:19 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Have you considered the effect on types like Data.Set that use the
 uniqueness of typeclass instances to maintain invariants? e.g. even when we
 have newtype X = X Y coercing Set X to Set Y can produce a tree with
 the wrong shape for the Ord instance of Y.



 Good point. I should add this.  The wrapper should only work if the relevant
 data constructors are in scope; rather like GHC’s existing auto-unwrapping
 on foreign calls
 (http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html#ffi-newtype-io)

I don't follow. Are you saying that adding an import, even if nothing
from that import is used, can effect if the program compiles?

Does that mean if we ever add Data.Map.Internal that exposes the data
constructors to users who know what they're doing (i.e. are willing
to take it upon themselves to maintain the invariants) then code that
used to compile will stop to do so?

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


Re: Newtype wrappers

2013-01-14 Thread Roman Cheplyaka
* Johan Tibell johan.tib...@gmail.com [2013-01-14 13:32:54-0800]
 On Mon, Jan 14, 2013 at 1:19 PM, Simon Peyton-Jones
 simo...@microsoft.com wrote:
  Have you considered the effect on types like Data.Set that use the
  uniqueness of typeclass instances to maintain invariants? e.g. even when we
  have newtype X = X Y coercing Set X to Set Y can produce a tree with
  the wrong shape for the Ord instance of Y.
 
 
 
  Good point. I should add this.  The wrapper should only work if the relevant
  data constructors are in scope; rather like GHC’s existing auto-unwrapping
  on foreign calls
  (http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html#ffi-newtype-io)
 
 I don't follow. Are you saying that adding an import, even if nothing
 from that import is used, can effect if the program compiles?
 
 Does that mean if we ever add Data.Map.Internal that exposes the data
 constructors to users who know what they're doing (i.e. are willing
 to take it upon themselves to maintain the invariants) then code that
 used to compile will stop to do so?

Now I don't follow you. Why will it stop compiling?

If you define wrappers/unwrappers involving Data.Map, then they will
compile if Data.Map.Internal is imported and will not compile if it isn't.

Roman

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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 1:45 PM, Roman Cheplyaka r...@ro-che.info wrote:
 * Johan Tibell johan.tib...@gmail.com [2013-01-14 13:32:54-0800]
 On Mon, Jan 14, 2013 at 1:19 PM, Simon Peyton-Jones
 simo...@microsoft.com wrote:
  Have you considered the effect on types like Data.Set that use the
  uniqueness of typeclass instances to maintain invariants? e.g. even when we
  have newtype X = X Y coercing Set X to Set Y can produce a tree with
  the wrong shape for the Ord instance of Y.
 
 
 
  Good point. I should add this.  The wrapper should only work if the 
  relevant
  data constructors are in scope; rather like GHC’s existing auto-unwrapping
  on foreign calls
  (http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html#ffi-newtype-io)

 I don't follow. Are you saying that adding an import, even if nothing
 from that import is used, can effect if the program compiles?

 Does that mean if we ever add Data.Map.Internal that exposes the data
 constructors to users who know what they're doing (i.e. are willing
 to take it upon themselves to maintain the invariants) then code that
 used to compile will stop to do so?

 Now I don't follow you. Why will it stop compiling?

 If you define wrappers/unwrappers involving Data.Map, then they will
 compile if Data.Map.Internal is imported and will not compile if it isn't.

Let me rephrase: how will Simon's proposed data constructors are in
scope mechanism work? For example, will

let xs :: Map = ...
in map MyNewtype xs

behave differently if the constructors of Map are in scope or not?

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


Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
It sounds like the solution you are proposing then is to an issue largely
orthogonal to the one I'm talking about.

As far as I can tell, I derive no immediate benefit from this version.

-Edward

On Mon, Jan 14, 2013 at 4:09 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  If you are worrying about #1496, don’t worry; we must fix that, and the
 fix will apply to newtype wrappers.


 If you are worrying about something else, can you articulate what the
 something else is?

 ** **

 I don’t want to involve type classes, nor Functor.  We don’t even have a
 good way to say “is a functor of its second type argument” for a type
 constructor of three arguments.

 ** **

 Simon

 ** **

 ** **

 ** **

 *From:* Edward Kmett [mailto:ekm...@gmail.com]
 *Sent:* 14 January 2013 18:39
 *To:* Simon Peyton-Jones
 *Cc:* GHC users
 *Subject:* Re: Newtype wrappers

 ** **

 Many of us definitely care. =)

 ** **

 The main concern that I would have is that the existing solutions to this
 problem could be implemented while retaining SafeHaskell, and I don't see
 how a library that uses this can ever recover its SafeHaskell guarantee.**
 **

 ** **

 Here is a straw man example of a solution that permits SafeHaskell in the
 resulting code that may be useful in addition to or in lieu of your
 proposed approach:

 ** **

 We could extend Data.Functor with an fmap# operation that was only, say,
 exposed via Data.Functor.Unsafe:

 ** **

 {-# LANGUAGE Unsafe, MagicHash #-}

 module Data.Functor.Unsafe where

 class Functor f where

   fmap# :: (a - b) - f a - f b

   fmap :: (a - b) - f a - f b

   ($) :: b - f a - f b

   fmap# = \f - \fa - fa `seq` fmap f p

 ** **

 Then we flag Data.Functor as Trustworthy and export just the safe subset:*
 ***

 ** **

 {-# LANGUAGE Trustworthy #-}

 module Data.Functor (Functor(fmap,($))) where

 import Data.Functor.Unsafe

 ** **

 then fmap# from Data.Functor.Unsafe is allowed to be fmap# _ =
 unsafeCoerce for any Functor that doesn't perform GADT-like interrogation
 of its argument (this could be assumed automatically in DeriveFunctor,
 which can't handle those cases anyways!)

 ** **

 Then any user who wants to enable a more efficient fmap for fmapping over
 his data type with a newtype instantiates fmap# for his Functor. They'd
 have to claim Trustworthy (or use the enhanced DeriveFunctor), to discharge
 the obligation that they aren't introducing an unsafeCoerce that is visible
 to the user. (After all the user has to import another Unsafe module to get
 access to fmap# to invoke it.)

 ** **

 Finally then code that is willing to trust other trustworthy code can
 claim to be Trustworthy in turn, import Data.Functor.Unsafe and use fmap#
 for newtypes and impossible arguments:

 ** **

 {-# LANGUAGE Trustworthy #-}

 module Data.Void where

 ** **

 import Data.Functor.Unsafe

 ** **

 newtype Void = Void Void deriving Functor

 ** **

 absurd :: Void - a

 absurd (Void a) = absurd a

 ** **

 vacuous :: Functor f = f Void - f a

 vacuous = fmap# absurd

 ** **

 This becomes valuable when data types like Void are used to mark the
 absence of variables in a syntax tree, which could be quite large.

 ** **

 Currently we have to fmap absurd over the tree, paying an asymptotic cost
 for not using (forall a. Expr a) or some newtype wrapped equivalent as our
 empty-expression type.

 ** **

 This would dramatically improve the performance of libraries like bound
 which commonly use constructions like Expr Void.

 ** **

 Its safety could be built upon by making another class for tracking
 newtypes etc so we can know whats safe to pass to fmap#, and you might be
 able to spot opportunities to rewrite an explicit fmap of something that is
 a `cast` in the core to a call to fmap#.

 ** **

 -Edward

 ** **

 On Mon, Jan 14, 2013 at 1:09 PM, Simon Peyton-Jones simo...@microsoft.com
 wrote:

 Friends

  

 I’d like to propose a way to “promote” newtypes over their enclosing
 type.  Here’s the writeup

   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

  

 Any comments?  Below is the problem statement, taken from the above page.*
 ***

  

 I’d appreciate

 · A sense of whether you care. Does this matter?

 · Improvements to the design I propose

  

 Simon

  

  

  

 *The problem*

 Suppose we have 

 newtype Age = MkAge Int

 Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age.
 Moreover, this conversion is a type conversion only, and involves no
 runtime instructions whatsoever. This cost model -- that newtypes are free
 -- is important to Haskell programmers, and encourages them to use newtypes
 freely to express type distinctions without introducing runtime overhead.
 

 Alas, the newtype cost model breaks down when we

Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 2:33 PM, Roman Cheplyaka r...@ro-che.info wrote:
 * Johan Tibell johan.tib...@gmail.com [2013-01-14 14:29:57-0800]
 Let me rephrase: how will Simon's proposed data constructors are in
 scope mechanism work? For example, will

 let xs :: Map = ...
 in map MyNewtype xs

 behave differently if the constructors of Map are in scope or not?

 Coercion is never implicit. In Simon's original proposal, for example,
 you need to define coercion functions using a special syntax.

 So this code will always work in the same, traditional way.

I'm completely lost. What is Simon's proposal?

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


Re: Newtype wrappers

2013-01-14 Thread Roman Cheplyaka
* Johan Tibell johan.tib...@gmail.com [2013-01-14 14:55:31-0800]
 On Mon, Jan 14, 2013 at 2:33 PM, Roman Cheplyaka r...@ro-che.info wrote:
  * Johan Tibell johan.tib...@gmail.com [2013-01-14 14:29:57-0800]
  Let me rephrase: how will Simon's proposed data constructors are in
  scope mechanism work? For example, will
 
  let xs :: Map = ...
  in map MyNewtype xs
 
  behave differently if the constructors of Map are in scope or not?
 
  Coercion is never implicit. In Simon's original proposal, for example,
  you need to define coercion functions using a special syntax.
 
  So this code will always work in the same, traditional way.
 
 I'm completely lost. What is Simon's proposal?

It's described here:
http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

Roman

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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 2:57 PM, Roman Cheplyaka r...@ro-che.info wrote:
 It's described here:
 http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

We seem to be talking past each other. There's a specific problem
related to type classes and invariants on data types mentioned earlier
on this thread. Simon's solution here seems to be that we only coerce
a structure from one newtype to the base type if the constructors are
exposed, hence my question if the code changes semantics due to adding
imports.

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


Re: Newtype wrappers

2013-01-14 Thread Evan Laforge
On Mon, Jan 14, 2013 at 3:11 PM, Johan Tibell johan.tib...@gmail.com wrote:
 On Mon, Jan 14, 2013 at 2:57 PM, Roman Cheplyaka r...@ro-che.info wrote:
 It's described here:
 http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

 We seem to be talking past each other. There's a specific problem
 related to type classes and invariants on data types mentioned earlier
 on this thread. Simon's solution here seems to be that we only coerce
 a structure from one newtype to the base type if the constructors are
 exposed, hence my question if the code changes semantics due to adding
 imports.

I assume it would change from doesn't compile to works if you add
the required import.  It's the same as the FFI thing, right?  If you
don't import M (T(..)), then 'foreign ... :: T - IO ()' gives an
error, but import it and coerces T to its underlying type (hopefully
that's a C type).

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


Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
Actually upon reflection, this does appear to help with implementing some
things in my code with a much reduced unsafeCoerce count, though it remains
orthogonal to the issue of how to lift these things through third-party
types that I raised above.

-Edward

On Mon, Jan 14, 2013 at 5:40 PM, Edward Kmett ekm...@gmail.com wrote:

 It sounds like the solution you are proposing then is to an issue largely
 orthogonal to the one I'm talking about.

 As far as I can tell, I derive no immediate benefit from this version.

 -Edward

 On Mon, Jan 14, 2013 at 4:09 PM, Simon Peyton-Jones simo...@microsoft.com
  wrote:

  If you are worrying about #1496, don’t worry; we must fix that, and the
 fix will apply to newtype wrappers.


 If you are worrying about something else, can you articulate what the
 something else is?

 ** **

 I don’t want to involve type classes, nor Functor.  We don’t even have a
 good way to say “is a functor of its second type argument” for a type
 constructor of three arguments.

 ** **

 Simon

 ** **

 ** **

 ** **

 *From:* Edward Kmett [mailto:ekm...@gmail.com]
 *Sent:* 14 January 2013 18:39
 *To:* Simon Peyton-Jones
 *Cc:* GHC users
 *Subject:* Re: Newtype wrappers

 ** **

 Many of us definitely care. =)

 ** **

 The main concern that I would have is that the existing solutions to this
 problem could be implemented while retaining SafeHaskell, and I don't see
 how a library that uses this can ever recover its SafeHaskell guarantee.*
 ***

 ** **

 Here is a straw man example of a solution that permits SafeHaskell in the
 resulting code that may be useful in addition to or in lieu of your
 proposed approach:

 ** **

 We could extend Data.Functor with an fmap# operation that was only, say,
 exposed via Data.Functor.Unsafe:

 ** **

 {-# LANGUAGE Unsafe, MagicHash #-}

 module Data.Functor.Unsafe where

 class Functor f where

   fmap# :: (a - b) - f a - f b

   fmap :: (a - b) - f a - f b

   ($) :: b - f a - f b

   fmap# = \f - \fa - fa `seq` fmap f p

 ** **

 Then we flag Data.Functor as Trustworthy and export just the safe subset:
 

 ** **

 {-# LANGUAGE Trustworthy #-}

 module Data.Functor (Functor(fmap,($))) where

 import Data.Functor.Unsafe

 ** **

 then fmap# from Data.Functor.Unsafe is allowed to be fmap# _ =
 unsafeCoerce for any Functor that doesn't perform GADT-like interrogation
 of its argument (this could be assumed automatically in DeriveFunctor,
 which can't handle those cases anyways!)

 ** **

 Then any user who wants to enable a more efficient fmap for fmapping over
 his data type with a newtype instantiates fmap# for his Functor. They'd
 have to claim Trustworthy (or use the enhanced DeriveFunctor), to discharge
 the obligation that they aren't introducing an unsafeCoerce that is visible
 to the user. (After all the user has to import another Unsafe module to get
 access to fmap# to invoke it.)

 ** **

 Finally then code that is willing to trust other trustworthy code can
 claim to be Trustworthy in turn, import Data.Functor.Unsafe and use fmap#
 for newtypes and impossible arguments:

 ** **

 {-# LANGUAGE Trustworthy #-}

 module Data.Void where

 ** **

 import Data.Functor.Unsafe

 ** **

 newtype Void = Void Void deriving Functor

 ** **

 absurd :: Void - a

 absurd (Void a) = absurd a

 ** **

 vacuous :: Functor f = f Void - f a

 vacuous = fmap# absurd

 ** **

 This becomes valuable when data types like Void are used to mark the
 absence of variables in a syntax tree, which could be quite large.

 ** **

 Currently we have to fmap absurd over the tree, paying an asymptotic cost
 for not using (forall a. Expr a) or some newtype wrapped equivalent as our
 empty-expression type.

 ** **

 This would dramatically improve the performance of libraries like bound
 which commonly use constructions like Expr Void.

 ** **

 Its safety could be built upon by making another class for tracking
 newtypes etc so we can know whats safe to pass to fmap#, and you might be
 able to spot opportunities to rewrite an explicit fmap of something that is
 a `cast` in the core to a call to fmap#.

 ** **

 -Edward

 ** **

 On Mon, Jan 14, 2013 at 1:09 PM, Simon Peyton-Jones 
 simo...@microsoft.com wrote:

 Friends

  

 I’d like to propose a way to “promote” newtypes over their enclosing
 type.  Here’s the writeup

   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

  

 Any comments?  Below is the problem statement, taken from the above page.
 

  

 I’d appreciate

 · A sense of whether you care. Does this matter?

 · Improvements to the design I propose

  

 Simon

  

  

  

 *The problem*

 Suppose we have 

 newtype Age = MkAge Int

 Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age.
 Moreover

Re: Newtype wrappers

2013-01-14 Thread Roman Cheplyaka
* Johan Tibell johan.tib...@gmail.com [2013-01-14 15:11:25-0800]
 On Mon, Jan 14, 2013 at 2:57 PM, Roman Cheplyaka r...@ro-che.info wrote:
  It's described here:
  http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers
 
 We seem to be talking past each other. There's a specific problem
 related to type classes and invariants on data types mentioned earlier
 on this thread. Simon's solution here seems to be that we only coerce
 a structure from one newtype to the base type if the constructors are
 exposed, hence my question if the code changes semantics due to adding
 imports.

Yes, but it is an additional condition. For coercion to be even
considered, the coercion function has to be defined somewhere.

So Simon's proposal, as I understand it, is to allow compilation of that
coercion function only when the relevant data constructors are in scope
in the module where the coercion function is defined.

In the code you showed in an earlier message, there's no coercion
function (just the newtype constructor used as a function), hence the
semantics of that code would not change.

Here's an example of the code whose compilation would depend on the
constructors availability:

  newtype Age = MkAge Int

  newtype wrap ageMapWrapper :: Map Int a - Map Age a

  f ... =
let xs :: Map Int String = ...
in ageMapWrapper xs

This code is currently impossible to write, if only for the reason that
newtype wrap is not a valid declaration yet. After the extension is
introduced, but before you expose Data.Map.Internal, this code will
parse (assuming the relevant extension is turned on) but fail
(presumably at the renaming stage) when it is discovered that the
coercion requires access to the internal structure of Map.

Finally, when you expose Data.Map.Internal, and the author of the above
code imports it, the code starts to compile, but the correctness of the
Map operations is now contingent on the Age's Ord instance and is the
responsibility of the code's author, as we would expect.

Roman

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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 3:18 PM, Evan Laforge qdun...@gmail.com wrote:
 I assume it would change from doesn't compile to works if you add
 the required import.  It's the same as the FFI thing, right?  If you
 don't import M (T(..)), then 'foreign ... :: T - IO ()' gives an
 error, but import it and coerces T to its underlying type (hopefully
 that's a C type).

This is what I thought Simon meant. If so, I don't think it's a good
idea, as adding the import removes a compiler error in favor of a
runtime error. If the programmer really wanted to do something this
unsafe, she should use unsafeCoerce.

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


Re: Newtype wrappers

2013-01-14 Thread Evan Laforge
On Mon, Jan 14, 2013 at 3:28 PM, Johan Tibell johan.tib...@gmail.com wrote:
 On Mon, Jan 14, 2013 at 3:18 PM, Evan Laforge qdun...@gmail.com wrote:
 I assume it would change from doesn't compile to works if you add
 the required import.  It's the same as the FFI thing, right?  If you
 don't import M (T(..)), then 'foreign ... :: T - IO ()' gives an
 error, but import it and coerces T to its underlying type (hopefully
 that's a C type).

 This is what I thought Simon meant. If so, I don't think it's a good
 idea, as adding the import removes a compiler error in favor of a
 runtime error. If the programmer really wanted to do something this
 unsafe, she should use unsafeCoerce.

Wait, what's the runtime error?  Do you mean messing up Set's invariants?

If you as the library writer don't want to allow unsafe things, then
don't export the constructor.  Then no one can break your invariants,
even with newtype malarky.  If you as the the library user go and
explicitly import the bare Set constructor from (theoretical)
Data.Set.Unsafe, then you are in the position to break Set's internal
invariants anyway, and have already accepted the great power / great
responsibility tradeoff.

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


Re: Newtype wrappers

2013-01-14 Thread Ian Lynagh
On Mon, Jan 14, 2013 at 03:28:15PM -0800, Johan Tibell wrote:
 On Mon, Jan 14, 2013 at 3:18 PM, Evan Laforge qdun...@gmail.com wrote:
  I assume it would change from doesn't compile to works if you add
  the required import.  It's the same as the FFI thing, right?  If you
  don't import M (T(..)), then 'foreign ... :: T - IO ()' gives an
  error, but import it and coerces T to its underlying type (hopefully
  that's a C type).
 
 This is what I thought Simon meant. If so, I don't think it's a good
 idea, as adding the import removes a compiler error in favor of a
 runtime error. If the programmer really wanted to do something this
 unsafe, she should use unsafeCoerce.

Simon's proposal would mean that

import Data.Set.Internal

newtype wrap w :: Set Int - Set Age

would be possible, in the same way that

import Data.Set.Internal

w :: Set Int - Set Age
w (BinSet x y) = BinSet (MkAge x) (MkAge y)
w Empty = Empty

would be possible. i.e. it wouldn't let you write anything that you
couldn't write anyway (although it would make it easier to write, and
it would have better performance).


The adding an import makes it compile issue is a red herring IMO.
Adding the import also makes my second example work for the same reason;
it's just more obvious that the constructor is needed in the second
example as it's visible in the code.


Thanks
Ian


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


Re: Newtype wrappers

2013-01-14 Thread Johan Tibell
On Mon, Jan 14, 2013 at 3:40 PM, Evan Laforge qdun...@gmail.com wrote:
 Wait, what's the runtime error?  Do you mean messing up Set's invariants?

Yes.

 If you as the library writer don't want to allow unsafe things, then
 don't export the constructor.  Then no one can break your invariants,
 even with newtype malarky.  If you as the the library user go and
 explicitly import the bare Set constructor from (theoretical)
 Data.Set.Unsafe, then you are in the position to break Set's internal
 invariants anyway, and have already accepted the great power / great
 responsibility tradeoff.

If it's explicit that this is what you're doing I'm fine with it. I
just don't want magic coercing depending on what's in scope.

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


Re: Newtype wrappers

2013-01-14 Thread Brandon Allbery
On Mon, Jan 14, 2013 at 5:29 PM, Johan Tibell johan.tib...@gmail.comwrote:

 Let me rephrase: how will Simon's proposed data constructors are in
 scope mechanism work? For example, will

 let xs :: Map = ...
 in map MyNewtype xs

 behave differently if the constructors of Map are in scope or not?


If you allow deriving this without the constructors in scope, the user can
use it to violate the invariant (by the new type causing Map to think it is
sorted differently than it is, because there is a different Ord constraint).

Requiring the constructors to be in scope doesn't actually prevent this,
but does give the user some chance to do something about it.  Meanwhile
something that deliberately hides its constructors to preserve an invariant
can't suddenly have that invariant violated by an errant use of this
feature.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Newtype wrappers

2013-01-14 Thread Ian Lynagh
On Mon, Jan 14, 2013 at 09:03:38PM +0200, Roman Cheplyaka wrote:
 * Simon Peyton-Jones simo...@microsoft.com [2013-01-14 18:09:50+]
  Friends
  
  I'd like to propose a way to promote newtypes over their enclosing type.  
  Here's the writeup
http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers
  
  Any comments?
 
 Why not just have a pseudo-function 'coerce'?
 
 By pseudo-function I mean something that can be used anywhere (or almost
 anywhere?) where a function can, but is a keyword and doesn't have a
 type. (It'd be similar to ($) as implemented by GHC, I figure.)
 
 The static semantics would be to compute the inner and outer types
 to the extent possible, and then behave as if the function was defined
 as a wrapper or unwrapper function for those types. In case when it is
 ambiguous, an error is issued, and the standard tricks can be used to
 refine the type (including annotation coerce itself with a type).

It would be even better if we implemented a syntax for type arguments.
Then, if type application was written f @ t, you would be able to (or
perhaps required to) write

coerce @ from_type @ to_type expr


Thanks
Ian


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


Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
No magic coercing is present in the proposal. You need to use explicit newtype 
wrap and newtype unwrap expressions.

Sent from my iPad

On Jan 14, 2013, at 6:42 PM, Johan Tibell johan.tib...@gmail.com wrote:

 On Mon, Jan 14, 2013 at 3:40 PM, Evan Laforge qdun...@gmail.com wrote:
 Wait, what's the runtime error?  Do you mean messing up Set's invariants?
 
 Yes.
 
 If you as the library writer don't want to allow unsafe things, then
 don't export the constructor.  Then no one can break your invariants,
 even with newtype malarky.  If you as the the library user go and
 explicitly import the bare Set constructor from (theoretical)
 Data.Set.Unsafe, then you are in the position to break Set's internal
 invariants anyway, and have already accepted the great power / great
 responsibility tradeoff.
 
 If it's explicit that this is what you're doing I'm fine with it. I
 just don't want magic coercing depending on what's in scope.
 
 ___
 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: Newtype wrappers

2013-01-14 Thread Chris Dornan
Looks great; I care and have no improvements to offer; +1 from me.

Chris

From:  Simon Peyton-Jones simo...@microsoft.com
Date:  Monday, 14 January 2013 18:09
To:  glasgow-haskell-users glasgow-haskell-users@haskell.org
Subject:  Newtype wrappers

Friends
 
I¹d like to propose a way to ³promote² newtypes over their enclosing type.
Here¹s the writeup
  http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers
 
Any comments?  Below is the problem statement, taken from the above page.
 
I¹d appreciate
·A sense of whether you care. Does this matter?

·Improvements to the design I propose

 
Simon
 
 
 
The problem
Suppose we have 
newtype Age = MkAge Int
Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age. Moreover,
this conversion is a type conversion only, and involves no runtime
instructions whatsoever. This cost model -- that newtypes are free -- is
important to Haskell programmers, and encourages them to use newtypes freely
to express type distinctions without introducing runtime overhead.

Alas, the newtype cost model breaks down when we involve other data
structures. Suppose we have these declarations
data T a   = TLeaf a | TNode (Tree a) (Tree a)
data S m a = SLeaf (m a) | SNode (S m a) (S m a)
and we have these variables in scope
x1 :: [Int]
x2 :: Char - Int
x3 :: T Int
x4 :: S IO Int
Can we convert these into the corresponding forms where the Int is replaced
by Age? Alas, not easily, and certainly not without overhead.
* For x1 we can write map MkAge x1 :: [Age]. But this does not follow the
newtype cost model: there will be runtime overhead from executing the map at
runtime, and sharing will be lost too. Could GHC optimise the map somehow?
This is hard; apart from anything else, how would GHC know that map was
special? And it it gets worse.
* For x2 we'd have to eta-expand: (\y - MkAge (x2 y)) :: Char - Age. But
this isn't good either, because eta exapansion isn't semantically valid (if
x2 was bottom, seq could distinguish the two). See #7542
http://hackage.haskell.org/trac/ghc/ticket/7542  for a real life example.
* For x3, we'd have to map over T, thus mapT MkAge x3. But what if mapT
didn't exist? We'd have to make it. And not all data types have maps. S is a
harder one: you could only map over S-values if m was a functor. There's a
lot of discussion abou this on #2110
http://hackage.haskell.org/trac/ghc/ticket/2110 .
 
___ 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: Newtype wrappers

2013-01-14 Thread Iavor Diatchki
Hello,

The general functionality for this seems useful, but we should be careful
exactly what types we allow in the 'newtype wrap/unwrap' declarations.  For
example, would we allow something like this:

newtype wrap cvt :: f a - f (Dual a)

If we just worry about what's in scope, then it should be accepted, however
this function could still be used to break the invariant on `Set` because
it is polymorphic.


In general, I was never comfortable with GHC's choice to add an axiom
equating a newtype and its representation type, because it looks unsound to
me (without any type-functions or newtype deriving).
For example, consider:

newtype T a = MkT Int

Now, if this generates an axiom asserting that `froall a. T a ~ Int`, then
we can derive a contradiction:

T Int ~ Int ~ T Char, and hence `Int ~ Char`.

It looks like what we need is a different concept: one that talks about the
equality of the representations of types, rather then equality of the types
themselves.

-Iavor




















On Mon, Jan 14, 2013 at 10:09 AM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Friends

 ** **

 I’d like to propose a way to “promote” newtypes over their enclosing
 type.  Here’s the writeup

   http://hackage.haskell.org/trac/ghc/wiki/NewtypeWrappers

 ** **

 Any comments?  Below is the problem statement, taken from the above page.*
 ***

 ** **

 I’d appreciate

 **· **A sense of whether you care. Does this matter?

 **· **Improvements to the design I propose

 ** **

 Simon

 ** **

 ** **

 ** **

 *The problem*

 Suppose we have 

 newtype Age = MkAge Int

 Then if n :: Int, we can convert n to an Age thus: MkAge n :: Age.
 Moreover, this conversion is a type conversion only, and involves no
 runtime instructions whatsoever. This cost model -- that newtypes are free
 -- is important to Haskell programmers, and encourages them to use newtypes
 freely to express type distinctions without introducing runtime overhead.
 

 Alas, the newtype cost model breaks down when we involve other data
 structures. Suppose we have these declarations 

 data T a   = TLeaf a | TNode (Tree a) (Tree a)

 data S m a = SLeaf (m a) | SNode (S m a) (S m a)

 and we have these variables in scope 

 x1 :: [Int]

 x2 :: Char - Int

 x3 :: T Int

 x4 :: S IO Int

 Can we convert these into the corresponding forms where the Int is
 replaced by Age? Alas, not easily, and certainly not without overhead. ***
 *

- For x1 we can write map MkAge x1 :: [Age]. But this does not follow
the newtype cost model: there will be runtime overhead from executing the
map at runtime, and sharing will be lost too. Could GHC optimise the
map somehow? This is hard; apart from anything else, how would GHC
know that map was special? And it it gets worse. 


- For x2 we'd have to eta-expand: (\y - MkAge (x2 y)) :: Char - Age.
But this isn't good either, because eta exapansion isn't semantically valid
(if x2 was bottom, seq could distinguish the two). See 
 #7542http://hackage.haskell.org/trac/ghc/ticket/7542for a real life example.



- For x3, we'd have to map over T, thus mapT MkAge x3. But what if 
 mapTdidn't exist? We'd have to make it. And not all data types have maps.
S is a harder one: you could only map over S-values if m was a
functor. There's a lot of discussion abou this on 
 #2110http://hackage.haskell.org/trac/ghc/ticket/2110.


 ** **

 ___
 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