Skip to content

Commit 0ec4d6b

Browse files
author
Kenneth MacKenzie
authored
Kwxm/nofib size info (SCP-3428) (#4376)
* Add command to nofib-exe to print size and budget info for each benchmark * Update script * Realign header * Update comment * Update comment * Remove accidental imports * updateMaterialized * Some awk reformatting
1 parent a28a62d commit 0ec4d6b

File tree

7 files changed

+185
-43
lines changed

7 files changed

+185
-43
lines changed

nix/pkgs/haskell/materialized-darwin/.plan.nix/plutus-benchmark.nix

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

nix/pkgs/haskell/materialized-linux/.plan.nix/plutus-benchmark.nix

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

nix/pkgs/haskell/materialized-windows/.plan.nix/plutus-benchmark.nix

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

plutus-benchmark/nofib-compare

Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
1+
#!/usr/bin/env bash
2+
# Compare the output from two runs of 'nofib-exe sizes-and-budgets' and print a
3+
# table of the increase/decrease in size/cpu/memory for each. We only print the
4+
# changes because including the input data would make the table too wide.
5+
6+
# Do something like
7+
# `cabal run nofib-exe sizes-and-budgets >results1
8+
# in one branch and then
9+
# `cabal run nofib-exe sizes-and-budgets >results2
10+
# in another, then
11+
# `nofib-compare results1 results2`
12+
# to see the comparison.
13+
#
14+
15+
if [[ $# -lt 2 || $1 == "-h" || $1 == "--help" ]]
16+
then
17+
echo -n "Usage: $0 <file1> <file2>"
18+
exit 1
19+
fi
20+
21+
INPUT1=$1
22+
INPUT2=$2
23+
24+
if [[ ! -r "$INPUT1" ]]
25+
then echo "Error: can't open $INPUT1" && exit 1
26+
fi
27+
28+
if [[ ! -r "$INPUT2" ]]
29+
then echo "Error: can't open $INPUT2" && exit 1
30+
fi
31+
32+
TMP1=$(mktemp /tmp/bc1-XXXXXXX)
33+
TMP2=$(mktemp /tmp/bc2-XXXXXXX)
34+
35+
trap 'rm -f "$TMP1" "$TMP2"' EXIT
36+
37+
# Print out everything after the first line containing "----", ie after the header.
38+
# This should ensure that we're only processing actual data.
39+
awk 'afterHdr >= 1 { print} /-------/ {afterHdr = 1}' "$INPUT1" > "$TMP1"
40+
awk 'afterHdr >= 1 { print} /-------/ {afterHdr = 1}' "$INPUT2" > "$TMP2"
41+
42+
paste "$TMP1" "$TMP2" |
43+
awk '
44+
function diff (n1, n2) {
45+
d = (n2-n1)/n1 * 100
46+
sign = (d<0) ? "" : ((d==0) ? " " : "+") # We get the "-" anyway if d<0
47+
return sprintf ("%s%.1f%%", sign, d)
48+
}
49+
BEGIN {
50+
printf ("Script Size CPU budget Memory budget\n")
51+
printf ("-------------------------------------------------------------------\n")
52+
}
53+
{ printf ("%-15s %15s %15s %15s\n", $1, diff($2,$6), diff($3,$7), diff($4,$8)) }
54+
'
55+

plutus-benchmark/nofib/exe/Main.hs

Lines changed: 119 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,21 @@
1-
{-# LANGUAGE LambdaCase #-}
1+
{-# LANGUAGE LambdaCase #-}
2+
{-# LANGUAGE TypeApplications #-}
23

34
module Main where
45

56
import Prelude ((<>))
6-
import Prelude qualified as Haskell
7+
import Prelude qualified as Hs
78

89
import Control.Monad ()
10+
import Control.Monad.Trans.Except (runExceptT)
911
import Data.ByteString qualified as BS
1012
import Data.Char (isSpace)
1113
import Flat qualified
1214
import Options.Applicative as Opt hiding (action)
1315
import System.Exit (exitFailure)
1416
import System.IO
1517
import Text.PrettyPrint.ANSI.Leijen (Doc, indent, line, string, text, vsep)
18+
import Text.Printf (printf)
1619

1720
import PlutusBenchmark.Common (toAnonDeBruijnTerm)
1821

@@ -22,23 +25,28 @@ import PlutusBenchmark.NoFib.LastPiece qualified as LastPiece
2225
import PlutusBenchmark.NoFib.Prime qualified as Prime
2326
import PlutusBenchmark.NoFib.Queens qualified as Queens
2427

25-
import PlutusCore (Name (..))
28+
import PlutusCore (EvaluationResult, Name (..))
2629
import 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, (<$), (<$>), (<*>), (<>))
3038
import 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
3442
failWithMsg s = hPutStrLn stderr s >> exitFailure
3543

3644

3745
-- | A program together with its arguments
3846
data 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
5867
knownFormulae = "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
6170
clausifyFormulaReader "F1" = Right Clausify.F1
6271
clausifyFormulaReader "F2" = Right Clausify.F2
6372
clausifyFormulaReader "F3" = Right Clausify.F3
@@ -87,15 +96,15 @@ knightsOptions =
8796
-- Lastpiece options --
8897

8998
lastpieceOptions :: 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
96105
knownPrimes = "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
99108
primeIdReader "P05" = Right Prime.P5
100109
primeIdReader "P08" = Right Prime.P8
101110
primeIdReader "P10" = Right Prime.P10
@@ -126,10 +135,10 @@ primetestOptions =
126135

127136
-- Queens options --
128137

129-
knownAlgorithms :: Haskell.String
138+
knownAlgorithms :: Hs.String
130139
knownAlgorithms = "bt, bm, bjbt1, bjbt2, fc"
131140

132-
queensAlgorithmReader :: Haskell.String -> Either Haskell.String Queens.Algorithm
141+
queensAlgorithmReader :: Hs.String -> Either Hs.String Queens.Algorithm
133142
queensAlgorithmReader "bt" = Right Queens.Bt
134143
queensAlgorithmReader "bm" = Right Queens.Bm
135144
queensAlgorithmReader "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

188200
evaluateWithCek :: UPLC.Term Name DefaultUni DefaultFun () -> EvaluationResult (UPLC.Term Name DefaultUni DefaultFun ())
189-
evaluateWithCek = unsafeEvaluateCekNoEmit PLC.defaultCekParameters
201+
evaluateWithCek = UPLC.unsafeEvaluateCekNoEmit PLC.defaultCekParameters
190202

191203
writeFlatNamed :: UPLC.Program Name DefaultUni DefaultFun () -> IO ()
192204
writeFlatNamed prog = BS.putStr $ Flat.flat prog
193205

194206
writeFlatDeBruijn ::UPLC.Program UPLC.DeBruijn DefaultUni DefaultFun () -> IO ()
195207
writeFlatDeBruijn prog = BS.putStr . Flat.flat $ prog
196208

197-
description :: Haskell.String
209+
description :: Hs.String
198210
description = "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.
211223
footerInfo :: 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+
225301
main :: IO ()
226302
main = 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)

plutus-benchmark/nofib/src/PlutusBenchmark/NoFib/Prime.hs

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -304,13 +304,17 @@ mkPrimalityTestTerm n =
304304
runFixedPrimalityTest :: PrimeID -> Result
305305
runFixedPrimalityTest pid = runPrimalityTest (getPrime pid)
306306

307+
308+
mkPrimalityCode :: PrimeID -> Tx.CompiledCode Result
309+
mkPrimalityCode pid =
310+
$$(Tx.compile [|| runFixedPrimalityTest ||])
311+
`Tx.applyCode` Tx.liftCode pid
312+
307313
-- % Run the program on a number known to be prime, for benchmarking
308314
-- (primes take a long time, composite numbers generally don't).
309315
mkPrimalityBenchTerm :: PrimeID -> Term
310316
mkPrimalityBenchTerm pid =
311-
compiledCodeToTerm $
312-
$$(Tx.compile [|| runFixedPrimalityTest ||])
313-
`Tx.applyCode` Tx.liftCode pid
317+
compiledCodeToTerm $ mkPrimalityCode pid
314318

315319
Tx.makeLift ''PrimeID
316320
Tx.makeLift ''Result

plutus-benchmark/plutus-benchmark.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,7 @@ executable nofib-exe
101101
, bytestring -any
102102
, flat -any
103103
, optparse-applicative -any
104+
, transformers -any
104105

105106
benchmark nofib
106107
import: lang

0 commit comments

Comments
 (0)