1- {-# LANGUAGE LambdaCase #-}
1+ {-# LANGUAGE LambdaCase #-}
2+ {-# LANGUAGE TypeApplications #-}
23
34module Main where
45
56import Prelude ((<>) )
6- import Prelude qualified as Haskell
7+ import Prelude qualified as Hs
78
89import Control.Monad ()
10+ import Control.Monad.Trans.Except (runExceptT )
911import Data.ByteString qualified as BS
1012import Data.Char (isSpace )
1113import Flat qualified
1214import Options.Applicative as Opt hiding (action )
1315import System.Exit (exitFailure )
1416import System.IO
1517import Text.PrettyPrint.ANSI.Leijen (Doc , indent , line , string , text , vsep )
18+ import Text.Printf (printf )
1619
1720import PlutusBenchmark.Common (toAnonDeBruijnTerm )
1821
@@ -22,23 +25,28 @@ import PlutusBenchmark.NoFib.LastPiece qualified as LastPiece
2225import PlutusBenchmark.NoFib.Prime qualified as Prime
2326import PlutusBenchmark.NoFib.Queens qualified as Queens
2427
25- import PlutusCore (Name (.. ))
28+ import PlutusCore (EvaluationResult , Name (.. ))
2629import PlutusCore qualified as PLC
27- import PlutusCore.Default
28- import PlutusCore.Pretty qualified as PLC
29- import PlutusTx.Prelude as Plutus hiding (fmap , mappend , (<$) , (<$>) , (<*>) , (<>) )
30+ import PlutusCore.Default (DefaultFun , DefaultUni )
31+ import PlutusCore.Evaluation.Machine.ExBudget (ExBudget (.. ))
32+ import PlutusCore.Evaluation.Machine.ExMemory (ExCPU (.. ), ExMemory (.. ))
33+ import PlutusCore.Pretty (prettyPlcClassicDebug )
34+ import PlutusTx (getPlc )
35+ import PlutusTx.Code (CompiledCode , sizePlc )
36+ import PlutusTx.Evaluation (evaluateCekTrace )
37+ import PlutusTx.Prelude hiding (fmap , mappend , (<$) , (<$>) , (<*>) , (<>) )
3038import UntypedPlutusCore qualified as UPLC
31- import UntypedPlutusCore.Evaluation.Machine.Cek
39+ import UntypedPlutusCore.Evaluation.Machine.Cek qualified as UPLC
3240
33- failWithMsg :: Haskell .String -> IO a
41+ failWithMsg :: Hs .String -> IO a
3442failWithMsg s = hPutStrLn stderr s >> exitFailure
3543
3644
3745-- | A program together with its arguments
3846data ProgAndArgs =
3947 Clausify Clausify. StaticFormula
40- | Queens Haskell .Integer Queens. Algorithm
41- | Knights Haskell .Integer Haskell .Integer
48+ | Queens Hs .Integer Queens. Algorithm
49+ | Knights Hs .Integer Hs .Integer
4250 | LastPiece
4351 | Prime Prime. PrimeID
4452 | Primetest Integer
@@ -50,14 +58,15 @@ data Options
5058 | DumpPLC ProgAndArgs
5159 | DumpFlatNamed ProgAndArgs
5260 | DumpFlatDeBruijn ProgAndArgs
61+ | SizesAndBudgets
5362
5463
5564-- Clausify options --
5665
57- knownFormulae :: Haskell .String
66+ knownFormulae :: Hs .String
5867knownFormulae = " one of F1, F2, F3, F4, F5, F6, F7"
5968
60- clausifyFormulaReader :: Haskell .String -> Either Haskell .String Clausify. StaticFormula
69+ clausifyFormulaReader :: Hs .String -> Either Hs .String Clausify. StaticFormula
6170clausifyFormulaReader " F1" = Right Clausify. F1
6271clausifyFormulaReader " F2" = Right Clausify. F2
6372clausifyFormulaReader " F3" = Right Clausify. F3
@@ -87,15 +96,15 @@ knightsOptions =
8796-- Lastpiece options --
8897
8998lastpieceOptions :: Parser ProgAndArgs
90- lastpieceOptions = Haskell .pure LastPiece
99+ lastpieceOptions = Hs .pure LastPiece
91100
92101
93102-- Primes options --
94103
95- knownPrimes :: Haskell .String
104+ knownPrimes :: Hs .String
96105knownPrimes = " P05, P08, P10, P20, P30, P40, P50, P60, P100, P150, or P200 (a prime with the indicated number of digits)"
97106
98- primeIdReader :: Haskell .String -> Either Haskell .String Prime. PrimeID
107+ primeIdReader :: Hs .String -> Either Hs .String Prime. PrimeID
99108primeIdReader " P05" = Right Prime. P5
100109primeIdReader " P08" = Right Prime. P8
101110primeIdReader " P10" = Right Prime. P10
@@ -126,10 +135,10 @@ primetestOptions =
126135
127136-- Queens options --
128137
129- knownAlgorithms :: Haskell .String
138+ knownAlgorithms :: Hs .String
130139knownAlgorithms = " bt, bm, bjbt1, bjbt2, fc"
131140
132- queensAlgorithmReader :: Haskell .String -> Either Haskell .String Queens. Algorithm
141+ queensAlgorithmReader :: Hs .String -> Either Hs .String Queens. Algorithm
133142queensAlgorithmReader " bt" = Right Queens. Bt
134143queensAlgorithmReader " bm" = Right Queens. Bm
135144queensAlgorithmReader " bjbt1" = Right Queens. Bjbt1
@@ -162,42 +171,45 @@ options = hsubparser
162171 ( command " run"
163172 (info (RunPLC <$> progAndArgs)
164173 (progDesc " same as runPLC" ))
165- <> command " runPLC "
174+ <> command " run-plc "
166175 (info (RunPLC <$> progAndArgs)
167176 (progDesc " compile the program to Plutus Core and evaluate it using the CEK machine" ))
168- <> command " runHaskell "
177+ <> command " run-hs "
169178 (info (RunHaskell <$> progAndArgs)
170- (progDesc " run the program directly as Haskell " ))
171- <> command " dumpPLC "
179+ (progDesc " run the program directly as Hs " ))
180+ <> command " dump-plc "
172181 (info (DumpPLC <$> progAndArgs)
173182 (progDesc " print the program (applied to arguments) as Plutus Core source on standard output" ))
174- <> command " dumpFlatNamed "
183+ <> command " dump-flat-named "
175184 (info (DumpFlatNamed <$> progAndArgs)
176185 (progDesc " dump the AST as Flat, preserving names" ))
177- <> command " dumpFlat "
186+ <> command " dump-flat "
178187 (info (DumpFlatDeBruijn <$> progAndArgs)
179- (progDesc " same as dumpFlatDeBruijn , but easier to type" ))
180- <> command " dumpFlatDeBruijn "
188+ (progDesc " same as dump-flat-deBruijn , but easier to type" ))
189+ <> command " dump-flat-deBruijn "
181190 (info (DumpFlatDeBruijn <$> progAndArgs)
182191 (progDesc " dump the AST as Flat, with names replaced by de Bruijn indices" ))
192+ <> command " sizes-and-budgets"
193+ (info (Hs. pure SizesAndBudgets )
194+ (progDesc " Print the size and cpu/memory budgets of each program" ))
183195 )
184196
185197
186198---------------- Evaluation ----------------
187199
188200evaluateWithCek :: UPLC. Term Name DefaultUni DefaultFun () -> EvaluationResult (UPLC. Term Name DefaultUni DefaultFun () )
189- evaluateWithCek = unsafeEvaluateCekNoEmit PLC. defaultCekParameters
201+ evaluateWithCek = UPLC. unsafeEvaluateCekNoEmit PLC. defaultCekParameters
190202
191203writeFlatNamed :: UPLC. Program Name DefaultUni DefaultFun () -> IO ()
192204writeFlatNamed prog = BS. putStr $ Flat. flat prog
193205
194206writeFlatDeBruijn :: UPLC. Program UPLC. DeBruijn DefaultUni DefaultFun () -> IO ()
195207writeFlatDeBruijn prog = BS. putStr . Flat. flat $ prog
196208
197- description :: Haskell .String
209+ description :: Hs .String
198210description = " This program provides operations on a number of Plutus programs "
199- ++ " ported from the nofib Haskell test suite. "
200- ++ " The programs are written in Haskell and can be run directly "
211+ ++ " ported from the nofib Hs test suite. "
212+ ++ " The programs are written in Hs and can be run directly "
201213 ++ " or compiled into Plutus Core and run on the CEK machine. "
202214 ++ " Compiled programs can also be output in a number of formats."
203215
@@ -209,7 +221,7 @@ knownProgs = map text ["clausify", "knights", "lastpiece", "prime", "primetest",
209221-- manual formatting in here because the text doesn't wrap as expected, presumably
210222-- due to what optparse-applicative is doing internally.
211223footerInfo :: Doc
212- footerInfo = text " Every command takes the name of a program and a (possbily empty) list of arguments."
224+ footerInfo = text " Most commands take the name of a program and a (possbily empty) list of arguments."
213225 <> line <> line
214226 <> text " The available programs are: "
215227 <> line
@@ -222,23 +234,93 @@ footerInfo = text "Every command takes the name of a program and a (possbily emp
222234 ++ " arguments and prints the result to the terminal in the specified format.\n "
223235 ++ " You'll probably want to redirect the output to a file." )
224236
237+
238+ -- Copied pretty much directly from plutus-tx/testlib/PlutusTx/Test.hs
239+ measureBudget :: CompiledCode a -> (Integer , Integer )
240+ measureBudget compiledCode =
241+ let programE = PLC. runQuote
242+ $ runExceptT @ PLC. FreeVariableError
243+ $ UPLC. unDeBruijnProgram
244+ $ getPlc compiledCode
245+ in case programE of
246+ Left _ -> (- 1 ,- 1 ) -- Something has gone wrong but I don't care.
247+ Right program ->
248+ let (_, UPLC. TallyingSt _ budget, _) = evaluateCekTrace program
249+ ExCPU cpu = exBudgetCPU budget
250+ ExMemory mem = exBudgetMemory budget
251+ in (Hs. fromIntegral cpu, Hs. fromIntegral mem)
252+
253+ getInfo :: (Hs. String , CompiledCode a ) -> (Hs. String , Integer , Integer , Integer )
254+ getInfo (name, code) =
255+ let size = sizePlc code
256+ (cpu, mem) = measureBudget code
257+ in (name, size, cpu, mem)
258+
259+ printSizesAndBudgets :: IO ()
260+ printSizesAndBudgets = do
261+ -- The applied programs to measure, which are the same as the ones in the benchmarks.
262+ -- We can't put all of these in one list because the 'a's in 'CompiledCode a' are different
263+ let clausify = [ (" clausify/F1" , Clausify. mkClausifyCode Clausify. F1 )
264+ , (" clausify/F2" , Clausify. mkClausifyCode Clausify. F2 )
265+ , (" clausify/F3" , Clausify. mkClausifyCode Clausify. F3 )
266+ , (" clausify/F4" , Clausify. mkClausifyCode Clausify. F4 )
267+ , (" clausify/F5" , Clausify. mkClausifyCode Clausify. F5 )
268+ ]
269+ knights = [ ( " knights/4x4" , Knights. mkKnightsCode 100 4 )
270+ , ( " knights/6x6" , Knights. mkKnightsCode 100 6 )
271+ , ( " knights/8x8" , Knights. mkKnightsCode 100 8 )
272+ ]
273+ primetest = [ (" primes/05digits" , Prime. mkPrimalityCode Prime. P5 )
274+ , (" primes/08digits" , Prime. mkPrimalityCode Prime. P8 )
275+ , (" primes/10digits" , Prime. mkPrimalityCode Prime. P10 )
276+ , (" primes/20digits" , Prime. mkPrimalityCode Prime. P20 )
277+ , (" primes/30digits" , Prime. mkPrimalityCode Prime. P30 )
278+ , (" primes/40digits" , Prime. mkPrimalityCode Prime. P40 )
279+ , (" primes/50digits" , Prime. mkPrimalityCode Prime. P50 )
280+ ]
281+ queens4x4 = [ (" queens4x4/bt" , Queens. mkQueensCode 4 Queens. Bt )
282+ , (" queens4x4/bm" , Queens. mkQueensCode 4 Queens. Bm )
283+ , (" queens4x4/bjbt1" , Queens. mkQueensCode 4 Queens. Bjbt1 )
284+ , (" queens4x4/bjbt2" , Queens. mkQueensCode 4 Queens. Bjbt2 )
285+ , (" queens4x4/fc" , Queens. mkQueensCode 4 Queens. Fc )
286+ ]
287+ queens5x5 = [ (" queens5x5/bt" ,Queens. mkQueensCode 5 Queens. Bt )
288+ , (" queens5x5/bm" ,Queens. mkQueensCode 5 Queens. Bm )
289+ , (" queens5x5/bjbt1" ,Queens. mkQueensCode 5 Queens. Bjbt1 )
290+ , (" queens5x5/bjbt2" ,Queens. mkQueensCode 5 Queens. Bjbt2 )
291+ , (" queens5x5/fc" ,Queens. mkQueensCode 5 Queens. Fc )
292+ ]
293+ statistics = map getInfo clausify ++ map getInfo knights ++ map getInfo primetest ++ map getInfo queens4x4 ++ map getInfo queens5x5
294+ formatInfo (name, size, cpu, mem) = printf " %-20s %10d %15d %15d\n " name size cpu mem
295+
296+ putStrLn " Script Size CPU budget Memory budget"
297+ putStrLn " -----------------------------------------------------------------"
298+ mapM_ (putStr . formatInfo) statistics
299+
300+
225301main :: IO ()
226302main = do
227303 execParser (info (helper <*> options) (fullDesc <> progDesc description <> footerDoc (Just footerInfo))) >>= \ case
228- RunPLC pa -> print . PLC. prettyPlcClassicDebug . evaluateWithCek . getTerm $ pa
304+ RunPLC pa ->
305+ print . prettyPlcClassicDebug . evaluateWithCek . getTerm $ pa
229306 RunHaskell pa ->
230307 case pa of
231308 Clausify formula -> print $ Clausify. runClausify formula
232309 Knights depth boardSize -> print $ Knights. runKnights depth boardSize
233310 LastPiece -> print $ LastPiece. runLastPiece
234311 Queens boardSize alg -> print $ Queens. runQueens boardSize alg
235312 Prime input -> print $ Prime. runFixedPrimalityTest input
236- Primetest n -> if n< 0 then Haskell .error " Positive number expected"
313+ Primetest n -> if n< 0 then Hs .error " Positive number expected"
237314 else print $ Prime. runPrimalityTest n
238- DumpPLC pa -> Haskell. mapM_ putStrLn $ unindent . PLC. prettyPlcClassicDebug . mkProg . getTerm $ pa
239- where unindent d = map (dropWhile isSpace) $ (Haskell. lines . Haskell. show $ d)
240- DumpFlatNamed pa -> writeFlatNamed . mkProg . getTerm $ pa
241- DumpFlatDeBruijn pa-> writeFlatDeBruijn . mkProg . toAnonDeBruijnTerm . getTerm $ pa
315+ DumpPLC pa ->
316+ Hs. mapM_ putStrLn $ unindent . prettyPlcClassicDebug . mkProg . getTerm $ pa
317+ where unindent d = map (dropWhile isSpace) $ (Hs. lines . Hs. show $ d)
318+ DumpFlatNamed pa ->
319+ writeFlatNamed . mkProg . getTerm $ pa
320+ DumpFlatDeBruijn pa ->
321+ writeFlatDeBruijn . mkProg . toAnonDeBruijnTerm . getTerm $ pa
322+ SizesAndBudgets
323+ -> printSizesAndBudgets
242324 -- Write the output to stdout and let the user deal with redirecting it.
243325 where getTerm :: ProgAndArgs -> UPLC. Term UPLC. Name DefaultUni DefaultFun ()
244326 getTerm =
@@ -248,11 +330,8 @@ main = do
248330 Knights depth boardSize -> Knights. mkKnightsTerm depth boardSize
249331 LastPiece -> LastPiece. mkLastPieceTerm
250332 Prime input -> Prime. mkPrimalityBenchTerm input
251- Primetest n -> if n< 0 then Haskell .error " Positive number expected"
333+ Primetest n -> if n< 0 then Hs .error " Positive number expected"
252334 else Prime. mkPrimalityTestTerm n
253335
254- -- getUnDBrTerm :: ProgAndArgs -> UPLC.Term Name DefaultUni DefaultFun ()
255- -- getUnDBrTerm = unDeBruijn . getDBrTerm
256-
257336 mkProg :: UPLC. Term name uni fun () -> UPLC. Program name uni fun ()
258337 mkProg = UPLC. Program () (UPLC. Version () 1 0 0 )
0 commit comments