jcpetruzza / barbies

BSD 3-Clause "New" or "Revised" License
92 stars 15 forks source link

Expand the Wear type family a bit #28

Open lspitzner opened 4 years ago

lspitzner commented 4 years ago

Greetings!

question

Is there any chance to expand the type family like this:

type family Wear t f a where
  Wear Bare    f (First a) = a
  Wear Bare    f (Last a) = a
  Wear Bare    f a = a
  Wear Covered f a = f a
  Wear (Param _ t) f a = Wear t f a
  Wear t       _ _ = TypeError (     'Text "`Wear` should only be used with "
                               ':<>: 'Text "`Bare` or `Covered`."
                               ':$$: 'Text "`" ':<>: 'ShowType t ':<>: 'Text "`"
                               ':<>: 'Text " is not allowed in this context."
                               )

(This also requires two new instances, of course:

instance GBare n (Rec (P n Identity (Last a)) (Identity (Last a))) (Rec a a) where
  gstrip _ = coerce
  {-# INLINE gstrip #-}

  gcover _ = coerce
  {-# INLINE gcover #-}

)

motivation

use-case is that for combining configs I have f ~ Option, and together with a ~ Last X this gives nice behaviour for generic Semigroup instances. So you'd have a

MyConfig t f = MyConfig
  { a :: Wear t f (Last Bool)
  , b :: Wear t f [Text]
  }

config1 :: MyConfig Covered Option
config2 :: MyConfig Covered Option
staticConfig :: MyConfig Covered Identity
fromOptionIdentity :: Identity a -> Option a -> Identity a
fromOptionIdentity x y = coerce (fromMaybe (coerce x) (coerce y)
finalConfig = bstrip (bzipWith fromOptionIdentity staticConfig (config1 <> config2))
-- (~~see the next issue for what bZipWith is supposed to be~~
--  nevermind, there is a bzipWith already)
-- and have
a finalConfig :: Bool
b finalConfig :: [Text]
-- instead of
a finalConfig :: Last Bool -- pesky left-over from the config merging logic

discussion

We cannot abstract over the type family (yet) so putting this in here is the only way to get this feature, I fear. The downside is that this is a bit confusing behaviour "why does this remove my First/Last wrapper" but then I don't think there are any users who have barbies over First/Last values, apart from this usecase.. it is a bit of a hack.

jcpetruzza commented 4 years ago

I can see why you'd want to do that! Still it feels a bit arbitrary, right? E.g. why stop with First / Last and not add Min, Max, Sum, Prod, etc? How about Identity? And I can imagine this could be surprising to other people.

As you say, with unsaturated type familes, you'd just write your own type-family and we wouldn't need the BareB class. But now I wonder, can't we abstract over Bare in BareB? I'm thinking something like this:

class FunctorB (b Covered) => BareWithB bare b where
  bstrip :: b Covered Identity -> b bare Identity
  bcover :: b bare Identity -> b Covered Identity

type BareB = BareWithB Bare 

That way, you could define:

data MyBare

type family MyWear t f a where
  MyWear MyBare    f (First a) = a
  MyWear MyBare    f (Last a) = a
  MyWear MyBare    f a = a
  MyWear Covered   f a = f a

And then define an instance BareWithB MyBare MyConfig. I haven't looked into the details of this, but I suspect the generic instance mechanism should still work. What do you think?

lspitzner commented 4 years ago

Wait, would that work without unsaturated TFs? Or are you talking about how to best make use of them? I don't see yet where MyWear gets applied, or how this works without unsaturated TFs.

Still that feels a bit arbitrary

yes.. but now that I think of it, there is a neater approach to resolving the arbitrariness:

newtype Thin f a = Thin (f a)
  -- we don't need/use the constructor, but it helps infer kinds

type family Wear t f a where
  Wear Bare    f (Thin g a) = a
  Wear Bare    f a          = a
  Wear Covered f (Thin g a) = f (g a)
  Wear Covered f a          = f a
  Wear (Param _ t) f a = Wear t f a
  Wear t       _ _ = TypeError …

-- now my example would become
MyConfig t f = MyConfig
  { a :: Wear t f (Thin Last Bool)
  , b :: Wear t f [Text]
  }

I haven't actually tested this, but I am pretty sure that MyConfig Bare and MyConfig Covered have the desired shape. And GBare can be made work with this too, right? What do you think?

The Thin constructor would be exported by barbies with exactly and only this purpose in mind, which brings the Wear behaviour back to "fully expectable".

lspitzner commented 4 years ago

GBare will need to rely on Coercible a (g a) there, I guess. Same as the implementation for Last I mentioned above, only over any suitable g.

jcpetruzza commented 4 years ago

Wait, would that work without unsaturated TFs? Or are you talking about how to best make use of them? I don't see yet where MyWear gets applied, or how this works without unsaturated TFs.

Yeah, sorry I was not very clear. I meant, without unsaturated type families. If we were to relax BareB to become BareByB, then you could define something like:

MyConfig t f = MyConfig
  { a :: MyWear t f (Last Bool)
  , b :: MyWear t f [Text]
  }
deriving (Generic, FunctorB (MyConfig Covered), BareByB MyBare MyConfig)

So by abstracting over Covered, one would be able to define your own "wear" type families.

In any case, I like your Thin proposal, which looks overall simpler to use and probably handles most interesting cases. If it can be made to work, it would be a good idea to add that. Haven't thought about it in detail, but as you say, one may need to modify this instance in Barbies/Generics/Bare.hs:

instance repbi ~ repbb => GBare n (Rec repbi repbi) (Rec repbb repbb) where
  gstrip _ = id
  {-# INLINE gstrip #-}

  gcover _ = id
  {-# INLINE gcover #-}

to become

instance Coercible repbi repbb => GBare n (Rec repbi repbi) (Rec repbb repbb) where
  gstrip _ = coerce
  {-# INLINE gstrip #-}

  gcover _ = coerce
  {-# INLINE gcover #-}
lspitzner commented 4 years ago

Thanks for the quick feedback!

jcpetruzza commented 4 years ago

Reopening since the Thin marker unfortunately break backwards compatibility.

jcpetruzza commented 4 years ago

The problem with Thin would manifest on parametric types, where we can't know if the argument will be under Thin and will, therefore, need a Coercible constraint. But since the functor argument is always a parameter, maybe we could use the marker on it? Something like this (untested):

newtype Sticky f g a = Sticky (f (g a))
  -- we don't need/use the constructor, but it helps infer kinds

type family Wear t f a where
  Wear Bare    (Sticky f g a) = a
  Wear Bare    f a          = a
  Wear Covered (Sticky f g a) = f (g a)
  Wear Covered f a          = f a
  Wear (Param _ t) f a = Wear t f a
  Wear t       _ _ = TypeError …

data MyConfig t f = MyConfig
  { a :: Wear t (Sticky f Last Bool)
  , b :: Wear t f [Text]
  }

I guess we'll need a GBare instance for the Sticky case, and with the Coercible constraint only there.

lspitzner commented 4 years ago

That's a good idea. I assume you mean

type family Wear t f a where
  Wear Bare    (Sticky f g) a = a
  Wear Bare    f a          = a
  Wear Covered (Sticky f g) a = f (g a)
  Wear Covered f a          = f a
  Wear (Param _ t) f a = Wear t f a
  Wear t       _ _ = TypeError …

data MyConfig t f = MyConfig
  { a :: Wear t (Sticky f Last) Bool
  , b :: Wear t f [Text]
  }

I'll try that.

lspitzner commented 4 years ago

It does not work out of the box, and I now doubt that it could. Consider the type of

bmap :: forall b f g . FunctorB b => (forall a . f a -> g a) -> b f -> b g

That is, f and g are parametric here too, and they could also be Sticky! Not that we'd expect that usage, but the language certainly allows it.

There is a different approach, that comes back full circle to your "define your own type family" approach, although there is no need to specialise it any specific wrappers. Consider this:

type family WearTwo t f g a where
  WearTwo Bare        f g a = a
  WearTwo Covered     f g a = f (g a)
  WearTwo (Param _ t) f g a = WearTwo t f g a
  WearTwo t           _ _ _ =
    TypeError (     'Text "`WearTwo` should only be used with "
              ':<>: 'Text "`Bare` or `Covered`."
              ':$$: 'Text "`" ':<>: 'ShowType t ':<>: 'Text "`"
              ':<>: 'Text " is not allowed in this context."
              )

data MyConfig t f = MyConfig
  { a :: WearTwo t f Last Bool
  , b :: Wear t f [Text]
  }

I still don't test the full "does the semigroup instance work for this" part, but the shapes of MyConfig are as desired/expected and btraverse works too. I have based this on top of the Thin commit, and I'd guess the Coercible instance is still required. The barbies tests pass.

lspitzner commented 4 years ago

I haven't checked, but I think with the Coercible instance in barbies code, the WearTwo family could be defined externally without a problem. Assuming Param is exposed (?). But then this type family is again completely general (it does not add special casing for specific wrappers (Last etc.)) so it makes sense to add it as a new feature to barbies.

I could make a new PR either with the minimum set of changes to allow this, or the full "add the WearTwo" idea. I will check later if there is a difference between these options and what they involve exactly :p

jcpetruzza commented 4 years ago

This is interesting. If relaxing the generic instance to use Coercible instead of ~ works (as in it doesn't break tests), I think I'd be happy to merge that in. Param is already exposed in Barbies.Internal, so people could already define their own variations of Wear. That said, we could still add something like WearTwo.

lspitzner commented 4 years ago

I haven't checked, but I think with the Coercible instance in barbies code, the WearTwo family could be defined externally without a problem.

Yep, I have confirmed that it works. So the WearTwo family could be defined externally, given the Coercible instance.

lspitzner commented 4 years ago

See #30 (which does include the WearTwo family for good measure.)