Skip to content

Commit

Permalink
compile script
Browse files Browse the repository at this point in the history
  • Loading branch information
stanislav-az committed May 29, 2023
1 parent 15267d2 commit 0c34b0c
Show file tree
Hide file tree
Showing 4 changed files with 54 additions and 2 deletions.
27 changes: 26 additions & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,30 @@
{-# LANGUAGE RecordWildCards #-}

module Main where

import Control.Exception (throw)
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Ext.Plutarch.Extra.Run (evalWithArgsT)
import Mixer.Datum.Plutus (MixerConfig (..))
import Mixer.Script (validatorLogic)
import Options (MixerOpts (..), mixerOpts)
import Options.Applicative (execParser)
import PlutusLedgerApi.V1.Bytes (LedgerBytes (..), fromHex)
import PlutusLedgerApi.V1.Value (CurrencySymbol (CurrencySymbol), TokenName, assetClass)
import PlutusLedgerApi.V2 (toData)

main :: IO ()
main = do
putStrLn "Hello, Haskell!"
MixerOpts {..} <- execParser mixerOpts
let ledgerTokenName :: TokenName = fromString tokenName
ledgerCurrSymbol :: CurrencySymbol <- either throw (pure . CurrencySymbol . getLedgerBytes) $ fromHex currencySymbol
let config =
toData
MixerConfig
{ protocolToken = assetClass ledgerCurrSymbol ledgerTokenName
, poolNominal = poolNominal
}
let (script, budget, log) = either (error . T.unpack) id $ evalWithArgsT validatorLogic [config]
putStrLn $ "Script budget: " <> show budget
putStrLn $ "Compilation log: " <> show log
3 changes: 2 additions & 1 deletion app/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,11 @@

module Options where

import Data.ByteString (ByteString)
import Options.Applicative

data MixerOpts = MixerOpts
{ currencySymbol :: String
{ currencySymbol :: ByteString
, tokenName :: String
, poolNominal :: Integer
, scriptPath :: FilePath
Expand Down
19 changes: 19 additions & 0 deletions src/Mixer/Datum/Plutus.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{-# LANGUAGE TemplateHaskell #-}

module Mixer.Datum.Plutus where

import GHC.Generics (Generic)
import PlutusLedgerApi.V1.Value (AssetClass)
import qualified PlutusTx

data MixerConfig = MixerConfig
{ protocolToken :: AssetClass
, poolNominal :: Integer
}
deriving stock (Generic, Show, Eq)

PlutusTx.makeLift ''MixerConfig

PlutusTx.makeIsDataIndexed
''MixerConfig
[('MixerConfig, 0)]
7 changes: 7 additions & 0 deletions tornadano.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -76,16 +76,20 @@ library
Ext.Plutarch.Api.V2.Value
Ext.Plutarch.Extra.Run
Mixer.Datum
Mixer.Datum.Plutus
Mixer.Script

hs-source-dirs: src
build-depends:
, aeson
, bytestring
, data-default
, lens
, plutarch
, plutarch-extra
, plutus-core
, plutus-ledger-api
, plutus-tx
, text

-- Modules included in this library but not exported.
Expand All @@ -103,7 +107,10 @@ executable dump-script
hs-source-dirs: app
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
, bytestring
, optparse-applicative
, plutus-ledger-api
, text
, tornadano

-- LANGUAGE extensions used by modules in this package.
Expand Down

0 comments on commit 0c34b0c

Please sign in to comment.