fused-effects / fused-effects

A fast, flexible, fused effect system for Haskell

Geek Repo:Geek Repo

Github PK Tool:Github PK Tool

GHC’s type inference can require explicit annotations in the presence of constructs that should be unambiguous

pjones opened this issue · comments

First off, thanks for fused-effects! I'm really enjoying how clean it is to use compared with the mtl.

I'm running into a problem with a polymorphic effect that I'm converting from mtl-style. Here's a snippet of the definition:

data family Key k

data Crypto t m k
  = GenerateKey Cipher Label (Key t -> m k)
  | FetchKey Label (Maybe (Key t) -> m k)
  | Encrypt (Key t) ByteString (Secret ByteString -> m k)
  | Decrypt (Key t) (Secret ByteString) (ByteString -> m k)

The Key data family is used to hide the implementation of crypto keys since different carriers will have different key types (e.g. hardware devices usually don't allow you to access the keys directly). Therefore I'd like the data family index (the t variable in Crypto) to remain polymorphic with all uses of the effect up to the point where it's interpreted via a run function.

However, GHC doesn't like the type variable and complains about it being ambiguous. For example:

app :: Has (Crypto k) sig m => m ()
--  Could not deduce (Control.Effect.Sum.Member (Crypto k0) sig)

I don't know how to help GHC or fused-effects sort out that k should be polymorphic.

What's really confusing to me is that when I provide a concrete type for the family index GHC still can't figure out what the type variable is in the smart constructors:

foo :: (Has (Crypto k) sig m, k ~ Cryptonite) => m ()
foo = do
  _ <- fetchKey (toLabel "a key")
  pure ()

-- or

foo' :: Has (Crypto Cryptonite) sig m => m ()
foo' = do
  _ <- fetchKey (toLabel "a key")
  pure ()

Both of these produce: Could not deduce (Control.Effect.Sum.Member (Crypto k0) sig)

Of course, this works:

foo' :: (Has (Crypto k) sig m, k ~ Cryptonite) => m ()
foo' = do
  (_ :: (Maybe (Key Cryptonite))) <- fetchKey (toLabel "a key")
  pure ()

But then my code would only work with a single carrier.

I would love some suggestions as to how I could achieve my goal of letting the carrier pick the key type which would remain completely opaque to the user of the library.

Thank you.

EDIT: consider Rob’s answer below as the more authoritative case, as usual :)

@pjones Hi there! Unfortunately, it’s not yet possible to tell GHC to make the kind of inference you want, at least not without providing some more information.

Some background: the error in foo above is due to the fact that you never use the result of fetchKey in such a way that the k parameter returned from fetchKey. Luckily, we can specify this at the call site, with an explicit type variable:

fetchKey :: forall k sig m . (Has (Crypto k) sig m) => Label -> m (Maybe (Key k))

Then, in invocations of fetchKey where it’s ambiguous, you can provide a type application:

