Skip to content

Commit bc20951

Browse files
committed
Completely change API to declarative DSL and implement Plutarch transpiler
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)
1 parent 8722465 commit bc20951

File tree

24 files changed

+1535
-713
lines changed

24 files changed

+1535
-713
lines changed

.ghcid

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
--command="cabal repl test-suite:cem-sdk-test" -W -T ":main --failure-report=/tmp/hspec-report.txt -r"
1+
--command="cabal repl test-suite:cem-sdk-test" -W -T ":main"

.hlint.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,3 +16,4 @@
1616
- ignore: {name: Use unless}
1717
- ignore: {name: "Use asks"}
1818
- ignore: {name: "Eta reduce"}
19+
- ignore: {name: Use concatMap}

cem-script.cabal

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ common common-lang
2828

2929
build-depends:
3030
, base
31+
, containers
3132
, mtl
3233
, transformers
3334

@@ -42,6 +43,7 @@ common common-lang
4243
LambdaCase
4344
NoImplicitPrelude
4445
NoPolyKinds
46+
OverloadedRecordDot
4547
OverloadedStrings
4648
PatternSynonyms
4749
QuantifiedConstraints
@@ -98,11 +100,12 @@ common common-offchain
98100
, cardano-ledger-babbage
99101
, cardano-ledger-core
100102
, cardano-ledger-shelley
101-
, containers
102103
, filepath
103104
, ouroboros-network-protocols
104105
, pretty-show
106+
, prettyprinter
105107
, retry
108+
, singletons-th
106109
, text
107110
, time
108111
, unix
@@ -114,7 +117,10 @@ common common-executable
114117
library data-spine
115118
import: common-lang
116119
hs-source-dirs: src-lib/data-spine
120+
121+
-- FIXME: was not meant to be dependent on Plutus...
117122
build-depends:
123+
, plutus-tx
118124
, singletons
119125
, template-haskell
120126

@@ -129,6 +135,7 @@ library cardano-extras
129135
build-depends: template-haskell
130136
exposed-modules:
131137
Cardano.Extras
138+
Plutarch.Extras
132139
Plutus.Deriving
133140
Plutus.Extras
134141

