In GHC it's disallowed because an existential is modeled as a data constructor with a field that captures the type in the same way that it captures the value fields. But since the representation of a newtype is supposed to be the same as the representation of the (single) field, you can't do that.
So, it'd be quite difficult to make GHC do this (i.e. it'd affect GHC's typed intermediate language); and I can't see any useful applications.
This would actually be a useful feature with GADTs, since matching on one can tell us what the existential field was, even without storing a context for it in our newtype.
It's definitely not essential to anything I'm doing, but perhaps the recent changes to GHC since the last time people looked at this ticket make this feature easier to implement?
Okay, so this ticket-revival stemmed from a question I asked on IRC, so here's what I wanted to use this for.
class (Monad (m context)) => MonadContext m context where getContext :: m context context withContext :: MonadContext m context' => context' -> m context' a -> m context adata FallibleContextualOperation failure context a = FallibleContextualOperation { fallibleContextualOperationAction :: context -> IO (Either failure a) }instance Monad (FallibleContextualOperation failure context) where return a = FallibleContextualOperation { fallibleContextualOperationAction = \_ -> return $ Right a } x >>= f = FallibleContextualOperation { fallibleContextualOperationAction = \context -> do v <- fallibleContextualOperationAction x context case v of failure@(Left _) -> return failure Right y -> fallibleContextualOperationAction (f y) context }instance MonadContext (FallibleContextualOperation failure) context where getContext = FallibleContextualOperation { fallibleContextualOperationAction = \context -> return $ Right context } withContext context' x = FallibleContextualOperation { fallibleContextualOperationAction = \context -> fallibleContextualOperationAction x context' }
I can provide more details of what this is motivated by upon request, but basically, I want to have my "master implementation" of this class based on FallibleContextualOperation, and then I want to make two types that get that behavior for free:
class Serializable context a where serialize :: Serialization context a deserialize :: Deserialization context a
.. and write many instances of this, elsewhere in my program, which don't need to know or care about the fact that there are two backend types (ByteStrings and open files), or any of this other nasty plumbing detail.
I don't know if this is sufficient motivation to justify the work the ticket is requesting, since I don't know just how much work it is. But it's presented here for everyone's edification. :)
I also have run into cases where I'd like to make a "trivial" GADT into a newtype. In particular, when programming in a "dependent"-like style using GADTs to encode the tags of dependent sums, it's often nice to have a wrapper that does nothing but alter the type index - a very general example would be "data Map f t a where Map :: t a -> Map f t (f a)" - which allows transforming the last type parameter by an arbitrary type-level function. Most of the time this usage could be avoided by including 'f' in the dependent sum type itself, but that complicates other things and even then I've found you occasionally want to modify the types of tags.
Another situation where I've wanted something like this to forget a phantom type - and I've seen the same pattern in other people's code I've read on hackage.
There is a different possible resolution to this request, which would probably be more work but not break portability - guarantee that any "data" declaration satisfying certain criteria will be compiled to a newtype-like representation. Here's my stab at that set of criteria:
Only one constructor
Only one field with nonzero width in that constructor (counting constraints as fields)
That field is marked strict
It seems like those requirements should be sufficient to justify special-case handling to compile them to something effectively the same as a newtype. Or if some mechanism already causes this to effectively by the case, then I'd be happy with that being documented and test-cases added to ensure it continues to be a stated goal to cover situations like these.
Anything involving existentials is going to be hard to implement using newtype directly. But as 'mokus' says, it might be possible to make a guarantee, right in the code generator, that certain sorts of data types do not allocate a box. The conditions are, I think, very nearly as 'mokus' says:
Only one constructor
Only one field with nonzero width in that constructor (counting constraints as fields)
That field is marked strict
That field has a boxed (or polymorphic) type
I think this'd be do-able. The question is how important it is in practice; it's one more thing to maintain.
Just a minor bump on this. The more fancy GADT and Poly/DataKind programming I do, the more this bothers me. It seems like a real pity to be penalized (with an extra box) for choosing to encode invariants in indices, especially with all the new delicious features GHC has been getting recently.
dataIntListwhereNil::IntListCons::Int->IntList->IntListdataNat=Z|SNatdataIntVec::Nat->*whereNilV::IntVecZConsV::Int->IntVecn->IntVec(Sn)-- N.B: not datanewtypeExists(f::k->*)=forallx.Exists(fx)typeIntVecList=ExistsIntVec-- IntList and IntVecList should be isomorphic! If Exists can't be a newtype, I have to pay a penalty for adding indices to my type :(
Yes, I always wondered how existentially quantifying over a type constructor with non-* domain kinds can ever necessitate extra information at runtime. I fully support the reopen proposal because of data Hidden :: k -> * where Hide :: t a -> Hidden t wants to be a newtype.
Which leads to inf containing a Fin whose existential index can't actually be any valid (finite) type. Fin thus becomes a bit of a misnomer in this context, since it's not finite. Making SomeFin into data rather than newtype fixes the problem by making inf into a bottom.
Hmm, when I try to convert it to a newtype, like this:
newtype Some tag = forall t. This (tag t)
I get this error:
src/Data/Some.hs:17:20: A newtype constructor cannot have existential type variables This :: forall (k :: BOX) (tag :: k -> *) (t :: k). tag t -> Some tag In the definition of data constructor ‘This’ In the newtype declaration for ‘Some’
Is there a different way of converting it to a newtype that I'm overlooking?
Anything involving existentials is going to be hard to implement using newtype directly. But as 'mokus' says, it might be possible to make a guarantee, right in the code generator, that certain sorts of data types do not allocate a box. The conditions are, I think, very nearly as 'mokus' says:
Only one constructor
Only one field with nonzero width in that constructor (counting constraints as fields)
That field is marked strict
That field has a boxed (or polymorphic) type
I think this'd be do-able. The question is how important it is in practice; it's one more thing to maintain.
I would like to have something like this very much! Among other things, it's one possible way to make IntMap nicer. One potential extension: I think constraints only need to count as fields if any of them are classes that have methods, or whose superclasses have methods. In particular, it could be very useful to have equality constraints involving type families.
Do LanO, LanS satisfy the conditions to be newtypes?
LanO does not, because its constructor takes no arguments. But that's perfectly fine; there's only one LanO value anyway. LanS does not either, because its constructor is lazy. If you wrote LanS :: !(Fin i) -> LanS (S i) then it would satisfy the conditions.
Note that data A = A !Int and newtype A = A Int have subtly different surface language semantics when they're pattern matched on. What would case undefined of A _ -> 1 evaluate to? For newtypes, it's 1 whereas for strict data types this would blow up.
I guess what I'm saying is: The suggested lowering must preserve data semantics and can never behave the same as actual newtypes. Semantically, data is data and newtype is newtype. It would get rid of the performance implications, though.
Yes for @sgraf's reason I wish we used an equivalence relation on these internal notion of deep representations, and also RuntimeReps. For example, given matching deep structure (not tracked in the kind/RuntimeRep):
forall a t. exists t' t'. (t :: Kind a) ~R (t' :: Kind TupleRep [a]) ~R (t'' :: Kind SumRep [a])
Maybe it's not worth the extra coercions in practice, but certainly I think its good teaching to pretend newtypes are always:
newtype Foo (a :: k) :: TupleRep [k] = Foo (a :: k)
to explain
newtype A :: TupleRep [LiftedRep] = A (Int :: LiftedRep)case undefined of A _ -> 1
contrasted with pretend elaborated unpacked !Int:
data A' :: LiftedRep = A' (!Int :: IntRep)case undefined of A' _ -> undefined
That the shallow representations of A and A' have different strictness (opposite of their interior's shallow strictness), cleanly justifies how the case-expressions have different semantics despite the overall isomorphism of A and A'.
I know there are a lot of open questions about how to implement the newtype optimization optimally for these types. But it seems fairly clear that just doing the simplest possible thing in STG will improve matters, taking the nasty work-arounds out of user code. Can we maybe just get that now, and see if someone comes up with a better implementation later?