Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Add some comments on FromBuiltin/ToBuiltin/Lift #5585

Merged
merged 7 commits into from
Nov 22, 2023
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
149 changes: 88 additions & 61 deletions plutus-tx/src/PlutusTx/Builtins/Class.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
-- editorconfig-checker-disable-file
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -fno-specialise #-}
Expand All @@ -27,21 +25,14 @@ import PlutusTx.Bool (Bool (..))
import PlutusTx.Integer (Integer)
import Prelude qualified as Haskell (String)

{- Note [Fundeps versus type families in To/FromBuiltin]
We could use a type family here to get the builtin representation of a type. After all, it's
entirely determined by the Haskell type.

However, this is harder for the plugin to deal with. It's okay to have a type variable
for the representation type that needs to be instantiated later, but it's *not* okay to
have an irreducible type application on a type variable. So fundeps are much nicer here.
-}

-- See Note [Builtin types and their Haskell versions]
{-|
A class witnessing the ability to convert from the builtin representation to the Haskell representation.
-}
class FromBuiltin arep a | arep -> a where
fromBuiltin :: arep -> a

-- See Note [Builtin types and their Haskell versions]
{-|
A class witnessing the ability to convert from the Haskell representation to the builtin representation.
-}
Expand All @@ -62,17 +53,6 @@ instance ToBuiltin Bool BuiltinBool where
{-# INLINABLE toBuiltin #-}
toBuiltin b = if b then true else false

{- Note [Strict conversions to/from unit]
Converting to/from unit *should* be straightforward: just ``const ()`.`
*But* GHC is very good at optimizing this, and we sometimes use unit
where side effects matter, e.g. as the result of `trace`. So GHC will
tend to turn `fromBuiltin (trace s)` into `()`, which is wrong.

So we want our conversions to/from unit to be strict in Haskell. This
means we need to case pointlessly on the argument, which means we need
case on unit (`chooseUnit`) as a builtin. But then it all works okay.
-}

instance FromBuiltin BuiltinUnit () where
-- See Note [Strict conversions to/from unit]
{-# INLINABLE fromBuiltin #-}
Expand All @@ -89,27 +69,6 @@ instance ToBuiltin ByteString BuiltinByteString where
{-# INLINABLE toBuiltin #-}
toBuiltin = BuiltinByteString

{- Note [noinline hack]
For some functions we have two conflicting desires:
- We want to have the unfolding available for the plugin.
- We don't want the function to *actually* get inlined before the plugin runs, since we rely
on being able to see the original function for some reason.

'INLINABLE' achieves the first, but may cause the function to be inlined too soon.

We can solve this at specific call sites by using the 'noinline' magic function from
GHC. This stops GHC from inlining it. As a bonus, it also won't be inlined if
that function is compiled later into the body of another function.

We do therefore need to handle 'noinline' in the plugin, as it itself does not have
an unfolding.

Another annoying quirk: even if you have 'noinline'd a function call, if the body is
a single variable, it will still inline! This is the case for the obvious definition
of 'stringToBuiltinString' (since the newtype constructor vanishes), so we have to add
some obfuscation to the body to prevent it inlining.
-}

-- We can't put this in `Builtins.hs`, since that force `O0` deliberately, which prevents
-- the unfoldings from going in. So we just stick it here. Fiddly.
instance IsString BuiltinString where
Expand Down Expand Up @@ -148,20 +107,6 @@ instance IsString BuiltinByteString where
stringToBuiltinByteString :: Haskell.String -> BuiltinByteString
stringToBuiltinByteString str = encodeUtf8 $ stringToBuiltinString str

{- Note [From/ToBuiltin instances for polymorphic builtin types]
For various technical reasons
(see Note [Representable built-in functions over polymorphic built-in types])
it's not always easy to provide polymorphic constructors for builtin types, but
we can usually provide destructors.

What this means in practice is that we can write a generic FromBuiltin instance
for pairs that makes use of polymorphic fst/snd builtins, but we can't write
a polymorphic ToBuiltin instance because we'd need a polymorphic version of (,).

Instead we write monomorphic instances corresponding to monomorphic constructor
builtins that we add for specific purposes.
-}

instance (FromBuiltin arep a, FromBuiltin brep b) => FromBuiltin (BuiltinPair arep brep) (a,b) where
{-# INLINABLE fromBuiltin #-}
fromBuiltin p = (fromBuiltin $ fst p, fromBuiltin $ snd p)
Expand Down Expand Up @@ -220,4 +165,86 @@ instance ToBuiltin BLS12_381.Pairing.MlResult BuiltinBLS12_381_MlResult where
{-# INLINABLE toBuiltin #-}
toBuiltin = BuiltinBLS12_381_MlResult

{- Note [Builtin types and their Haskell versions]
Consider the builtin pair type. In Plutus Tx, we have an (opaque) type for
this. It's opaque because you can't actually pattern match on it, instead you can
only in fact use the specific functions that are available as builtins.

We _also_ have the normal Haskell pair type. This is very different: you can
pattern match on it, and you can use whatever user-defined functions you like on it.

Users would really like to use the latter, and not the former. So we often want
to _wrap_ our builtin functions with little adapters that convert between the
"opaque builtin" "version" of a type and the "normal Haskell" "version" of a type.

This is what the ToBuiltin and FromBuiltin classes do. They let us write wrappers
for builtins relatively consistently by just calling toBuiltin on their arguments
and fromBuiltin on the result. They shouldn't really be used otherwise.

Ideally, we would not have instances for types which don't have a different
Haskell representation type, such as Integer. Integer in Plutus Tx user code _is_ the
opaque builtin type, we don't expose a different one. So there's no conversion to
do. However, this interacts badly with the instances for polymorphic builtin types, which
also convert the type _inside_ them. (This is necessary to avoid doing multiple
traversals of the type, e.g. we don't want to turn a builtin list into a Haskell
list, and then traverse it again to conver the contents). Then we _need_ instances
for all builtin types, even if they don't quite make sense.

Possibly this indicates that these type classes are a bit too 'ad-hoc' and we should
get rid of them.
-}

{- Note [Fundeps versus type families in To/FromBuiltin]
We could use a type family here to get the builtin representation of a type. After all, it's
entirely determined by the Haskell type.

However, this is harder for the plugin to deal with. It's okay to have a type variable
for the representation type that needs to be instantiated later, but it's *not* okay to
have an irreducible type application on a type variable. So fundeps are much nicer here.
-}

{- Note [Strict conversions to/from unit]
Converting to/from unit *should* be straightforward: just `const ()`.
*But* GHC is very good at optimizing this, and we sometimes use unit
where side effects matter, e.g. as the result of `trace`. So GHC will
tend to turn `fromBuiltin (trace s)` into `()`, which is wrong.

So we want our conversions to/from unit to be strict in Haskell. This
means we need to case pointlessly on the argument, which means we need
case on unit (`chooseUnit`) as a builtin. But then it all works okay.
-}

{- Note [noinline hack]
For some functions we have two conflicting desires:
- We want to have the unfolding available for the plugin.
- We don't want the function to *actually* get inlined before the plugin runs, since we rely
on being able to see the original function for some reason.

'INLINABLE' achieves the first, but may cause the function to be inlined too soon.
Comment on lines +218 to +223
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I remember RV having a somewhat similar problem. I think the solution I came up at the time was to turn

f = body
{-# INLINEABLE f #-}

into

f = res where
   res = body
   {-# NOINLINE res #-}
{-# INLINE f #-}

Might want to try it here?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, although the current hack has worked okay for some time.


We can solve this at specific call sites by using the 'noinline' magic function from
GHC. This stops GHC from inlining it. As a bonus, it also won't be inlined if
that function is compiled later into the body of another function.

We do therefore need to handle 'noinline' in the plugin, as it itself does not have
an unfolding.

Another annoying quirk: even if you have 'noinline'd a function call, if the body is
a single variable, it will still inline! This is the case for the obvious definition
of 'stringToBuiltinString' (since the newtype constructor vanishes), so we have to add
some obfuscation to the body to prevent it inlining.
-}

{- Note [From/ToBuiltin instances for polymorphic builtin types]
For various technical reasons
(see Note [Representable built-in functions over polymorphic built-in types])
it's not always easy to provide polymorphic constructors for builtin types, but
we can usually provide destructors.

What this means in practice is that we can write a generic FromBuiltin instance
for pairs that makes use of polymorphic fst/snd builtins, but we can't write
a polymorphic ToBuiltin instance because we'd need a polymorphic version of (,).

Instead we write monomorphic instances corresponding to monomorphic constructor
builtins that we add for specific purposes.
-}
69 changes: 62 additions & 7 deletions plutus-tx/src/PlutusTx/Lift/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ import PlutusCore.Quote
import PlutusIR.MkPir
import PlutusTx.Builtins
import PlutusTx.Builtins.Class (FromBuiltin)
import PlutusTx.Builtins.Internal (BuiltinList)
import PlutusTx.Builtins.Internal (BuiltinBool, BuiltinList, BuiltinPair, BuiltinUnit)

import Language.Haskell.TH qualified as TH hiding (newName)

Expand Down Expand Up @@ -115,7 +115,7 @@ instance Typeable uni (->) where
-- Primitives

typeRepBuiltin
:: forall (a :: GHC.Type) uni fun. uni `PLC.HasTypeLevel` a
:: forall k (a :: k) uni fun. uni `PLC.HasTypeLevel` a
=> Proxy a -> RTCompile uni fun (Type TyName uni ())
typeRepBuiltin (_ :: Proxy a) = pure $ mkTyBuiltin @_ @a ()

Expand All @@ -135,56 +135,111 @@ instance (TypeError ('Text "Int is not supported, use Integer instead"))
instance uni `PLC.HasTypeLevel` Integer => Typeable uni Integer where
typeRep = typeRepBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` Integer => Lift uni Integer where
lift = liftBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` BS.ByteString => Typeable uni BS.ByteString where
typeRep = typeRepBuiltin

instance uni `PLC.HasTermLevel` BS.ByteString => Lift uni BS.ByteString where
lift = liftBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` Data => Typeable uni BuiltinData where
typeRep _ = typeRepBuiltin (Proxy @Data)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` Data => Lift uni BuiltinData where
lift = liftBuiltin . builtinDataToData

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` BS.ByteString => Typeable uni BuiltinByteString where
typeRep _proxyPByteString = typeRepBuiltin (Proxy @BS.ByteString)
typeRep _proxyByteString = typeRepBuiltin (Proxy @BS.ByteString)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` BS.ByteString => Lift uni BuiltinByteString where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` T.Text => Typeable uni BuiltinString where
typeRep _proxyPByteString = typeRepBuiltin (Proxy @T.Text)
typeRep _proxyByteString = typeRepBuiltin (Proxy @T.Text)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` T.Text => Lift uni BuiltinString where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` () => Typeable uni BuiltinUnit where
typeRep _proxyUnit = typeRepBuiltin (Proxy @())

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` () => Lift uni BuiltinUnit where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` Bool => Typeable uni BuiltinBool where
typeRep _proxyBool = typeRepBuiltin (Proxy @Bool)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` Bool => Lift uni BuiltinBool where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` [] => Typeable uni BuiltinList where
typeRep _proxyBuiltinList = typeRepBuiltin (Proxy @[])

-- See Note [Lift and Typeable instances for builtins]
instance (FromBuiltin arep a, uni `PLC.HasTermLevel` [a]) => Lift uni (BuiltinList arep) where
lift = liftBuiltin . fromBuiltin

instance uni `PLC.HasTypeLevel` (,) => Typeable uni BuiltinPair where
typeRep _proxyBuiltinPair = typeRepBuiltin (Proxy @(,))

instance (FromBuiltin arep a, FromBuiltin brep b, uni `PLC.HasTermLevel` (a, b)) =>
Lift uni (BuiltinPair arep brep) where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` PlutusCore.Crypto.BLS12_381.G1.Element =>
Typeable uni BuiltinBLS12_381_G1_Element where
typeRep _ = typeRepBuiltin (Proxy @PlutusCore.Crypto.BLS12_381.G1.Element)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` PlutusCore.Crypto.BLS12_381.G1.Element =>
Lift uni BuiltinBLS12_381_G1_Element where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` PlutusCore.Crypto.BLS12_381.G2.Element =>
Typeable uni BuiltinBLS12_381_G2_Element where
typeRep _ = typeRepBuiltin (Proxy @PlutusCore.Crypto.BLS12_381.G2.Element)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` PlutusCore.Crypto.BLS12_381.G2.Element =>
Lift uni BuiltinBLS12_381_G2_Element where
lift = liftBuiltin . fromBuiltin

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTypeLevel` PlutusCore.Crypto.BLS12_381.Pairing.MlResult =>
Typeable uni BuiltinBLS12_381_MlResult where
typeRep _ = typeRepBuiltin (Proxy @PlutusCore.Crypto.BLS12_381.Pairing.MlResult)

-- See Note [Lift and Typeable instances for builtins]
instance uni `PLC.HasTermLevel` PlutusCore.Crypto.BLS12_381.Pairing.MlResult =>
Lift uni BuiltinBLS12_381_MlResult where
lift = liftBuiltin . fromBuiltin

{- Note [Lift and Typeable instances for builtins]
We can, generally, lift builtin values. We just make a constant with the value inside.
However, in Plutus Tx we use opaque types for most builtin types to avoid people
trying to pattern match on them. So the types don't quite match up with what we need
to put inside the constant.

Fortunately, we have To/FromBuiltin, which happen to do what we want.
See Note [Builtin types and their Haskell versions].
This is arguably slightly an abuse: the versions of the types that we want in
Plutus Tx source code and the versions that we use as the implementations of
the builtin types in the universe could be different. But in practice they
aren't. So we can write fairly straightforward instances for most types.

Similarly, for Typeable we may have to use a different type from the opaque one.
michaelpj marked this conversation as resolved.
Show resolved Hide resolved
-}
2 changes: 0 additions & 2 deletions plutus-tx/src/PlutusTx/Lift/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@
{-# OPTIONS_GHC -Wno-orphans #-}
module PlutusTx.Lift.Instances () where

import PlutusCore.Data
import PlutusTx.Bool (Bool (..))
import PlutusTx.Either (Either (..))
import PlutusTx.Lift.TH
Expand All @@ -34,4 +33,3 @@ makeLift ''(,,)
makeLift ''(,,,)
makeLift ''(,,,,)

makeLift ''Data