{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.String (PString, pfromText, pencodeUtf8, pdecodeUtf8) where
import Data.String (IsString, fromString)
import Data.Text (Text)
import Data.Text qualified as Text
import GHC.Generics (Generic)
import Plutarch.Bool (PEq, (#==))
import Plutarch.ByteString (PByteString)
import Plutarch.Internal (Term, (#), (:-->))
import Plutarch.Internal.Newtype (PlutusTypeNewtype)
import Plutarch.Internal.Other (POpaque)
import Plutarch.Internal.PlutusType (DPTStrat, DerivePlutusType, PlutusType)
import Plutarch.Lift (
DerivePConstantDirect (DerivePConstantDirect),
PConstantDecl,
PLifted,
PUnsafeLiftDecl,
pconstant,
)
import Plutarch.Unsafe (punsafeBuiltin)
import PlutusCore qualified as PLC
newtype PString s = PString (Term s POpaque)
deriving stock (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PString s) x -> PString s
forall (s :: S) x. PString s -> Rep (PString s) x
$cto :: forall (s :: S) x. Rep (PString s) x -> PString s
$cfrom :: forall (s :: S) x. PString s -> Rep (PString s) x
Generic)
deriving anyclass (forall (s :: S). PString s -> Term s (PInner PString)
forall (s :: S) (b :: PType).
Term s (PInner PString) -> (PString s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PString) -> (PString s -> Term s b) -> Term s b
$cpmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PString) -> (PString s -> Term s b) -> Term s b
pcon' :: forall (s :: S). PString s -> Term s (PInner PString)
$cpcon' :: forall (s :: S). PString s -> Term s (PInner PString)
PlutusType)
instance DerivePlutusType PString where type DPTStrat _ = PlutusTypeNewtype
instance PUnsafeLiftDecl PString where type PLifted PString = Text
deriving via (DerivePConstantDirect Text PString) instance PConstantDecl Text
{-# DEPRECATED pfromText "Use `pconstant` instead." #-}
pfromText :: Text.Text -> Term s PString
pfromText :: forall (s :: S). Text -> Term s PString
pfromText = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant
instance IsString (Term s PString) where
fromString :: String -> Term s PString
fromString = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
instance PEq PString where
Term s PString
x #== :: forall (s :: S). Term s PString -> Term s PString -> Term s PBool
#== Term s PString
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.EqualsString forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
y
instance Semigroup (Term s PString) where
Term s PString
x <> :: Term s PString -> Term s PString -> Term s PString
<> Term s PString
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.AppendString forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
y
instance Monoid (Term s PString) where
mempty :: Term s PString
mempty = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Text
Text.empty
pencodeUtf8 :: Term s (PString :--> PByteString)
pencodeUtf8 :: forall (s :: S). Term s (PString :--> PByteString)
pencodeUtf8 = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.EncodeUtf8
pdecodeUtf8 :: Term s (PByteString :--> PString)
pdecodeUtf8 :: forall (s :: S). Term s (PByteString :--> PString)
pdecodeUtf8 = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.DecodeUtf8