diff --git a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs index f093b6f5613..86f64e3a6b6 100644 --- a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs +++ b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs @@ -419,7 +419,7 @@ This is very fiddly: - Sometimes the selector has been inlined. - We can't easily get access to the name of the method definition itself, so instead we mark that as INLINE and look for a special function ('stringToBuiltinString') that is in its - body (which we put inside 'noinline', see Note [noinline hack]). + body (and we use the OPAQUE pragma on that function to ensure it isn't inlined). - Sometimes our heuristics fail. - The actual definition of 'stringToBuiltinString' works, so in the worst case we fall back to using it and converting the list of characters into an expression. @@ -751,11 +751,11 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do Nothing -> throwSd UnsupportedError $ "Use of fromString on type other than builtin strings or bytestrings:" GHC.<+> GHC.ppr ty - -- 'stringToBuiltinByteString' invocation, will be wrapped in a 'noinline' + -- 'stringToBuiltinByteString' invocation (strip -> GHC.Var n) `GHC.App` (strip -> stringExprContent -> Just bs) | GHC.getName n == sbbsName -> pure $ PIR.Constant annMayInline $ PLC.someValue bs - -- 'stringToBuiltinString' invocation, will be wrapped in a 'noinline' + -- 'stringToBuiltinString' invocation (strip -> GHC.Var n) `GHC.App` (strip -> stringExprContent -> Just bs) | GHC.getName n == sbsName -> case TE.decodeUtf8' bs of Right t -> pure $ PIR.Constant annMayInline $ PLC.someValue t @@ -785,7 +785,7 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do -- Unboxed unit, (##). GHC.Var (GHC.idDetails -> GHC.DataConWorkId dc) | dc == GHC.unboxedUnitDataCon -> pure (PIR.mkConstant annMayInline ()) -- Ignore the magic 'noinline' function, it's the identity but has no unfolding. - -- See Note [noinline hack] + -- See Note [GHC.Magic.noinline] GHC.Var n `GHC.App` GHC.Type _ `GHC.App` arg | GHC.getName n == GHC.noinlineIdName -> compileExpr arg -- See Note [GHC runtime errors] -- diff --git a/plutus-tx/plutus-tx.cabal b/plutus-tx/plutus-tx.cabal index acf31d03b80..78a5854d81a 100644 --- a/plutus-tx/plutus-tx.cabal +++ b/plutus-tx/plutus-tx.cabal @@ -128,7 +128,6 @@ library , deriving-compat , extra , flat ^>=0.6 - , ghc-prim , hashable , lens , memory diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index c8166b6824b..6281249edb1 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -2,7 +2,6 @@ {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} -{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} @@ -21,14 +20,13 @@ import PlutusTx.Builtins.Internal import Data.Kind qualified as GHC import Data.String (IsString (..)) import Data.Text qualified as Text -import GHC.Magic qualified as Magic import Prelude qualified as Haskell (String) #if MIN_VERSION_base(4,20,0) import Prelude (type (~)) #endif -{- Note [noinline hack] +{- Note [GHC.Magic.noinline] 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 @@ -42,33 +40,20 @@ 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. -} -obfuscatedId :: a -> a -obfuscatedId a = a -{-# NOINLINE obfuscatedId #-} - stringToBuiltinByteString :: Haskell.String -> BuiltinByteString stringToBuiltinByteString str = encodeUtf8 $ stringToBuiltinString str -{-# INLINABLE stringToBuiltinByteString #-} +{-# OPAQUE stringToBuiltinByteString #-} stringToBuiltinString :: Haskell.String -> BuiltinString --- To explain why the obfuscatedId is here --- See Note [noinline hack] -stringToBuiltinString str = obfuscatedId (BuiltinString $ Text.pack str) -{-# INLINABLE stringToBuiltinString #-} +stringToBuiltinString str = BuiltinString (Text.pack str) +{-# OPAQUE stringToBuiltinString #-} -{- Same noinline hack as with `String` type. -} instance IsString BuiltinByteString where -- Try and make sure the dictionary selector goes away, it's simpler to match on -- the application of 'stringToBuiltinByteString' - -- See Note [noinline hack] - fromString = Magic.noinline stringToBuiltinByteString + fromString = stringToBuiltinByteString {-# INLINE fromString #-} -- We can't put this in `Builtins.hs`, since that force `O0` deliberately, which prevents @@ -76,8 +61,7 @@ instance IsString BuiltinByteString where instance IsString BuiltinString where -- Try and make sure the dictionary selector goes away, it's simpler to match on -- the application of 'stringToBuiltinString' - -- See Note [noinline hack] - fromString = Magic.noinline stringToBuiltinString + fromString = stringToBuiltinString {-# INLINE fromString #-} {- Note [Built-in types and their Haskell counterparts]