@@ -149,7 +156,7 @@ library
149156
Cardano.CEM.Monads.L1
150157
Cardano.CEM.OffChain
151158
Cardano.CEM.OnChain
152-
Cardano.CEM.Stages
159+
Cardano.CEM.DSL
153160
Cardano.CEM.Testing.StateMachine
154161
Cardano.CEM.TH
155162

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
{-# LANGUAGE QualifiedDo #-}
2+
3+
module Plutarch.Extras where
4+
5+
import Prelude
6+
7+
import Plutarch
8+
import Plutarch.Builtin
9+
import Plutarch.LedgerApi
10+
import Plutarch.LedgerApi.AssocMap (KeyGuarantees (..))
11+
import Plutarch.LedgerApi.Value
12+
import Plutarch.Maybe (pfromJust)
13+
import Plutarch.Monadic qualified as P
14+
import Plutarch.Prelude
15+
16+
pMkAdaOnlyValue :: Term s (PInteger :--> PValue Unsorted _)
17+
pMkAdaOnlyValue = phoistAcyclic $ plam $ \lovelaces ->
18+
pforgetSorted $
19+
psingletonData # padaSymbolData # pdata padaToken # pdata lovelaces
20+
21+
pscriptHashAddress :: Term s (PAsData PScriptHash :--> PAddress)
22+
pscriptHashAddress = plam $ \datahash ->
23+
let credential = pcon (PScriptCredential (pdcons @"_0" # datahash #$ pdnil))
24+
nothing = pdata $ pcon (PDNothing pdnil)
25+
inner = pdcons @"credential" # pdata credential #$ pdcons @"stakingCredential" # nothing #$ pdnil
26+
in pcon (PAddress inner)
27+
28+
ppkhAddress :: Term s (PAsData PPubKeyHash :--> PAddress)
29+
ppkhAddress = plam $ \datahash ->
30+
let credential = pcon (PPubKeyCredential (pdcons @"_0" # datahash #$ pdnil))
31+
nothing = pdata $ pcon (PDNothing pdnil)
32+
inner = pdcons @"credential" # pdata credential #$ pdcons @"stakingCredential" # nothing #$ pdnil
33+
in pcon (PAddress inner)
34+
35+
getOwnAddress :: ClosedTerm (PAsData PScriptContext :--> PAsData PAddress)
36+
getOwnAddress = phoistAcyclic $ plam $ \ctx -> P.do
37+
PSpending outRef' <- pmatch $ pfromData $ pfield @"purpose" # ctx
38+
pfield @"address"
39+
#$ pfield @"resolved"
40+
#$ pfromJust
41+
#$ (pfindOwnInput # (pfield @"inputs" #$ pfield @"txInfo" # ctx))
42+
#$ pfield @"_0"
43+
# outRef'

src-lib/data-spine/Data/Spine.hs

Lines changed: 86 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,26 @@
33
{-# LANGUAGE DefaultSignatures #-}
44
{-# LANGUAGE PolyKinds #-}
55

6-
module Data.Spine (HasSpine (..), deriveSpine, OfSpine (..)) where
6+
module Data.Spine where
7+
8+
-- TODO
9+
-- (HasSpine (..), deriveSpine, OfSpine (..))
710

811
import Prelude
912

13+
import Data.Data (Proxy)
14+
import Data.List (elemIndex)
15+
import Data.Map qualified as Map
16+
import Data.Maybe (mapMaybe)
17+
import Data.Void (Void)
18+
import GHC.Natural (Natural)
19+
import GHC.Records (HasField)
20+
import GHC.TypeLits (KnownSymbol, symbolVal)
1021
import Language.Haskell.TH
1122
import Language.Haskell.TH.Syntax
1223

24+
import PlutusTx (FromData, ToData, UnsafeFromData, unstableMakeIsData)
25+
1326
-- | Definitions
1427

1528
{- | Spine is datatype, which tags constructors of ADT.
@@ -22,9 +35,47 @@ class
2235
) =>
2336
HasSpine sop
2437
where
25-
type Spine sop
38+
type Spine sop = spine | spine -> sop
2639
getSpine :: sop -> Spine sop
2740

41+
-- | Version of `HasSpine` knowing its Plutus Data encoding
42+
class
43+
( Enum (Spine sop)
44+
, Bounded (Spine sop)
45+
, HasSpine sop
46+
, UnsafeFromData sop
47+
, ToData sop
48+
, FromData sop
49+
) =>
50+
HasPlutusSpine sop
51+
where
52+
fieldsMap :: Map.Map (Spine sop) [String]
53+
54+
toNat :: Int -> Natural
55+
toNat = fromInteger . toInteger
56+
57+
spineFieldsNum :: forall sop. (HasPlutusSpine sop) => Spine sop -> Natural
58+
spineFieldsNum spine = toNat $ length $ (fieldsMap @sop) Map.! spine
59+
60+
-- TODO: use spine do discriminate
61+
fieldNum ::
62+
forall sop label.
63+
(HasPlutusSpine sop, KnownSymbol label) =>
64+
Proxy label ->
65+
Natural
66+
fieldNum proxyLabel =
67+
head $ mapMaybe fieldIndex (Map.elems $ fieldsMap @sop)
68+
where
69+
fieldName = symbolVal proxyLabel
70+
fieldIndex dict = toNat <$> elemIndex fieldName dict
71+
72+
allSpines :: forall sop. (HasPlutusSpine sop) => [Spine sop]
73+
allSpines = [Prelude.minBound .. Prelude.maxBound]
74+
75+
instance HasSpine Void where
76+
type Spine Void = Void
77+
getSpine = \case {}
78+
2879
instance (HasSpine sop1, HasSpine sop2) => HasSpine (sop1, sop2) where
2980
type Spine (sop1, sop2) = (Spine sop1, Spine sop2)
3081
getSpine (d1, d2) = (getSpine d1, getSpine d2)
@@ -33,15 +84,14 @@ instance (HasSpine sop) => HasSpine (Maybe sop) where
3384
type Spine (Maybe sop) = Maybe (Spine sop)
3485
getSpine = fmap getSpine
3586

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

39-
-- | Deriving utils
4089
addSuffix :: Name -> String -> Name
4190
addSuffix (Name (OccName name) flavour) suffix =
4291
Name (OccName $ name <> suffix) flavour
4392

44-
reifyDatatype :: Name -> Q (Name, [Name])
93+
-- FIXME: cleaner return type
94+
reifyDatatype :: Name -> Q (Name, [Name], [[Name]])
4595
reifyDatatype ty = do
4696
(TyConI tyCon) <- reify ty
4797
(name, cs :: [Con]) <-
@@ -50,7 +100,17 @@ reifyDatatype ty = do
50100
NewtypeD _ n _ _ cs _ -> pure (n, [cs])
51101
_ -> fail "deriveTags: only 'data' and 'newtype' are supported"
52102
csNames <- mapM consName cs
53-
return (name, csNames)
103+
csFields <- mapM consFields cs
104+
return (name, csNames, csFields)
105+
where
106+
fieldName (name, _, _) = name
107+
consFields (RecC _ fields) = return $ map fieldName fields
108+
consFields (NormalC _ fields) | length fields == 0 = return []
109+
consFields _ =
110+
fail $
111+
"Spine: only Sum-of-Products are supported, but "
112+
<> show ty
113+
<> " is not"
54114

55115
consName :: (MonadFail m) => Con -> m Name
56116
consName cons =
@@ -61,7 +121,7 @@ consName cons =
61121

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

71131
deriveMapping :: Name -> String -> Q Exp
72132
deriveMapping ty suff = do
73-
(_, csNames) <- reifyDatatype ty
133+
(_, csNames, _) <- reifyDatatype ty
74134
-- XXX: Quasi-quote splice does not work for case matches list
75135
let
76136
matches =
@@ -87,9 +147,7 @@ deriveSpine name = do
87147
let
88148
suffix = "Spine"
89149
spineName = addSuffix name suffix
90-
spineDec <- deriveTags name suffix [''Eq, ''Ord, ''Enum, ''Show]
91-
-- TODO: derive Sing
92-
-- TODO: derive HasField (OfSpine ...)
150+
spineDec <- deriveTags name suffix [''Eq, ''Ord, ''Enum, ''Show, ''Bounded]
93151

94152
decls <-
95153
[d|
@@ -98,3 +156,19 @@ deriveSpine name = do
98156
getSpine = $(deriveMapping name suffix)
99157
|]
100158
return $ spineDec <> decls
159+
160+
derivePlutusSpine :: Name -> Q [Dec]
161+
derivePlutusSpine name = do
162+
decls <- deriveSpine name
163+
isDataDecls <- unstableMakeIsData name
164+
165+
(_, _, fieldsNames') <- reifyDatatype name
166+
let fieldsNames = map (map nameBase) fieldsNames'
167+
instanceDecls <-
168+
[d|
169+
instance HasPlutusSpine $(conT name) where
170+
fieldsMap =
171+
Map.fromList $ zip (allSpines @($(conT name))) fieldsNames
172+
|]
173+
174+
return $ decls <> isDataDecls <> instanceDecls

0 commit comments

Comments
 (0)