Skip to content

Commit

Permalink
Completely change API to declarative DSL and implement Plutarch trans…
Browse files Browse the repository at this point in the history
…piler

Changes:

* Completely change API to declarative DSL (closes #24 #81, part of #29)
* Implement Plutarch transpiler (closes #48 #79)
* Support lifting Plutus functions to declarative DSL (closes #68)
* Compilation pass changing all error messages to codes
  and saving their correspondence to table
* Remove `Stages` concept altogeter (see issue #92)
  • Loading branch information
uhbif19 committed Jun 30, 2024
1 parent 8722465 commit bc20951
Show file tree
Hide file tree
Showing 24 changed files with 1,535 additions and 713 deletions.
2 changes: 1 addition & 1 deletion .ghcid
Original file line number Diff line number Diff line change
@@ -1 +1 @@
--command="cabal repl test-suite:cem-sdk-test" -W -T ":main --failure-report=/tmp/hspec-report.txt -r"
--command="cabal repl test-suite:cem-sdk-test" -W -T ":main"
1 change: 1 addition & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -16,3 +16,4 @@
- ignore: {name: Use unless}
- ignore: {name: "Use asks"}
- ignore: {name: "Eta reduce"}
- ignore: {name: Use concatMap}
11 changes: 9 additions & 2 deletions cem-script.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ common common-lang

build-depends:
, base
, containers
, mtl
, transformers

Expand All @@ -42,6 +43,7 @@ common common-lang
LambdaCase
NoImplicitPrelude
NoPolyKinds
OverloadedRecordDot
OverloadedStrings
PatternSynonyms
QuantifiedConstraints
Expand Down Expand Up @@ -98,11 +100,12 @@ common common-offchain
, cardano-ledger-babbage
, cardano-ledger-core
, cardano-ledger-shelley
, containers
, filepath
, ouroboros-network-protocols
, pretty-show
, prettyprinter
, retry
, singletons-th
, text
, time
, unix
Expand All @@ -114,7 +117,10 @@ common common-executable
library data-spine
import: common-lang
hs-source-dirs: src-lib/data-spine

-- FIXME: was not meant to be dependent on Plutus...
build-depends:
, plutus-tx
, singletons
, template-haskell

Expand All @@ -129,6 +135,7 @@ library cardano-extras
build-depends: template-haskell
exposed-modules:
Cardano.Extras
Plutarch.Extras
Plutus.Deriving
Plutus.Extras

Expand All @@ -149,7 +156,7 @@ library
Cardano.CEM.Monads.L1
Cardano.CEM.OffChain
Cardano.CEM.OnChain
Cardano.CEM.Stages
Cardano.CEM.DSL
Cardano.CEM.Testing.StateMachine
Cardano.CEM.TH

Expand Down
43 changes: 43 additions & 0 deletions src-lib/cardano-extras/Plutarch/Extras.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
{-# LANGUAGE QualifiedDo #-}

module Plutarch.Extras where

import Prelude

import Plutarch
import Plutarch.Builtin
import Plutarch.LedgerApi
import Plutarch.LedgerApi.AssocMap (KeyGuarantees (..))
import Plutarch.LedgerApi.Value
import Plutarch.Maybe (pfromJust)
import Plutarch.Monadic qualified as P
import Plutarch.Prelude

pMkAdaOnlyValue :: Term s (PInteger :--> PValue Unsorted _)
pMkAdaOnlyValue = phoistAcyclic $ plam $ \lovelaces ->
pforgetSorted $
psingletonData # padaSymbolData # pdata padaToken # pdata lovelaces

pscriptHashAddress :: Term s (PAsData PScriptHash :--> PAddress)
pscriptHashAddress = plam $ \datahash ->
let credential = pcon (PScriptCredential (pdcons @"_0" # datahash #$ pdnil))
nothing = pdata $ pcon (PDNothing pdnil)
inner = pdcons @"credential" # pdata credential #$ pdcons @"stakingCredential" # nothing #$ pdnil
in pcon (PAddress inner)

ppkhAddress :: Term s (PAsData PPubKeyHash :--> PAddress)
ppkhAddress = plam $ \datahash ->
let credential = pcon (PPubKeyCredential (pdcons @"_0" # datahash #$ pdnil))
nothing = pdata $ pcon (PDNothing pdnil)
inner = pdcons @"credential" # pdata credential #$ pdcons @"stakingCredential" # nothing #$ pdnil
in pcon (PAddress inner)

getOwnAddress :: ClosedTerm (PAsData PScriptContext :--> PAsData PAddress)
getOwnAddress = phoistAcyclic $ plam $ \ctx -> P.do
PSpending outRef' <- pmatch $ pfromData $ pfield @"purpose" # ctx
pfield @"address"
#$ pfield @"resolved"
#$ pfromJust
#$ (pfindOwnInput # (pfield @"inputs" #$ pfield @"txInfo" # ctx))
#$ pfield @"_0"
# outRef'
98 changes: 86 additions & 12 deletions src-lib/data-spine/Data/Spine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,26 @@
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE PolyKinds #-}

module Data.Spine (HasSpine (..), deriveSpine, OfSpine (..)) where
module Data.Spine where

-- TODO
-- (HasSpine (..), deriveSpine, OfSpine (..))

import Prelude

import Data.Data (Proxy)
import Data.List (elemIndex)
import Data.Map qualified as Map
import Data.Maybe (mapMaybe)
import Data.Void (Void)
import GHC.Natural (Natural)
import GHC.Records (HasField)
import GHC.TypeLits (KnownSymbol, symbolVal)
import Language.Haskell.TH
import Language.Haskell.TH.Syntax

import PlutusTx (FromData, ToData, UnsafeFromData, unstableMakeIsData)

-- | Definitions

{- | Spine is datatype, which tags constructors of ADT.
Expand All @@ -22,9 +35,47 @@ class
) =>
HasSpine sop
where
type Spine sop
type Spine sop = spine | spine -> sop
getSpine :: sop -> Spine sop

-- | Version of `HasSpine` knowing its Plutus Data encoding
class
( Enum (Spine sop)
, Bounded (Spine sop)
, HasSpine sop
, UnsafeFromData sop
, ToData sop
, FromData sop
) =>
HasPlutusSpine sop
where
fieldsMap :: Map.Map (Spine sop) [String]

toNat :: Int -> Natural
toNat = fromInteger . toInteger

spineFieldsNum :: forall sop. (HasPlutusSpine sop) => Spine sop -> Natural
spineFieldsNum spine = toNat $ length $ (fieldsMap @sop) Map.! spine

-- TODO: use spine do discriminate
fieldNum ::
forall sop label.
(HasPlutusSpine sop, KnownSymbol label) =>
Proxy label ->
Natural
fieldNum proxyLabel =
head $ mapMaybe fieldIndex (Map.elems $ fieldsMap @sop)
where
fieldName = symbolVal proxyLabel
fieldIndex dict = toNat <$> elemIndex fieldName dict

allSpines :: forall sop. (HasPlutusSpine sop) => [Spine sop]
allSpines = [Prelude.minBound .. Prelude.maxBound]

instance HasSpine Void where
type Spine Void = Void
getSpine = \case {}

instance (HasSpine sop1, HasSpine sop2) => HasSpine (sop1, sop2) where
type Spine (sop1, sop2) = (Spine sop1, Spine sop2)
getSpine (d1, d2) = (getSpine d1, getSpine d2)
Expand All @@ -33,15 +84,14 @@ instance (HasSpine sop) => HasSpine (Maybe sop) where
type Spine (Maybe sop) = Maybe (Spine sop)
getSpine = fmap getSpine

-- | Newtype encoding sop value of fixed known spine
newtype OfSpine (x :: Spine datatype) = UnsafeMkOfSpine {getValue :: datatype}
-- Deriving utils

-- | Deriving utils
addSuffix :: Name -> String -> Name
addSuffix (Name (OccName name) flavour) suffix =
Name (OccName $ name <> suffix) flavour

reifyDatatype :: Name -> Q (Name, [Name])
-- FIXME: cleaner return type
reifyDatatype :: Name -> Q (Name, [Name], [[Name]])
reifyDatatype ty = do
(TyConI tyCon) <- reify ty
(name, cs :: [Con]) <-
Expand All @@ -50,7 +100,17 @@ reifyDatatype ty = do
NewtypeD _ n _ _ cs _ -> pure (n, [cs])
_ -> fail "deriveTags: only 'data' and 'newtype' are supported"
csNames <- mapM consName cs
return (name, csNames)
csFields <- mapM consFields cs
return (name, csNames, csFields)
where
fieldName (name, _, _) = name
consFields (RecC _ fields) = return $ map fieldName fields
consFields (NormalC _ fields) | length fields == 0 = return []
consFields _ =
fail $
"Spine: only Sum-of-Products are supported, but "
<> show ty
<> " is not"

consName :: (MonadFail m) => Con -> m Name
consName cons =
Expand All @@ -61,7 +121,7 @@ consName cons =

deriveTags :: Name -> String -> [Name] -> Q [Dec]
deriveTags ty suff classes = do
(tyName, csNames) <- reifyDatatype ty
(tyName, csNames, _) <- reifyDatatype ty
-- XXX: Quasi-quote splice does not work for case matches list
let cs = map (\name -> NormalC (addSuffix name suff) []) csNames
v =
Expand All @@ -70,7 +130,7 @@ deriveTags ty suff classes = do

deriveMapping :: Name -> String -> Q Exp
deriveMapping ty suff = do
(_, csNames) <- reifyDatatype ty
(_, csNames, _) <- reifyDatatype ty
-- XXX: Quasi-quote splice does not work for case matches list
let
matches =
Expand All @@ -87,9 +147,7 @@ deriveSpine name = do
let
suffix = "Spine"
spineName = addSuffix name suffix
spineDec <- deriveTags name suffix [''Eq, ''Ord, ''Enum, ''Show]
-- TODO: derive Sing
-- TODO: derive HasField (OfSpine ...)
spineDec <- deriveTags name suffix [''Eq, ''Ord, ''Enum, ''Show, ''Bounded]

decls <-
[d|
Expand All @@ -98,3 +156,19 @@ deriveSpine name = do
getSpine = $(deriveMapping name suffix)
|]
return $ spineDec <> decls

derivePlutusSpine :: Name -> Q [Dec]
derivePlutusSpine name = do
decls <- deriveSpine name
isDataDecls <- unstableMakeIsData name

(_, _, fieldsNames') <- reifyDatatype name
let fieldsNames = map (map nameBase) fieldsNames'
instanceDecls <-
[d|
instance HasPlutusSpine $(conT name) where
fieldsMap =
Map.fromList $ zip (allSpines @($(conT name))) fieldsNames
|]

return $ decls <> isDataDecls <> instanceDecls
Loading

0 comments on commit bc20951

Please sign in to comment.