fetchKey @Cryptonite (toLabel "a key”)

This is equivalent to your use of ScopedTypeVariables in foo’ above, though it is perhaps more syntactically pleasing.

Alternatively, if in practice the Cryptonite key is unambiguous, you may not need these type annotations. For example, if the result type of foo above mentioned k, the type inference would succeed. If you really wanted to go the whole nine yards, Backpack could create a parameterized module with a concrete value for k, which would eliminate the possibility of ambiguity, at the cost of a more-complicated .cabal file for your users.

I hope that sometime in the future GHC will allow us to specify “hey, there’s only one k to which this function has access; if there’s ambiguity, assume we mean that which we can access”. Unfortunately, I don’t know how well, if at all, this fits into GHC’s typechecker, so beyond our writing a GHC plugin to help these inferences (which polysemy has done, or at least started) I don’t think a fix is on the horizon—which is a shame, as I’ve hit this before, and it’s tough.

Thank you @patrickt.

I suppose I'll need to try this from a different angle. I think I'll remove the type variable from the effect type and use ExistentialQuantification to move it into the data constructors with a class constraint so I can recover the information I need about a key.

Thanks again.

Thanks for the kind words! This is a pretty interesting case.

For what it’s worth, I think @patrickt is incorrect; I think this is very likely quite tractable, as I’ll outline below.

There are a bunch of different strategies for this sort of problem, which is good in that the design space offers a lot of options, and kind of bad in that there isn’t a ton of guidance out there for how to optimize for the properties you want your system to have. I think we can help there.

First, it’s worth exploring why this is happening. (Apologies in advance if I’m covering anything you’re familiar with; I’m hoping to extract this into a general tutorial so I’m deliberately writing a little broadly.)

ghc requires that type signatures be unambiguous, meaning that any callsite should be able to resolve its types using its arguments (or more generally using the type environment it’s used in—this works with partial application and such as well). That’s the case when all of the types are constants or quantified type variables, so ambiguity doesn’t arise in very simple cases.

However, if a type variable is used in a constraint and not on the right-hand side of the =>, callers can’t instantiate it by supplying some specific type via arguments or environment. ghc won’t be able to solve the constraint, then, because it can’t safely equate the ambiguous type variable with any other type. It rules this out by checking for this at definition sites.

The exception to this “variable used in a constraint only” rule involves injectivity, which is a feature which can be applied to typeclasses and type families in some cases using FunctionalDependencies and TypeFamilyDependencies. This is why the sig type parameter in fused-effects constraints don’t trigger this warning—the Algebra class has a functional dependency which says that you can uniquely determine sig so long as you know m. So as long as m appears on the right-hand side, sig remains unambiguous.

Ambiguity in cases like this is one reason why mtl uses functional dependencies to further constrain the effects—MonadReader r m has a functional dependency which requires that all instances satisfy the property that the constraint solver should be able to determine what type r is given knowledge of m. That property is quite restrictive, however, as it also has the consequence that you can only have one r—one reader effect—for any particular m. So this is why fused-effects doesn’t do that as well.

There’s (at least) one other situation where ambiguity can arise, and which you’ve encountered here as well: on its own, the result of a type family doesn’t indicate what the arguments to that type family were. That’s what’s happening in your Crypto Cryptonite examples—even tho you’ve told it that k is instantiated to Cryptonite, the uses of it don’t know that they’re supposed to be using that particular k, because Key k doesn’t provide a way to determine which k was supposed to be selected. As you noticed, constraining the result using a type annotation or type application will resolve that, but without that, or other means, it’s ambiguous.

Now, what can be done about that?

  1. One possibility is to make the relationship between k and Key k injective. This isn’t always possible with type families—TypeFamilyDependencies is a bit underpowered—but the idea is to tell it that not only can there be at most one Key k for any k (which is already the case absent orphan type instances, if such a thing exists), there can also be at most one k for any given Key k. This is of course only going to be applicable if that’s actually the case, so it’s worth considering carefully. Can you have two different crypto providers for a given key?

    Related, it’s also worth asking if the indirection through the Key type family is the best way of accomplishing the goal of abstraction. In particular, if you parameterize the effect by the key type instead, then all uses of it can still be polymorphic until instantiated by a carrier. The module defining the carrier can ensure this by e.g. not exporting the key type at all, altho this can be inconvenient in cases where you’d like to define a customized handler in a new module. However, this falls down if you want to be able to define operations that are specific to Cryptonite but which can’t know anything about its key; but I don’t think that’s going to work out with the data family either since if Key Cryptonite reduces, it will always reduce to the same thing. There’d have to be some extra type variable involved to circumvent that either way, and in that case you’re still stuck with how to let callers instantiate it—ambiguity again.

    In any case, neither of these options would be unambiguous by themselves, because foo :: Has (Crypto k) sig m => m () still leaves k ambiguous; so more is required.

  2. In semantic we’ve occasionally used phantom type parameters in a newtype to help alleviate this sort of issue; see e.g. our Evaluator newtype. This approach requires operations involving the type parameters to be wrapped in Evaluator, but as a result the ambiguity is resolved because e.g. address always appears on the right-hand side of the =>. This is a kind of low-tech way of expressing the same requirement as MonadReader, that there be at most one valid instantiation of the type parameter for that m; instead of using a functional dependency, it expresses it by unification directly. It can be a little inconvenient if you’re using existing effects like Reader because you have to define new smart constructors using the newtype, but it’s quite effective.

  3. I’ve recently had quite a bit of success using an approach to case-by-case injectivity similar to capabilities for cases where I know that e.g. m really does uniquely determine the type parameter of some effect. For example, in an OpenGL game I’m writing, I know that OpenGL allows at most one bound vertex array at a time (barring any weird extensions I’m unfamiliar with 😅). Therefore, since the uniqueness condition is imposed externally, there’s no point in allowing you to use multiple such, and I can dramatically improve type inference as a result of this.

    The approach I’ve taken involves a helper class & constraint synonyms akin to Member & Has, implementing labelled effects: any existing effectful operation can be lifted into a labelled one by means of simple helpers, and the same goes for the carriers. Thus, a client can trivially distinguish between distinct yet completely polymorphic type parameters solely by means of a specific label type parameter of arbitrary kind. (If memory serves, capabilities favours type-level strings; for my use case, I’m using my existing abstractions of vertex arrays and the like; yours might use e.g. Cryptonite for this purpose, parameterizing the effect by a type parameter for the key type instead.)

    I intend to integrate this into fused-effects proper, but the really good news is that it doesn’t actually have to be defined here to be useful—it doesn’t change anything about fused-effects, it just adds another tool for using it. So you won’t have to wait for me to get around to shipping it 😊

    The code for the supporting infrastructure lives in a Control.Effect.Labelled module in my game starlight; an example of its intended use is GL.Array. bindArray runs the labelled Reader effect, askArray lifts the ask operation into a Labelled operation using runUnderLabel, and ArrayC is simply a convenience to replace a real newtype I had previously defined and exported. Note that the wrappers are optional; askArray in particular is primarily a convenience to supply the type application resolving the label so that callers don’t have to do so themselves. An effect designed to be used with labels needn’t define un-labelled operations at all, of course, and could define only the labelled smart constructors, if desired.

  4. Your API could also take proxies to resolve the ambiguity; cf GHC.TypeLits.natVal for an example of this kind of pattern; Foreign.Storable.sizeOf is related, tho without the proxy.

  5. As you’ve found, existentials can be a valuable option, tho there can be scope-escaping challenges there.

  6. Finally, and not highly recommended, I occasionally use AllowAmbiguousTypes and ScopedTypeVariables to make it the caller’s problem instead. This is really unfriendly API, so my personal approach is to try to limit it to within a single module when e.g. wanting to avoid dummy parameters for proxies for efficiency reasons. This requires either that the caller know the specific type they want to apply at, or that they at least bind the type parameter explicitly with a forall and then reference it with type annotations or applications.

I believe a combination of 1 and 3 is probably your best bet, because it allows you to be fully polymorphic without the Key data family, while still relating e.g. Cryptonite directly to its key by using it as a label, and getting good type inference properties as a result. Injectivity is a tremendously powerful tool, but often quite unwieldy given the restrictions imposed by FunctionalDependencies and the limitations of TypeFamilyDependencies; I have found that labelled effects are a superb way of applying injectivity to effects without having to invent it all for yourself anew.

Regardless, always happy to discuss this further if you’d like; best of luck!

@robrix Wow, thank you very much. I'll need to take some time to digest your suggestions.

That said, I think I can make the Key type family injective. My design goal is to allow users of the effect to write code that will work with any key type. Each backend/carrier will only support its own key type (Cryptonite for software crypto, which is basically a ByteString, and some other type for hardware crypto, which is an opaque pointer to a hardware slot). Therefore keys are uniquely identifiable by the carrier type.

To make sure I understand correctly, please allow me to blab on for a moment.

One interesting use case of this Crypto effect is generating certificates. The code for generating and signing certificates can be totally agnostic about which crypto backend is being used. However, when generating and signing root certificates its desirable to use hardware keys to make it very difficult to compromise the certificate authority. Intermediate and leaf keys need to be generated and signed with software crypto for practical reasons. Thus, a single application might need to use multiple carriers in different execution paths.

If I can make the type family injective---or find some other way to tie the family index to the carrier--I believe I can support the use case above.

Also, you're spot on about the functional dependency. That's how the current MTL-based implementation works.

Again, thank you very much.

We should move this novel by @robrix into docs/ 😃

or my blog maybe

@pjones: yeah, this still sounds pretty much an ideal case for labelled effects using e.g. Cryptonite as a label determining the key type t, à la HasLabelled Cryptonite (Crypto t) sig m => …; no Key data family required (leastways not in the effect or public interface), and the injectivity relates t to Cryptonite (or rather, Cryptonite to Crypto t), rather than to m, so you can still use multiple carriers in the same action without hassle. Worse comes to worst you might need some way for callers to specify which one they mean via a proxy or type application, but I think there’s a pretty elegant solution lurking in there not too far from the surface.

Whether labelled effects, type family dependencies, or fundeps, injectivity is such a great tool for designing interfaces, so I’m always glad when I can help folks make better use of it 😊

@robrix The part I'm having a hard time understanding with the labelled approach is the label itself.

In this particular case, Cryptonite is the index to the Key k type family. Another index would be something like PKCS11 (for hardware keys). So, in this case I don't want users to specify the key type/label/index in their type signatures but allow it to be selected based on the carrier.

I'm getting the impression that I need stop using a type family for this, and instead have the functions take and return a carrier-specific type variable as you suggested in the second half of option 1. So something like this:

generateKey :: Has (Crypto k) sig m => Cipher -> m k

But, if I understand correctly, I'd still need to find a way to make this injective.

Does that sound correct?

@pjones: Ah I see! Thank you for clarifying that.

generateKey as written wouldn’t need to be injective since it’d be unambiguous, but composite actions using it might; so yes, I think there still might need to be another step.

You mentioned wanting to have multiple different options for crypto within the same program. Do you think you’ll need them within the same action? I.e. would you need to be able to do:

foo = do
  key1 <- generateKey cipher1
  key2 <- generateKey cipher2
  

where key1 and key2 use different indices? If not, or if it would be acceptable to jump through some hoops if you did need to, then determining the index from m (and thus the carrier) is actually pretty straightforward; labels can be type parameters of arbitrary kind as well as concrete types, so there’s no obstacle to using m as the label.

Another option, marginally less strange-feeling than using m, would be to have a single concrete type used as the label. This would work out equivalently to using m, as you’d essentially be saying that the innermost carrier will receive all requests for Crypto k irrespective of k. Since the labels are of arbitrary kind, a convenient choice might be Crypto, tho it does seem a little strange:

generateKey :: HasLabelled Crypto (Crypto k) sig m => Cipher -> m k

On the other hand, if it’s crucial to be able to conveniently interleave requests for different carriers within the same action (much like one can ask for different Reader vars within the same scope), then injectivity might not be the best tool for the job, and a proxy argument identifying k or a newtype might be a better option instead. Injectivity lets you pin a type variable to some other type, but by the same token, it also means that you can’t un-pin it from that type.

This is one reason why even once I’ve moved labelled arguments into fused-effects, I won’t be requiring them for e.g. Reader; as powerful a tool as injectivity is, it’s most flexible to be able to apply it precisely where you require it, which always comes back to “when can it vary freely?” This can be a question of semantics, as with OpenGL; or it can be a question of ergonomics, as I believe is the case here, and it can be unfortunately challenging to pick the right tradeoffs for your use case.

If you think your users will accept it, this might even be a reasonable case for AllowAmbiguousTypes and TypeApplications after all; you could let your users pick a type of arbitrary rank to identify different in-scope carriers themselves. Symbols might be a convenient choice (tho I would prefer empty datatypes myself), e.g.:

foo :: (HasLabelled @"super-secure" (Crypto k1) sig m, HasLabelled @"super-duper-secure" (Crypto k2) sig m) => m ()
foo = do
  key1 <- generateKey @"super-secure" cipher1
  key2 <- generateKey @"super-duper-secure" cipher2
  

I would be ok with this tradeoff myself, and e.g. capabilities seems to be pretty well-regarded, but I don’t know your users.

@robrix This is getting very interesting!

I wasn't planning on supporting more than one Crypto effect in a single action. However, that's not a terrible idea even if it would be rarely used. In that case the labelled approach would be very useful.

Regarding injectivity, I had completely forgotten that data families (which I'm using) are always injective since they create new types. That plus functional dependencies is what allowed all this code to work in the mtl-based implementation.

As you suggested, if the type variable is used to the right of => everything works. Here's the example app from the repo slightly modified:

--------------------------------------------------------------------------------
-- Load in our dependencies:
import Control.Carrier.Crypto.Cryptonite
import Control.Carrier.Lift
import Control.Carrier.Throw.Either
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Char8 as ByteString
import qualified Data.ByteString.Lazy.Char8 as LByteString
import Data.Function ((&))

--------------------------------------------------------------------------------
-- | An example application.
--
-- Notice that our application is polymorphic in its monad.  This
-- limits it to only those effects that are listed as class
-- constraints, and we can easily choose a different cryptography
-- backend as needed.
--
-- NOTE: @Lift IO@ is only needed here for the use of 'putStrLn'.  In
-- a real application you would probably want to avoid using 'IO'
-- since it allows your application to do anything.
app
  :: ( Has (Lift IO)  sig m
     , Has (Crypto k) sig m
     )
  => m (Key k)
app = do
  let label  = toLabel "my symmetric key label"
      cipher = AES256
      number = 42 :: Int

  keyM <- fetchKey label
  key  <- maybe (generateKey cipher label) pure keyM

  sendM (putStrLn ("key file is: " <> ByteString.unpack (getLabel label)))

  secretNumber <- encrypt' key number
  sendM (LByteString.putStrLn (Aeson.encode secretNumber))

  pure key

--------------------------------------------------------------------------------
main :: IO ()
main = do
  -- We're going to store keys on the file system in the current directory.
  manager <- fileManager "."
  crypto <- initCryptonite manager

  (_ :: Either CryptoError (Key Cryptonite)) <-
    app & runCryptonite crypto & runThrow & runM

  pure ()

If the app function returns a unit instead of a key then it won't compile. Strangely, using a Proxy doesn't work here. I'm not sure why though.

So, if I understand you correctly, if I pull in your HasLabelled code then I could write the app signature like so:

app :: HasLabelled Something (Crypto k) sig m => m ()

Then GHC could figure out what k is and the user could leave it polymorphic. Does that sound correct?

Regarding injectivity, I had completely forgotten that data families (which I'm using) are always injective since they create new types. That plus functional dependencies is what allowed all this code to work in the mtl-based implementation.

TIL! That makes perfect sense, though. I honestly don’t have much experience with data families; clearly I shall have to explore this more 😊

Then GHC could figure out what k is and the user could leave it polymorphic. Does that sound correct?

Yes. app might have to e.g. use TypeApplications to specify @Something (like e.g. askArray does), but its callers will not.

Selfishly, I hope this works out well for you because I’d like to gather more feedback on the approach to make sure that I get it exactly right when adding it to fused-effects. My use in starlight is pretty compelling, but maybe it’s even better if tweaked just slightly…? With any luck, more experience will tell. All of which is to say, please do let me know how it goes!

I've been thinking about this a lot and have decided to keep the MTL interface.

The current interface is very straight forward and comfortable with good type inference. Asking my users to adopt fused-effects was already a bit of a stretch. Exposing the labelled effects interface introduces too much complexity.

I'm hoping to revisit this in the future and build an effect on top of the MTL class that I have right now.

Thanks for all your help.