So like, for stateT, isn’t the “fix” adding suport for higher order role annotations to surface Haskell?On Sun, Jan 3, 2021 at 1:02 PM Carter Schonwald <carter.schonwald@gmail.com> wrote:Isn’t the issue here the first orderness of the current roles system in ghc? In which case what technological issues should be fixed? That we can’t do this because of limitations in the role system and I feel that doing this sortah change would *force* this to be prioritized.This limitation is a misfeature, how can we make this get addressed sooner rather than later? Is this somewhere where Eg Haskell foundation or something could help?On Sun, Jan 3, 2021 at 12:15 PM Oleg Grenrus <oleg.grenrus@iki.fi> wrote:I think Mag, regex-applicative etc. examples are all reparable. The main culprit is however StateT and a like, as you pointed out. It's meaningless to discuss Mag if we cannot even write Functor m => Functor (StateT s m).
> Coercible constraints aren't unpacked in data constructors
Aren't they zero-width at run time? That's IMO a bug if that is not true.
- Oleg
On 3.1.2021 19.08, David Feuer wrote:
Mag uses the One it does for efficiency/compactness. Coercible constraints aren't unpacked in data constructors, sadly. If you're looking for more examples of slightly-invalid but useful Functors, the first place I'd check (beyond the very-Mag-like things in lens that inspired Mag) is Roman Cheplyaka's regex-applicative. I don't know if his lifts coercions or not (haven't looked in a while) but it does some similarly illegitimate things for good reasons.
On Sun, Jan 3, 2021, 12:03 PM Oleg Grenrus <oleg.grenrus@iki.fi> wrote:
Prelude Control.Monad.Trans.State> :i StateT
type role StateT nominal representational nominal
Note, `StateT` is nominal in last argument (a). Thus if (forall c d. Coercible ...) where a Functor superclass, Functor (and thus Monad) wouldn't be definable for StateT. That would be... unfortunate.
Until there are "higher roles" Functor cannot be Coercible1. It would rule very simple code.
(OTOH Mag can be repaired, https://oleg.fi/gists/posts/2019-07-31-fmap-coerce-coerce.html#functor-should-be-parametric).
- Oleg
On 3.1.2021 18.31, Carter Schonwald wrote:
Hey David,could you exposit what would go wrong? a concrete proof witness or explanation would help me a lot. other people might benefit too.
for the stateT s Maybe a, perhaps i'm still waking up this AM, so let me try
newtype StateT s m a = StateT {runStateT :: s -> m (a, s)}
so this should expand to
'(s -> Maybe (a,s)),'but the coerce would be on the 'a' here ... so i'm not seeing the issue?
the latter example seem to boil down to "a free appplicative/functor Gadt" with some extra bits, though i've not worked through to seeing the unsafety
for the latter examples, the definitions are the following :
traverseBia :: (Traversable t, Biapplicative p) => (a -> p b c) -> t a -> p (t b) (t c) traverseBia = inline (traverseBiaWith traverse) -------- traverseBiaWith :: forall p a b c s t. Biapplicative p => (forall f x. Applicative f => (a -> f x) -> s -> f (t x)) -> (a -> p b c) -> s -> p (t b) (t c) traverseBiaWith trav p s = smash p (trav One s) ------- smash :: forall p t a b c. Biapplicative p => (a -> p b c) -> (forall x. Mag a x (t x)) -> p (t b) (t c) smash p m = go m m where go :: forall x y. Mag a b x -> Mag a c y -> p x y go (Pure t) (Pure u) = bipure t u go (Map f x) (Map g y) = bimap f g (go x y) go (Ap fs xs) (Ap gs ys) = go fs gs <<*>> go xs ys #if MIN_VERSION_base(4,10,0) go (LiftA2 f xs ys) (LiftA2 g zs ws) =