├── .arcconfig ├── .gitignore ├── .gitlab-ci.yml ├── CODEOWNERS ├── Makefile ├── README.md ├── Simon-nofib-notes ├── common └── NofibUtils.hs ├── docs └── paper │ ├── Jmakefile │ ├── MAIL │ ├── compile.sc │ ├── compile.txt │ ├── hbc-vs-ghc.cln │ ├── hbc-vs-ghc.sc │ ├── nofib_only.bib │ ├── paper.bbl │ ├── paper.verb │ ├── reviews │ ├── run.sc │ ├── run.txt │ ├── slides-root.tex │ ├── slides.tex │ ├── ticky.sc │ └── ticky.sc.lat ├── easy.sh ├── gc ├── Makefile ├── cacheprof │ ├── Arch_x86.hs │ ├── Generics.hs │ ├── Main.hs │ ├── Makefile │ ├── cacheprof.stdin │ ├── cacheprof.stdout │ └── cacheprof_hooks2_x86.s ├── circsim │ ├── Main.lhs │ ├── Makefile │ ├── circsim.faststdout │ ├── circsim.slowstdout │ └── circsim.stdout ├── constraints │ ├── Main.hs │ ├── Makefile │ ├── constraints.faststdout │ ├── constraints.slowstdout │ └── constraints.stdout ├── fibheaps │ ├── Main.lhs │ ├── Makefile │ ├── fibheaps.stdout │ ├── orig │ └── stuff ├── fulsom │ ├── Bah.hs │ ├── Csg.hs │ ├── Interval.hs │ ├── Kolor.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── Matrix.hs │ ├── Oct.hs │ ├── Patchlevel.hs │ ├── Quad.hs │ ├── README.nofib │ ├── README.original │ ├── Raster.hs │ ├── Shapes.hs │ ├── Types.hs │ ├── Vector.hs │ ├── fulsom.stdout │ ├── out │ ├── pics │ │ └── sphere.gif │ ├── raster │ │ └── raster.c │ ├── stuff │ ├── stuff-SAVE │ └── stuff2 ├── gc_bench │ ├── Makefile │ └── gc_bench.hs ├── happy │ ├── AbsSyn.lhs │ ├── AttrGrammar.lhs │ ├── AttrGrammarParser.hs │ ├── First.lhs │ ├── GenUtils.lhs │ ├── Grammar.lhs │ ├── Info.lhs │ ├── LALR.lhs │ ├── Lexer.lhs │ ├── Makefile │ ├── ParseMonad.lhs │ ├── Parser.hs │ ├── Paths_happy.hs │ ├── ProduceCode.lhs │ ├── ProduceGLRCode.lhs │ ├── Set.hs │ ├── Target.lhs │ ├── TestInput.hs │ ├── TestInput.y │ ├── happy.expected │ ├── happy.lhs │ └── happy.stderr ├── hash │ ├── HashTable.hs │ ├── Makefile │ ├── hash.hs │ └── hash.stdout ├── lcss │ ├── Main.hs │ ├── Makefile │ ├── lcss.faststdout │ ├── lcss.slowstdout │ └── lcss.stdout ├── linear │ ├── AbsCg.lhs │ ├── AbsDensematrix.lhs │ ├── Absmatlib.lhs │ ├── Cg.lhs │ ├── Densematrix.lhs │ ├── Input.lhs │ ├── Makefile │ ├── Matlib.lhs │ ├── Matrix.lhs │ ├── Misc.lhs │ ├── Utils.lhs │ ├── linear.expected │ ├── linear.lhs │ ├── linear.ps │ └── linear.stdout ├── mutstore1 │ ├── Main.hs │ ├── Makefile │ └── Store1.hs ├── mutstore2 │ ├── Main.hs │ ├── Makefile │ └── Store2.hs ├── power │ ├── Main.hs │ ├── Makefile │ ├── power.faststdout │ ├── power.slowstdout │ └── power.stdout ├── spellcheck │ ├── Makefile │ ├── input │ ├── spellcheck.hs │ ├── spellcheck.stdout │ └── words └── treejoin │ ├── 27000.1 │ ├── 27000.2 │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ └── treejoin.stdout ├── imaginary ├── Makefile ├── bernouilli │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── bernouilli.faststdout │ ├── bernouilli.slowstdout │ └── bernouilli.stdout ├── digits-of-e1 │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ ├── digits-of-e1.faststdout │ ├── digits-of-e1.slowstdout │ └── digits-of-e1.stdout ├── digits-of-e2 │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ ├── digits-of-e2.faststdout │ ├── digits-of-e2.slowstdout │ └── digits-of-e2.stdout ├── exp3_8 │ ├── Main.hs │ ├── Makefile │ ├── exp3_8.faststdout │ └── exp3_8.stdout ├── gen_regexps │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── gen_regexps.faststdout │ ├── gen_regexps.slowstdout │ └── gen_regexps.stdout ├── integrate │ ├── Main.hs │ ├── Makefile │ ├── integrate.faststdout │ ├── integrate.slowstdout │ └── integrate.stdout ├── kahan │ ├── Main.hs │ └── Makefile ├── paraffins │ ├── Main.hs │ ├── Makefile │ ├── paraffins.c │ ├── paraffins.faststdout │ ├── paraffins.slowstdout │ └── paraffins.stdout ├── primes │ ├── Main.hs │ ├── Makefile │ ├── csieve.c │ ├── primes.faststdout │ ├── primes.slowstdout │ └── primes.stdout ├── queens │ ├── Main.hs │ ├── Makefile │ ├── queens.faststdout │ ├── queens.slowstdout │ └── queens.stdout ├── rfib │ ├── Main.hs │ ├── Makefile │ ├── rfib.faststdout │ ├── rfib.slowstdout │ └── rfib.stdout ├── tak │ ├── Main.hs │ ├── Makefile │ ├── tak.faststdout │ ├── tak.slowstdout │ └── tak.stdout ├── wheel-sieve1 │ ├── Main.hs │ ├── Makefile │ ├── wheel-sieve1.faststdout │ ├── wheel-sieve1.slowstdout │ └── wheel-sieve1.stdout ├── wheel-sieve2 │ ├── Main.hs │ ├── Makefile │ ├── wheel-sieve2.faststdout │ ├── wheel-sieve2.slowstdout │ └── wheel-sieve2.stdout └── x2n1 │ ├── Main.hs │ ├── Makefile │ ├── x2n1.faststdout │ ├── x2n1.slowstdout │ └── x2n1.stdout ├── mk ├── boilerplate.mk ├── ghc-opts.mk ├── ghc-paths.mk ├── ghc-recurse.mk ├── ghc-suffix.mk ├── ghc-target.mk ├── opts.mk ├── paths.mk ├── suffix.mk └── target.mk ├── nofib-analyse ├── CmdLine.hs ├── GenUtils.lhs ├── Main.hs ├── Makefile ├── Slurp.hs ├── cabal.project └── nofib-analyse.cabal ├── parallel ├── Makefile ├── OLD │ ├── NESL │ │ ├── GranRandom.hs │ │ ├── Makefile │ │ ├── Strategies.lhs │ │ ├── fft.lhs │ │ ├── integrate.lhs │ │ ├── matrix-inverse.lhs │ │ ├── quick_hull.lhs │ │ └── sieve.lhs │ ├── bom │ │ ├── GranRandom.hs │ │ ├── Makefile │ │ ├── Strategies.lhs │ │ ├── bom.hs │ │ ├── dateNaiveAhead.hs │ │ └── dateNaiveChunk.hs │ ├── par001 │ │ ├── Main.hs │ │ ├── Makefile │ │ └── par001.stdout │ ├── parfact │ │ ├── Makefile │ │ ├── parfact.hs │ │ └── parfact.stdout │ ├── soda │ │ ├── Main.hs │ │ ├── Makefile │ │ └── soda.stdout │ └── soda7 │ │ ├── Main.hs │ │ ├── Makefile │ │ └── soda7.stdout ├── blackscholes │ ├── Future.hs │ ├── Makefile │ ├── blackscholes.hs │ ├── blackscholes.stdout │ └── blackscholes_data.hs-inc ├── cfd │ ├── C_matrix.hs │ ├── Chl_method_q.hs │ ├── Data8.hs │ ├── Defs.hs │ ├── Gen_net.hs │ ├── Jcb_method.hs │ ├── L_matrix.hs │ ├── Main.hs │ ├── Makefile │ ├── Norm.hs │ ├── Quad_def.hs │ ├── S_Array.hs │ ├── S_matrix.hs │ ├── TG_iter.hs │ └── cfd.stdout ├── coins │ ├── Makefile │ ├── coins.hs │ └── coins.stdout ├── dcbm │ ├── DCBM.hs │ ├── DbParallel.hs │ ├── Delay.hs │ ├── Fwif.hs │ ├── Main.hs │ ├── Makefile │ ├── Primitives.lhc │ ├── Primitives.lhi │ └── Types.hs ├── gray │ ├── CSG.hs │ ├── Construct.hs │ ├── Data.hs │ ├── Eval.hs │ ├── Geometry.hs │ ├── Illumination.hs │ ├── Intersections.hs │ ├── Interval.hs │ ├── Main.hs │ ├── Makefile │ ├── Misc.hs │ ├── Parse.hs │ ├── Primitives.hs │ ├── RayTrace.hs │ ├── Surface.hs │ ├── foo │ ├── foo.gif │ ├── galois.gml │ ├── gray.ppm │ └── gray.stdout ├── linsolv │ ├── CRA.hs │ ├── Main.hs │ ├── Makefile │ ├── Matrix.hs │ ├── ModArithm.hs │ └── linsolv.stdout ├── mandel │ ├── Main.lhs │ ├── Makefile │ ├── Mandel.lhs │ ├── PortablePixmap.lhs │ └── mandel.stdout ├── matmult │ ├── ListAux.hs │ ├── Makefile │ ├── MatMult.hs │ └── matmult.stdout ├── minimax │ ├── Board.hs │ ├── Game.hs │ ├── Main.hs │ ├── Makefile │ ├── Prog.hs │ ├── Tree.hs │ ├── Wins.hs │ └── minimax.stdout ├── nbody │ ├── Future.hs │ ├── Makefile │ ├── nbody.hs │ └── nbody.stdout ├── parfib │ ├── Main.hs │ ├── Makefile │ └── parfib.stdout ├── partak │ ├── Main.hs │ ├── Makefile │ └── partak.stdout ├── partree │ ├── Makefile │ ├── Tree.hs │ ├── partree.hs │ └── partree.stdout ├── prsa │ ├── Main.hs │ ├── Makefile │ ├── Rsa.hs │ └── prsa.stdout ├── queens │ ├── Main.hs │ ├── Makefile │ └── queens.stdout ├── quicksort │ ├── QuickSort.hs │ └── QuickSortD.hs ├── ray │ ├── Main.lhs │ ├── Makefile │ └── ray.stdout ├── sumeuler │ ├── ListAux.hs │ ├── Makefile │ ├── SumEuler.hs │ ├── SumEulerPrimes.hs │ └── sumeuler.stdout ├── threadfib │ └── threadfib.hs ├── transclos │ ├── Main.hs │ ├── Makefile │ ├── TransClos.hs │ └── transclos.stdout └── warshall │ ├── Makefile │ └── warshall.hs ├── real ├── Makefile ├── anna │ ├── AbsConc3.hs │ ├── AbstractEval2.hs │ ├── AbstractMisc.hs │ ├── AbstractVals2.hs │ ├── Apply.hs │ ├── BarakiConc3.hs │ ├── BarakiMeet.hs │ ├── BaseDefs.hs │ ├── Constructors.hs │ ├── Dependancy.hs │ ├── DomainExpr.hs │ ├── EtaAbstract.hs │ ├── FrontierDATAFN2.hs │ ├── FrontierGENERIC2.hs │ ├── FrontierMisc2.hs │ ├── Inverse.hs │ ├── LambdaLift5.hs │ ├── Main.hs │ ├── MakeDomains.hs │ ├── Makefile │ ├── Monster.hs │ ├── Monstermakefile │ ├── MyUtils.hs │ ├── NofibUtils.hs │ ├── Parser2.hs │ ├── PrettyPrint.hs │ ├── PrintResults.hs │ ├── README │ ├── ReadTable.hs │ ├── Simplify.hs │ ├── SmallerLattice.hs │ ├── StrictAn6.hs │ ├── SuccsAndPreds2.hs │ ├── TExpr2DExpr.hs │ ├── Testmakefile │ ├── TypeCheck5.hs │ ├── Utils.hs │ ├── anna.faststdin │ ├── anna.faststdout │ ├── anna.full │ ├── anna.postscript │ ├── anna.prescript │ ├── anna.slowstdin │ ├── anna.slowstdout │ ├── anna.stdin │ ├── anna.stdout │ ├── big.sum.out │ ├── cor_files │ │ ├── ap_CaseAlts.cor │ │ ├── ap_CaseArgs.cor │ │ ├── ap_CaseOfCase.cor │ │ ├── ap_CaseOfCase2.cor │ │ ├── ap_CaseOfCase3.cor │ │ ├── ap_FuncCall.cor │ │ ├── ap_ListOfList.cor │ │ ├── ap_SemiLazyAdd.cor │ │ ├── ap_SemiLazyCase.cor │ │ ├── ap_SimpleLazy.cor │ │ ├── ap_SimpleStrict.cor │ │ ├── ap_Unzip.cor │ │ ├── ap_Zip.cor │ │ ├── append.cor │ │ ├── avlTree.cor │ │ ├── big.cor │ │ ├── bmark.cor │ │ ├── bomb.cor │ │ ├── bomb2.cor │ │ ├── bug.cor │ │ ├── bug_Anna1.cor │ │ ├── bug_Anna2.cor │ │ ├── bug_Anna3.cor │ │ ├── bug_Anna4.cor │ │ ├── bug_Anna5.cor │ │ ├── bug_Anna6.cor │ │ ├── bug_types1.cor │ │ ├── bug_types2.cor │ │ ├── bury.cor │ │ ├── cfoldr.cor │ │ ├── concat.cor │ │ ├── concat22.cor │ │ ├── concat24.cor │ │ ├── concat44.cor │ │ ├── coreExpr.cor │ │ ├── coreExpr0.cor │ │ ├── divide.cor │ │ ├── dividetree.cor │ │ ├── dot_3.cor │ │ ├── dot_4.cor │ │ ├── eta.cor │ │ ├── filter.cor │ │ ├── foldrFoldl.cor │ │ ├── fourier.cor │ │ ├── funcDomain.cor │ │ ├── higherOrder.cor │ │ ├── john.cor │ │ ├── llfiasco.cor │ │ ├── manyIterate.cor │ │ ├── mutualRec.cor │ │ ├── ol_num.cor │ │ ├── pairid.cor │ │ ├── parallelOr.cor │ │ ├── poly_loseGain.cor │ │ ├── poly_simple.cor │ │ ├── preludeList.cor │ │ ├── realNasties.cor │ │ ├── reverse.cor │ │ ├── sebastian1.cor │ │ ├── sebastian2.cor │ │ ├── sets.cor │ │ ├── standardTest.cor │ │ └── treeDepth.cor │ ├── nofib_driver │ └── runtime_files │ │ └── anna_table ├── bspt │ ├── BSPT.lhs │ ├── Euclid.lhs │ ├── EuclidGMS.lhs │ ├── GeomNum.lhs │ ├── Init.lhs │ ├── Input.lhs │ ├── Interface.lhs │ ├── Interpret.lhs │ ├── Libfuns.lhs │ ├── MGRlib.lhs │ ├── Main.hs │ ├── Makefile │ ├── Merge.lhs │ ├── NofibUtils.hs │ ├── Params.lhs │ ├── Prog.hs │ ├── Rationals.lhs │ ├── Render.lhs │ ├── Stdlib.lhs │ ├── bspt.faststdout │ ├── bspt.slowstdout │ ├── bspt.stdin │ └── bspt.stdout ├── cacheprof │ ├── Arch_x86.hs │ ├── Generics.hs │ ├── Main.hs │ ├── Makefile │ ├── cacheprof.faststdin │ ├── cacheprof.full │ ├── cacheprof.slowstdin │ ├── cacheprof.stdin │ └── runtime_files │ │ └── cacheprof_hooks2_x86.s ├── compress │ ├── BinConv.hs │ ├── BinTest.hs │ ├── Decode.hs │ ├── Defaults.hs │ ├── Encode.hs │ ├── Lzw.hs │ ├── Lzw.icl │ ├── Lzw2.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── PTTrees.hs │ ├── README.nofib │ ├── Uncompress.hs │ ├── compress.faststdin │ ├── compress.faststdout │ ├── compress.slowstdin │ ├── compress.slowstdout │ ├── compress.stdin │ ├── compress.stdout │ └── lzw.c ├── compress2 │ ├── Encode.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── WriteRoutines.hs │ ├── compress2.faststdin │ ├── compress2.faststdout │ ├── compress2.slowstdin │ ├── compress2.slowstdout │ ├── compress2.stdin │ ├── compress2.stdout │ └── inC │ │ ├── bin_conv.c │ │ ├── io_copy.c │ │ └── prefix_trees.c ├── eff │ ├── CS │ │ ├── CS.stdout │ │ ├── EffBench.hs │ │ ├── Main.hs │ │ └── Makefile │ ├── CSD │ │ ├── CSD.stdout │ │ ├── EffBench.hs │ │ ├── Main.hs │ │ └── Makefile │ ├── FS │ │ ├── EffBench.hs │ │ ├── FS.stdout │ │ ├── Main.hs │ │ └── Makefile │ ├── Makefile │ ├── S │ │ ├── Main.hs │ │ ├── Makefile │ │ └── S.stdout │ ├── VS │ │ ├── EffBench.hs │ │ ├── Main.hs │ │ ├── Makefile │ │ └── VS.stdout │ ├── VSD │ │ ├── EffBench.hs │ │ ├── Main.hs │ │ ├── Makefile │ │ └── VSD.stdout │ └── VSM │ │ ├── EffBench.hs │ │ ├── Main.hs │ │ ├── Makefile │ │ └── VSM.stdout ├── fem │ ├── Assemble_loadvec.hs │ ├── Assemble_stiffness.hs │ ├── Basics.hs │ ├── DB_interface.hs │ ├── Database.hs │ ├── Degrees.hs │ ├── Displacement.hs │ ├── Elemforce.hs │ ├── Elemstif.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── Matrix.hs │ ├── NofibUtils.hs │ ├── Pre_assemble.hs │ ├── PrintSource.hs │ ├── Printuvwforce.hs │ ├── README │ ├── VBlldecomp.hs │ ├── VBmatrix.hs │ ├── Vector.hs │ ├── data.0 │ ├── data.1 │ ├── data.2 │ ├── data.3 │ ├── fem.stdin │ └── inC │ │ ├── FEM_MODEL_DATA │ │ ├── G.1 │ │ ├── G.2 │ │ ├── G.3 │ │ ├── G.4 │ │ ├── README │ │ ├── TIMING │ │ ├── assemble_loadvec.c │ │ ├── assemble_stiffness.c │ │ ├── bar_2d.c │ │ ├── data │ │ ├── data.1 │ │ ├── data.2 │ │ ├── data.3 │ │ ├── data.4 │ │ ├── database │ │ ├── displacement.c │ │ ├── fem.c │ │ ├── internalforce.c │ │ ├── pre_assemble.c │ │ ├── read_data.c │ │ ├── run │ │ └── vblldecomp.c ├── fluid │ ├── Asb_routs.hs │ ├── C_matrix.hs │ ├── Chl_decomp.hs │ ├── Chl_method.hs │ ├── Chl_routs.hs │ ├── Defs.hs │ ├── Elefac.hs │ ├── Input_proc.hs │ ├── Jcb_method.hs │ ├── L_matrix.hs │ ├── Main.hs │ ├── Makefile │ ├── Min_degree.hs │ ├── NofibUtils.hs │ ├── Norm.hs │ ├── README │ ├── Rhs_Asb_routs.hs │ ├── S_Array.hs │ ├── S_matrix.hs │ ├── TG_iter.hs │ ├── Tol_cal.hs │ ├── chan.hed │ ├── fluid.stdin │ ├── res8 │ └── runtime_files │ │ └── chan8.dat ├── fulsom │ ├── Bah.hs │ ├── Csg.hs │ ├── Interval.hs │ ├── Kolor.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── Matrix.hs │ ├── NofibUtils.hs │ ├── Oct.hs │ ├── Patchlevel.hs │ ├── Quad.hs │ ├── README.nofib │ ├── README.original │ ├── Raster.hs │ ├── Shapes.hs │ ├── Types.hs │ ├── Vector.hs │ ├── fulsom.faststdout │ ├── fulsom.slowstdout │ ├── fulsom.stdout │ ├── pics │ │ └── sphere.gif │ └── raster │ │ └── raster.c ├── gamteb │ ├── Compton.hs │ ├── Consts.hs │ ├── Distance.hs │ ├── GamtebMain.hs │ ├── GamtebType.hs │ ├── InitTable.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Output.hs │ ├── Pair.hs │ ├── PhotoElec.hs │ ├── RoulSplit.hs │ ├── TransPort.hs │ ├── Utils.hs │ ├── gamteb.faststdout │ ├── gamteb.slowstdout │ ├── gamteb.stdout │ ├── inFortran │ │ ├── fact.f │ │ ├── gamo.f │ │ └── gamteb.f │ ├── inLML │ │ ├── compton.m │ │ ├── compton.m.97 │ │ ├── consts.m │ │ ├── consts.m.97 │ │ ├── distance.m │ │ ├── distance.m.97 │ │ ├── floatop.m.97 │ │ ├── gamteb.doc │ │ ├── gamteb.m │ │ ├── gamteb.m.97 │ │ ├── gamtebType.m │ │ ├── gamtebType.m.97 │ │ ├── gamteb_for.f │ │ ├── gamteb_id.id │ │ ├── libroutines │ │ ├── output.m │ │ ├── output.m.97 │ │ ├── pair.m │ │ ├── pair.m.97 │ │ ├── photoElec.m │ │ ├── photoElec.m.97 │ │ ├── roulSplit.m │ │ ├── roulSplit.m.97 │ │ ├── transPort.m │ │ ├── transPort.m.97 │ │ ├── utils.m │ │ └── utils.m.97 │ └── results │ │ ├── gm2048 │ │ ├── gm4096 │ │ ├── gm6000 │ │ ├── gm7000 │ │ ├── pm2048 │ │ ├── pm4096 │ │ ├── pm6000 │ │ └── pm7000 ├── gg │ ├── Activity.hs │ ├── GRIP.hs │ ├── Graph.hs │ ├── Main.hs │ ├── Makefile │ ├── Msg.Header │ ├── NofibUtils.hs │ ├── PSlib.hs │ ├── Parse.hs │ ├── Pool.hs │ ├── Report.tex │ ├── Spark.hs │ ├── StdLib.hs │ ├── example │ │ ├── README.nofib │ │ ├── Report.tex │ │ └── report │ ├── gg.1 │ ├── gg.faststdin │ ├── gg.faststdout │ ├── gg.slowstdin │ ├── gg.slowstdout │ ├── gg.stderr │ ├── gg.stdin │ ├── gg.stdin-2.Z │ ├── gg.stdout │ └── report ├── grep │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Parsers.hs │ ├── StringMatch.hs │ ├── grep.faststdin │ ├── grep.faststdout │ ├── grep.slowstdin │ ├── grep.slowstdout │ ├── grep.stdin │ └── grep.stdout ├── hidden │ ├── Comparing.hs │ ├── Cross.hs │ ├── EdgePlate.hs │ ├── Geometric.hs │ ├── Hide.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── Matrices.hs │ ├── Memo.hs │ ├── MyIO.hs │ ├── NofibUtils.hs │ ├── Numbers.hs │ ├── Postscript.hs │ ├── Preds.hs │ ├── Rotate.lhs │ ├── Solve.hs │ ├── Vectors.hs │ ├── etc │ │ └── nbpip.c │ ├── hidden.stderr │ ├── hidden.stdin │ └── runtime_files │ │ ├── bookcase.plate │ │ ├── cube.plate │ │ ├── four.plate │ │ ├── horse.plate │ │ ├── houses.plate │ │ ├── pyramid.plate │ │ ├── rad.plate │ │ └── table.plate ├── hpg │ ├── Config.lhs │ ├── Env.lhs │ ├── GenExp.lhs │ ├── GenType.lhs │ ├── GenVal.lhs │ ├── MAIL │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ ├── README.nofib │ ├── Types.lhs │ ├── Utils.lhs │ ├── hpg.1 │ ├── hpg.faststdout │ ├── hpg.slowstdout │ ├── hpg.stdout │ ├── hpg.tex │ ├── intro.tex │ └── outro.tex ├── infer │ ├── Environment.hs │ ├── FiniteMap.hs │ ├── Infer.hs │ ├── InferMonad.hs │ ├── Main.hs │ ├── Makefile │ ├── MaybeM.hs │ ├── MyList.hs │ ├── NofibUtils.hs │ ├── Parse.hs │ ├── Shows.hs │ ├── State.hs │ ├── StateX.hs │ ├── Substitution.hs │ ├── Term.hs │ ├── TestTerm.hs │ ├── TestType.hs │ ├── Type.hs │ ├── infer.faststdin │ ├── infer.faststdout │ ├── infer.slowstdin │ ├── infer.slowstdout │ ├── infer.stdin │ └── infer.stdout ├── lift │ ├── LambdaLift.lhs │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Print.lhs │ ├── Test.hs │ ├── Utilities.lhs │ ├── lift.faststdout │ ├── lift.slowstdout │ └── lift.stdout ├── linear │ ├── AbsCg.lhs │ ├── AbsDensematrix.lhs │ ├── Absmatlib.lhs │ ├── Cg.lhs │ ├── Densematrix.lhs │ ├── Input.lhs │ ├── Main.lhs │ ├── Makefile │ ├── Matlib.lhs │ ├── Matrix.lhs │ ├── Misc.lhs │ ├── NofibUtils.hs │ ├── Utils.lhs │ ├── linear.faststdout │ ├── linear.slowstdout │ └── linear.stdout ├── maillist │ ├── Main.hs │ ├── Makefile │ ├── maillist.faststdout │ ├── maillist.slowstdout │ ├── maillist.stdout │ └── runtime_files │ │ ├── fast │ │ ├── norm │ │ └── slow ├── mkhprog │ ├── Main.lhs │ ├── Makefile │ ├── NofibUtils.hs │ └── mkhprog.1 ├── parser │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── parser.faststdin │ ├── parser.faststdout │ ├── parser.slowstdin │ ├── parser.slowstdout │ ├── parser.stdin │ └── parser.stdout ├── pic │ ├── ChargeDensity.hs │ ├── Consts.hs │ ├── ElecField.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Pic.hs │ ├── PicType.hs │ ├── Potential.hs │ ├── PushParticle.hs │ ├── Utils.hs │ └── inId │ │ ├── doc.culler │ │ ├── doc.olaf │ │ ├── pic88.id │ │ ├── pic_cul.id │ │ └── pic_olaf.id ├── prolog │ ├── Engine.hs │ ├── Examples │ ├── Interact.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Parse.hs │ ├── PrologData.hs │ ├── PureEngine.hs │ ├── README.nofib │ ├── StackEngine.hs │ ├── Subst.hs │ ├── Version.hs │ ├── prolog.faststdin │ ├── prolog.faststdout │ ├── prolog.slowstdin │ ├── prolog.slowstdout │ ├── prolog.stdin │ ├── prolog.stdout │ └── runtime_files │ │ └── stdlib ├── reptile │ ├── ALT_output │ ├── Auxprogfuns.hs │ ├── Diff.hs │ ├── Drawfuns.hs │ ├── Geomfuns.hs │ ├── Help.hs │ ├── Interstate.hs │ ├── Layout.hs │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── Mgrfuns.hs │ ├── NofibUtils.hs │ ├── Progfuns.hs │ ├── Psfuns.hs │ ├── Rational.hs │ ├── Tilefuns.hs │ ├── ghc_output │ ├── glasgow_output │ ├── hbc_output │ ├── reptile.faststdin │ ├── reptile.faststdout │ ├── reptile.slowstdin │ ├── reptile.slowstdout │ ├── reptile.stdin │ ├── reptile.stdout │ └── york_output ├── rsa │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Rsa.hs │ ├── rsa.faststdin │ ├── rsa.faststdout │ ├── rsa.slowstdin │ ├── rsa.slowstdout │ ├── rsa.stdin │ └── rsa.stdout ├── scs │ ├── LinearAlgebra.hs │ ├── Main.hs │ ├── Makefile │ ├── Parse.hs │ ├── ParseLib.hs │ ├── RandomFix.hs │ ├── Simulate.hs │ ├── Types.hs │ ├── runtime_files │ │ └── inverter.in │ └── scs.stdout ├── symalg │ ├── Ast.hs │ ├── BasicNumber.hs │ ├── BasicNumberApprox.hs │ ├── Env.hs │ ├── Eval.hs │ ├── Lexer.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Op.hs │ ├── Parser.hs │ ├── Print.hs │ ├── RealM.hs │ ├── symalg.faststdin │ ├── symalg.faststdout │ ├── symalg.slowstdin │ ├── symalg.slowstdout │ ├── symalg.stdin │ └── symalg.stdout └── veritas │ ├── Attributes.lhs │ ├── Auto.hs │ ├── Build_Tm.lhs │ ├── Build_itrm.lhs │ ├── Core_database.hs │ ├── Core_datatype.hs │ ├── Dcore.hs │ ├── DerivedRules.hs │ ├── Display.hs │ ├── Editor.hs │ ├── Edlib.lhs │ ├── Getops.hs │ ├── Globals.hs │ ├── Goals.hs │ ├── Kernel.hs │ ├── Lookup.hs │ ├── Main.hs │ ├── Makefile │ ├── NofibUtils.hs │ ├── Parse.lhs │ ├── README │ ├── Sub_Core1.hs │ ├── Sub_Core2.hs │ ├── Sub_Core3.hs │ ├── Sub_Core4.hs │ ├── Tacticals.hs │ ├── Tactics.hs │ ├── Tags.hs │ ├── ThmTactics.hs │ ├── Token.lhs │ ├── Tree.hs │ ├── Type_defs.lhs │ ├── Unparse.lhs │ ├── Vtslib.hs │ ├── X_interface.hs │ ├── grip-in │ ├── veritas.faststdout │ ├── veritas.slowstdout │ ├── veritas.stdin │ └── veritas.stdout ├── runstdtest ├── Makefile └── runstdtest.prl ├── shootout ├── Makefile ├── README.md ├── binary-trees │ ├── Main.hs │ ├── Makefile │ ├── binary-trees.faststdout │ ├── binary-trees.slowstdout │ └── binary-trees.stdout ├── fannkuch-redux │ ├── Main.hs │ ├── Makefile │ ├── fannkuch-redux.faststdout │ └── fannkuch-redux.stdout ├── fasta │ ├── Main.hs │ ├── Makefile │ └── fasta-c.c ├── k-nucleotide │ ├── Main.hs │ ├── Makefile │ ├── k-nucleotide.faststdout │ ├── k-nucleotide.slowstdout │ └── k-nucleotide.stdout ├── n-body │ ├── Main.hs │ ├── Makefile │ ├── n-body.faststdout │ ├── n-body.slowstdout │ └── n-body.stdout ├── pidigits │ ├── Main.hs │ ├── Makefile │ ├── pidigits.faststdout │ ├── pidigits.slowstdout │ └── pidigits.stdout ├── reverse-complement │ ├── Main.hs │ ├── Makefile │ └── revcomp-c.c └── spectral-norm │ ├── Main.hs │ ├── Makefile │ ├── spectral-norm.faststdout │ └── spectral-norm.stdout ├── smp ├── Makefile ├── callback001 │ ├── Main.hs │ ├── Makefile │ ├── callback001.stdout │ ├── cbits.c │ └── cbits.h ├── callback002 │ ├── Main.hs │ ├── Makefile │ ├── cbits.c │ └── cbits.h ├── chan │ ├── Makefile │ └── chan.hs ├── sieve │ ├── Makefile │ ├── README │ └── sieve.hs ├── smpbench.sh ├── stm001 │ ├── Makefile │ └── StmTest.hs ├── stm002 │ └── StmTest2.hs ├── systolic │ └── Main.hs ├── tchan │ ├── Makefile │ └── tchan.hs ├── threads001 │ ├── Main.hs │ ├── Makefile │ └── threads001.stdout ├── threads002 │ ├── Main.hs │ └── Makefile ├── threads003 │ ├── Main.hs │ └── Makefile ├── threads004 │ ├── Main.hs │ └── Makefile ├── threads005 │ └── Main.hs ├── threads006 │ ├── Main.hs │ └── Makefile └── threads007 │ ├── Control │ └── Concurrent │ │ └── CML.hs │ ├── Main.hs │ └── Makefile └── spectral ├── Makefile ├── ansi ├── Main.hs ├── Makefile ├── ansi.faststdout ├── ansi.slowstdout ├── ansi.stdout └── blub ├── atom ├── Main.hs ├── Makefile ├── atom.faststdout ├── atom.slowstdout └── atom.stdout ├── awards ├── Main.hs ├── Makefile ├── QSort.hs └── awards.faststdout ├── banner ├── Main.hs ├── Makefile ├── banner.stdin.template └── banner.stdout.template ├── boyer ├── Main.lhs ├── Makefile ├── boyer.faststdout ├── boyer.slowstdout └── boyer.stdout ├── boyer2 ├── Checker.hs ├── Lisplikefns.hs ├── Main.hs ├── Makefile ├── README ├── Rewritefns.hs ├── Rulebasetext.hs ├── boyer2.faststdout ├── boyer2.slowstdout └── boyer2.stdout ├── calendar ├── Main.hs ├── Makefile ├── calendar.faststdout ├── calendar.slowstdout └── calendar.stdout ├── cichelli ├── Auxil.hs ├── Interval.hs ├── Key.lhs ├── Main.hs ├── Makefile ├── Prog.hs ├── cichelli.faststdout ├── cichelli.slowstdout └── cichelli.stdout ├── circsim ├── Main.lhs ├── Makefile ├── circsim.faststdout ├── circsim.slowstdout └── circsim.stdout ├── clausify ├── Main.hs ├── Makefile ├── clausify.faststdout ├── clausify.slowstdout └── clausify.stdout ├── constraints ├── Main.hs ├── Makefile ├── constraints.faststdout ├── constraints.slowstdout └── constraints.stdout ├── cryptarithm1 ├── Main.hs ├── Makefile ├── cryptarithm1.faststdout ├── cryptarithm1.slowstdout └── cryptarithm1.stdout ├── cryptarithm2 ├── Main.hs ├── Makefile ├── cryptarithm2.faststdout ├── cryptarithm2.slowstdout └── cryptarithm2.stdout ├── cse ├── Main.hs ├── Makefile ├── StateMonad.hs ├── cse.faststdout ├── cse.slowstdout └── cse.stdout ├── dom-lt ├── Dom.hs ├── Main.hs ├── Makefile ├── dom-lt.faststdout ├── dom-lt.slowstdout ├── dom-lt.stdout └── ghc-examples.in ├── eliza ├── Main.hs ├── Makefile ├── eliza.faststdout ├── eliza.slowstdout ├── eliza.stdin └── eliza.stdout ├── exact-reals ├── Era.hs ├── Makefile └── exact-reals.stdout ├── expert ├── Knowledge.hs ├── Main.hs ├── Makefile ├── Match.hs ├── README ├── Result.hs ├── Search.hs ├── Table.hs ├── expert.faststdout ├── expert.slowstdout ├── expert.stdin ├── expert.stdout └── runtime_files │ └── animals ├── fft2 ├── Complex_Vectors.lhs ├── Fourier.lhs ├── MAIL ├── Main.lhs ├── Makefile ├── README.nofib ├── fft.c ├── fft2.stdout ├── fourier.f ├── fourier.m └── old │ ├── Makefile │ ├── fft2.slowstdout │ ├── fft2.slowstdout-x86-linux │ ├── fft2.slowstdout-x86-mingw │ ├── fft2.slowstdout-x86_64 │ ├── fft2.stdout │ ├── fft2.stdout-mingw │ ├── fft2.stdout-x86_64 │ ├── fft2.stdout1 │ ├── fft2.stdout2 │ ├── fft2.stdout3 │ ├── fft2.stdout4 │ ├── fft2.stdout5 │ ├── fft2.stdout6 │ └── fft2.stdout7 ├── fibheaps ├── Main.lhs ├── Makefile └── orig ├── fish ├── Main.hs └── Makefile ├── gcd ├── Main.hs ├── Makefile ├── gcd.faststdout ├── gcd.slowstdout └── gcd.stdout ├── hartel ├── Fast2haskell.hs ├── Fast2haskell2.hs ├── Makefile ├── comp_lab_zift │ ├── Main.hs │ ├── Makefile │ ├── comp_lab_zift.faststdout │ ├── comp_lab_zift.slowstdout │ └── comp_lab_zift.stdout ├── event │ ├── Main.hs │ ├── Makefile │ ├── event.faststdout │ ├── event.slowstdout │ └── event.stdout ├── fft │ ├── Main.hs │ ├── Makefile │ ├── fft.faststdout │ ├── fft.slowstdout │ └── fft.stdout ├── genfft │ ├── Main.hs │ ├── Makefile │ ├── genfft.faststdout │ ├── genfft.slowstdout │ └── genfft.stdout ├── ida │ ├── Main.hs │ ├── Makefile │ ├── ida.faststdout │ ├── ida.slowstdout │ └── ida.stdout ├── listcompr │ ├── Main.hs │ ├── Makefile │ ├── listcompr.faststdout │ ├── listcompr.slowstdout │ └── listcompr.stdout ├── listcopy │ ├── Main.hs │ ├── Makefile │ ├── listcopy.faststdout │ ├── listcopy.slowstdout │ └── listcopy.stdout ├── nucleic2 │ ├── MAIL │ ├── Main.hs │ ├── Makefile │ ├── RA.hs │ ├── RC.hs │ ├── README │ ├── RG.hs │ ├── RU.hs │ ├── Types.hs │ ├── paper │ │ ├── paper.bbl │ │ ├── paper.ps │ │ └── paper.tex │ └── unboxery.h ├── parstof │ ├── Main.hs │ ├── Makefile │ ├── parstof.faststdout │ ├── parstof.slowstdout │ └── parstof.stdout ├── sched │ ├── Main.hs │ ├── Makefile │ ├── sched.faststdout │ ├── sched.slowstdout │ └── sched.stdout ├── solid │ ├── Main.hs │ ├── Makefile │ ├── solid.faststdout │ ├── solid.slowstdout │ └── solid.stdout ├── transform │ ├── Main.hs │ ├── Makefile │ ├── transform.faststdout │ ├── transform.slowstdout │ └── transform.stdout ├── typecheck │ ├── Main.hs │ ├── Makefile │ ├── typecheck.faststdout │ ├── typecheck.slowstdout │ └── typecheck.stdout ├── wang │ ├── Main.hs │ ├── Makefile │ ├── wang.faststdout │ ├── wang.slowstdout │ └── wang.stdout └── wave4main │ ├── Main.hs │ ├── Makefile │ ├── wave4main.faststdout │ ├── wave4main.slowstdout │ └── wave4main.stdout ├── integer ├── Main.hs └── Makefile ├── knights ├── ChessSetArray.lhs ├── ChessSetList.lhs ├── KnightHeuristic.lhs ├── Main.lhs ├── Makefile ├── Queue.lhs ├── README ├── Sort.lhs ├── functional.bib ├── knights.faststdout ├── knights.slowstdout ├── knights.stdout └── root.lit ├── lambda ├── Main.hs ├── Makefile ├── lambda.faststdout ├── lambda.slowstdout └── lambda.stdout ├── last-piece ├── Main.hs ├── Makefile └── last-piece.stdout ├── lcss ├── Main.hs ├── Makefile ├── lcss.faststdout ├── lcss.slowstdout └── lcss.stdout ├── life ├── Main.hs ├── Makefile ├── life.faststdout ├── life.slowstdout ├── life.stdout └── life.test ├── mandel ├── MAIL ├── Main.hs ├── Makefile ├── Mandel.lhs ├── MandelOld.lhs ├── PortablePixmap.lhs └── root.lit ├── mandel2 ├── Main.hs └── Makefile ├── mate ├── Board.hs ├── Main.hs ├── Makefile ├── Move.hs ├── Problem.hs ├── README ├── Solution.hs ├── mate.faststdout ├── mate.slowstdout ├── mate.stdout └── runtime_files │ ├── ellerman.prob │ ├── ellerman.soln │ ├── fridlizius.prob │ ├── fridlizius.soln │ ├── heathcote3.prob │ ├── heathcote3.soln │ ├── holzhausen.prob │ ├── holzhausen.soln │ ├── kidson.prob │ ├── kohtz.prob │ ├── kohtz.soln │ ├── marin.prob │ ├── marin.soln │ ├── shinkman.prob │ ├── shinkman.soln │ ├── simple.prob │ ├── simple.soln │ ├── wurzburg.prob │ └── wurzburg.soln ├── minimax ├── Board.hs ├── Game.hs ├── Main.hs ├── Makefile ├── Prog.hs ├── Tree.hs └── Wins.hs ├── multiplier ├── Main.hs ├── Makefile ├── multiplier.faststdout ├── multiplier.slowstdout └── multiplier.stdout ├── para ├── Main.lhs ├── Makefile ├── c++ │ ├── Para.C │ ├── Para.h │ ├── Part2.C │ ├── Queue.C │ ├── Queue.h │ ├── Thin.C │ ├── Thin.h │ ├── cout │ ├── crowd │ └── part2 └── runtime_files │ └── input-data ├── power ├── Main.hs └── Makefile ├── pretty ├── CharSeq.hs ├── Main.hs ├── Makefile ├── Pretty.hs └── pretty.stdout ├── primetest ├── IntLib.lhs ├── Main.lhs ├── Makefile ├── MyRandom.lhs ├── Prime.lhs ├── Readme ├── mersenne607 ├── primetest.faststdin ├── primetest.faststdout ├── primetest.slowstdin ├── primetest.slowstdout ├── primetest.stdin └── primetest.stdout ├── puzzle ├── Main.hs └── Makefile ├── rewrite ├── Main.lhs ├── Makefile └── rewrite.stdout ├── scc ├── Digraph.hs ├── Digraph.m ├── Main.hs ├── Makefile └── scc.stdout ├── secretary ├── Main.lhs ├── Makefile └── secretary.stdout ├── simple ├── MAIL ├── Main.hs ├── Makefile ├── simple.c └── simple.f ├── sorting ├── Main.hs ├── Makefile ├── NofibUtils.hs ├── Sort.hs ├── sorting.faststdout ├── sorting.slowstdout └── sorting.stdout ├── sphere ├── Main.lhs ├── Makefile ├── sphere.faststdout ├── sphere.slowstdout └── sphere.stdout └── treejoin ├── MAIL ├── Main.hs ├── Makefile ├── runtime_files ├── 1500.1 ├── 1500.2 ├── 27000.1 ├── 27000.2 ├── 8000.1 └── 8000.2 └── treejoin.stdout /.arcconfig: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/.arcconfig -------------------------------------------------------------------------------- /.gitignore: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/.gitignore -------------------------------------------------------------------------------- /.gitlab-ci.yml: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/.gitlab-ci.yml -------------------------------------------------------------------------------- /CODEOWNERS: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/CODEOWNERS -------------------------------------------------------------------------------- /Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/Makefile -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/README.md -------------------------------------------------------------------------------- /Simon-nofib-notes: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/Simon-nofib-notes -------------------------------------------------------------------------------- /common/NofibUtils.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/common/NofibUtils.hs -------------------------------------------------------------------------------- /docs/paper/Jmakefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/Jmakefile -------------------------------------------------------------------------------- /docs/paper/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/MAIL -------------------------------------------------------------------------------- /docs/paper/compile.sc: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/compile.sc -------------------------------------------------------------------------------- /docs/paper/compile.txt: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/compile.txt -------------------------------------------------------------------------------- /docs/paper/hbc-vs-ghc.cln: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/hbc-vs-ghc.cln -------------------------------------------------------------------------------- /docs/paper/hbc-vs-ghc.sc: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/hbc-vs-ghc.sc -------------------------------------------------------------------------------- /docs/paper/nofib_only.bib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/nofib_only.bib -------------------------------------------------------------------------------- /docs/paper/paper.bbl: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/paper.bbl -------------------------------------------------------------------------------- /docs/paper/paper.verb: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/paper.verb -------------------------------------------------------------------------------- /docs/paper/reviews: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/reviews -------------------------------------------------------------------------------- /docs/paper/run.sc: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/run.sc -------------------------------------------------------------------------------- /docs/paper/run.txt: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/run.txt -------------------------------------------------------------------------------- /docs/paper/slides-root.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/slides-root.tex -------------------------------------------------------------------------------- /docs/paper/slides.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/slides.tex -------------------------------------------------------------------------------- /docs/paper/ticky.sc: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/ticky.sc -------------------------------------------------------------------------------- /docs/paper/ticky.sc.lat: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/docs/paper/ticky.sc.lat -------------------------------------------------------------------------------- /easy.sh: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/easy.sh -------------------------------------------------------------------------------- /gc/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/Makefile -------------------------------------------------------------------------------- /gc/cacheprof/Arch_x86.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/cacheprof/Arch_x86.hs -------------------------------------------------------------------------------- /gc/cacheprof/Generics.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/cacheprof/Generics.hs -------------------------------------------------------------------------------- /gc/cacheprof/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/cacheprof/Main.hs -------------------------------------------------------------------------------- /gc/cacheprof/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/cacheprof/Makefile -------------------------------------------------------------------------------- /gc/circsim/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/circsim/Main.lhs -------------------------------------------------------------------------------- /gc/circsim/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/circsim/Makefile -------------------------------------------------------------------------------- /gc/circsim/circsim.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/circsim/circsim.stdout -------------------------------------------------------------------------------- /gc/constraints/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/constraints/Main.hs -------------------------------------------------------------------------------- /gc/constraints/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/constraints/Makefile -------------------------------------------------------------------------------- /gc/fibheaps/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fibheaps/Main.lhs -------------------------------------------------------------------------------- /gc/fibheaps/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fibheaps/Makefile -------------------------------------------------------------------------------- /gc/fibheaps/fibheaps.stdout: -------------------------------------------------------------------------------- 1 | True -------------------------------------------------------------------------------- /gc/fibheaps/orig: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fibheaps/orig -------------------------------------------------------------------------------- /gc/fibheaps/stuff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fibheaps/stuff -------------------------------------------------------------------------------- /gc/fulsom/Bah.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Bah.hs -------------------------------------------------------------------------------- /gc/fulsom/Csg.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Csg.hs -------------------------------------------------------------------------------- /gc/fulsom/Interval.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Interval.hs -------------------------------------------------------------------------------- /gc/fulsom/Kolor.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Kolor.hs -------------------------------------------------------------------------------- /gc/fulsom/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/MAIL -------------------------------------------------------------------------------- /gc/fulsom/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Main.hs -------------------------------------------------------------------------------- /gc/fulsom/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Makefile -------------------------------------------------------------------------------- /gc/fulsom/Matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Matrix.hs -------------------------------------------------------------------------------- /gc/fulsom/Oct.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Oct.hs -------------------------------------------------------------------------------- /gc/fulsom/Patchlevel.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Patchlevel.hs -------------------------------------------------------------------------------- /gc/fulsom/Quad.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Quad.hs -------------------------------------------------------------------------------- /gc/fulsom/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/README.nofib -------------------------------------------------------------------------------- /gc/fulsom/README.original: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/README.original -------------------------------------------------------------------------------- /gc/fulsom/Raster.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Raster.hs -------------------------------------------------------------------------------- /gc/fulsom/Shapes.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Shapes.hs -------------------------------------------------------------------------------- /gc/fulsom/Types.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Types.hs -------------------------------------------------------------------------------- /gc/fulsom/Vector.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/Vector.hs -------------------------------------------------------------------------------- /gc/fulsom/fulsom.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/fulsom.stdout -------------------------------------------------------------------------------- /gc/fulsom/out: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/out -------------------------------------------------------------------------------- /gc/fulsom/pics/sphere.gif: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/pics/sphere.gif -------------------------------------------------------------------------------- /gc/fulsom/raster/raster.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/raster/raster.c -------------------------------------------------------------------------------- /gc/fulsom/stuff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/stuff -------------------------------------------------------------------------------- /gc/fulsom/stuff-SAVE: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/stuff-SAVE -------------------------------------------------------------------------------- /gc/fulsom/stuff2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/fulsom/stuff2 -------------------------------------------------------------------------------- /gc/gc_bench/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/gc_bench/Makefile -------------------------------------------------------------------------------- /gc/gc_bench/gc_bench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/gc_bench/gc_bench.hs -------------------------------------------------------------------------------- /gc/happy/AbsSyn.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/AbsSyn.lhs -------------------------------------------------------------------------------- /gc/happy/AttrGrammar.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/AttrGrammar.lhs -------------------------------------------------------------------------------- /gc/happy/First.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/First.lhs -------------------------------------------------------------------------------- /gc/happy/GenUtils.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/GenUtils.lhs -------------------------------------------------------------------------------- /gc/happy/Grammar.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Grammar.lhs -------------------------------------------------------------------------------- /gc/happy/Info.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Info.lhs -------------------------------------------------------------------------------- /gc/happy/LALR.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/LALR.lhs -------------------------------------------------------------------------------- /gc/happy/Lexer.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Lexer.lhs -------------------------------------------------------------------------------- /gc/happy/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Makefile -------------------------------------------------------------------------------- /gc/happy/ParseMonad.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/ParseMonad.lhs -------------------------------------------------------------------------------- /gc/happy/Parser.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Parser.hs -------------------------------------------------------------------------------- /gc/happy/Paths_happy.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Paths_happy.hs -------------------------------------------------------------------------------- /gc/happy/ProduceCode.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/ProduceCode.lhs -------------------------------------------------------------------------------- /gc/happy/Set.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Set.hs -------------------------------------------------------------------------------- /gc/happy/Target.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/Target.lhs -------------------------------------------------------------------------------- /gc/happy/TestInput.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/TestInput.hs -------------------------------------------------------------------------------- /gc/happy/TestInput.y: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/TestInput.y -------------------------------------------------------------------------------- /gc/happy/happy.expected: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/happy.expected -------------------------------------------------------------------------------- /gc/happy/happy.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/happy.lhs -------------------------------------------------------------------------------- /gc/happy/happy.stderr: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/happy/happy.stderr -------------------------------------------------------------------------------- /gc/hash/HashTable.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/hash/HashTable.hs -------------------------------------------------------------------------------- /gc/hash/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/hash/Makefile -------------------------------------------------------------------------------- /gc/hash/hash.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/hash/hash.hs -------------------------------------------------------------------------------- /gc/hash/hash.stdout: -------------------------------------------------------------------------------- 1 | Just 100 2 | -------------------------------------------------------------------------------- /gc/lcss/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/lcss/Main.hs -------------------------------------------------------------------------------- /gc/lcss/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/lcss/Makefile -------------------------------------------------------------------------------- /gc/lcss/lcss.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/lcss/lcss.faststdout -------------------------------------------------------------------------------- /gc/lcss/lcss.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/lcss/lcss.slowstdout -------------------------------------------------------------------------------- /gc/lcss/lcss.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/lcss/lcss.stdout -------------------------------------------------------------------------------- /gc/linear/AbsCg.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/AbsCg.lhs -------------------------------------------------------------------------------- /gc/linear/Absmatlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Absmatlib.lhs -------------------------------------------------------------------------------- /gc/linear/Cg.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Cg.lhs -------------------------------------------------------------------------------- /gc/linear/Densematrix.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Densematrix.lhs -------------------------------------------------------------------------------- /gc/linear/Input.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Input.lhs -------------------------------------------------------------------------------- /gc/linear/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Makefile -------------------------------------------------------------------------------- /gc/linear/Matlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Matlib.lhs -------------------------------------------------------------------------------- /gc/linear/Matrix.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Matrix.lhs -------------------------------------------------------------------------------- /gc/linear/Misc.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Misc.lhs -------------------------------------------------------------------------------- /gc/linear/Utils.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/Utils.lhs -------------------------------------------------------------------------------- /gc/linear/linear.expected: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/linear.expected -------------------------------------------------------------------------------- /gc/linear/linear.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/linear.lhs -------------------------------------------------------------------------------- /gc/linear/linear.ps: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/linear.ps -------------------------------------------------------------------------------- /gc/linear/linear.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/linear/linear.stdout -------------------------------------------------------------------------------- /gc/mutstore1/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore1/Main.hs -------------------------------------------------------------------------------- /gc/mutstore1/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore1/Makefile -------------------------------------------------------------------------------- /gc/mutstore1/Store1.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore1/Store1.hs -------------------------------------------------------------------------------- /gc/mutstore2/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore2/Main.hs -------------------------------------------------------------------------------- /gc/mutstore2/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore2/Makefile -------------------------------------------------------------------------------- /gc/mutstore2/Store2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/mutstore2/Store2.hs -------------------------------------------------------------------------------- /gc/power/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/power/Main.hs -------------------------------------------------------------------------------- /gc/power/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/power/Makefile -------------------------------------------------------------------------------- /gc/power/power.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/power/power.faststdout -------------------------------------------------------------------------------- /gc/power/power.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/power/power.slowstdout -------------------------------------------------------------------------------- /gc/power/power.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/power/power.stdout -------------------------------------------------------------------------------- /gc/spellcheck/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/spellcheck/Makefile -------------------------------------------------------------------------------- /gc/spellcheck/input: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/spellcheck/input -------------------------------------------------------------------------------- /gc/spellcheck/spellcheck.stdout: -------------------------------------------------------------------------------- 1 | [] 2 | -------------------------------------------------------------------------------- /gc/spellcheck/words: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/spellcheck/words -------------------------------------------------------------------------------- /gc/treejoin/27000.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/treejoin/27000.1 -------------------------------------------------------------------------------- /gc/treejoin/27000.2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/treejoin/27000.2 -------------------------------------------------------------------------------- /gc/treejoin/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/treejoin/MAIL -------------------------------------------------------------------------------- /gc/treejoin/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/treejoin/Main.hs -------------------------------------------------------------------------------- /gc/treejoin/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/gc/treejoin/Makefile -------------------------------------------------------------------------------- /gc/treejoin/treejoin.stdout: -------------------------------------------------------------------------------- 1 | () 2 | -------------------------------------------------------------------------------- /imaginary/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/Makefile -------------------------------------------------------------------------------- /imaginary/bernouilli/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /imaginary/digits-of-e1/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /imaginary/digits-of-e2/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /imaginary/exp3_8/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/exp3_8/Main.hs -------------------------------------------------------------------------------- /imaginary/exp3_8/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/exp3_8/Makefile -------------------------------------------------------------------------------- /imaginary/exp3_8/exp3_8.faststdout: -------------------------------------------------------------------------------- 1 | 6561 2 | -------------------------------------------------------------------------------- /imaginary/exp3_8/exp3_8.stdout: -------------------------------------------------------------------------------- 1 | 19683 2 | -------------------------------------------------------------------------------- /imaginary/gen_regexps/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /imaginary/integrate/integrate.faststdout: -------------------------------------------------------------------------------- 1 | 0.0 2 | -------------------------------------------------------------------------------- /imaginary/integrate/integrate.slowstdout: -------------------------------------------------------------------------------- 1 | 1.3615586841036482e34 2 | -------------------------------------------------------------------------------- /imaginary/integrate/integrate.stdout: -------------------------------------------------------------------------------- 1 | 9.093955583391733e28 2 | -------------------------------------------------------------------------------- /imaginary/kahan/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/kahan/Main.hs -------------------------------------------------------------------------------- /imaginary/kahan/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/kahan/Makefile -------------------------------------------------------------------------------- /imaginary/primes/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/primes/Main.hs -------------------------------------------------------------------------------- /imaginary/primes/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/primes/Makefile -------------------------------------------------------------------------------- /imaginary/primes/csieve.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/primes/csieve.c -------------------------------------------------------------------------------- /imaginary/queens/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/queens/Main.hs -------------------------------------------------------------------------------- /imaginary/queens/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/queens/Makefile -------------------------------------------------------------------------------- /imaginary/queens/queens.faststdout: -------------------------------------------------------------------------------- 1 | 14200 2 | -------------------------------------------------------------------------------- /imaginary/queens/queens.slowstdout: -------------------------------------------------------------------------------- 1 | 365596 2 | -------------------------------------------------------------------------------- /imaginary/queens/queens.stdout: -------------------------------------------------------------------------------- 1 | 73712 2 | -------------------------------------------------------------------------------- /imaginary/rfib/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/rfib/Main.hs -------------------------------------------------------------------------------- /imaginary/rfib/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/rfib/Makefile -------------------------------------------------------------------------------- /imaginary/rfib/rfib.faststdout: -------------------------------------------------------------------------------- 1 | 2.9860703e7 2 | -------------------------------------------------------------------------------- /imaginary/rfib/rfib.slowstdout: -------------------------------------------------------------------------------- 1 | 1.402817465e9 2 | -------------------------------------------------------------------------------- /imaginary/rfib/rfib.stdout: -------------------------------------------------------------------------------- 1 | 3.31160281e8 2 | -------------------------------------------------------------------------------- /imaginary/tak/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/tak/Main.hs -------------------------------------------------------------------------------- /imaginary/tak/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/tak/Makefile -------------------------------------------------------------------------------- /imaginary/tak/tak.faststdout: -------------------------------------------------------------------------------- 1 | 16 2 | -------------------------------------------------------------------------------- /imaginary/tak/tak.slowstdout: -------------------------------------------------------------------------------- 1 | 9 2 | -------------------------------------------------------------------------------- /imaginary/tak/tak.stdout: -------------------------------------------------------------------------------- 1 | 9 2 | -------------------------------------------------------------------------------- /imaginary/x2n1/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/x2n1/Main.hs -------------------------------------------------------------------------------- /imaginary/x2n1/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/x2n1/Makefile -------------------------------------------------------------------------------- /imaginary/x2n1/x2n1.faststdout: -------------------------------------------------------------------------------- 1 | 34. -------------------------------------------------------------------------------- /imaginary/x2n1/x2n1.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/imaginary/x2n1/x2n1.stdout -------------------------------------------------------------------------------- /mk/boilerplate.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/boilerplate.mk -------------------------------------------------------------------------------- /mk/ghc-opts.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/ghc-opts.mk -------------------------------------------------------------------------------- /mk/ghc-paths.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/ghc-paths.mk -------------------------------------------------------------------------------- /mk/ghc-recurse.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/ghc-recurse.mk -------------------------------------------------------------------------------- /mk/ghc-suffix.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/ghc-suffix.mk -------------------------------------------------------------------------------- /mk/ghc-target.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/ghc-target.mk -------------------------------------------------------------------------------- /mk/opts.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/opts.mk -------------------------------------------------------------------------------- /mk/paths.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/paths.mk -------------------------------------------------------------------------------- /mk/suffix.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/suffix.mk -------------------------------------------------------------------------------- /mk/target.mk: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/mk/target.mk -------------------------------------------------------------------------------- /nofib-analyse/CmdLine.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/nofib-analyse/CmdLine.hs -------------------------------------------------------------------------------- /nofib-analyse/GenUtils.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/nofib-analyse/GenUtils.lhs -------------------------------------------------------------------------------- /nofib-analyse/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/nofib-analyse/Main.hs -------------------------------------------------------------------------------- /nofib-analyse/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/nofib-analyse/Makefile -------------------------------------------------------------------------------- /nofib-analyse/Slurp.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/nofib-analyse/Slurp.hs -------------------------------------------------------------------------------- /nofib-analyse/cabal.project: -------------------------------------------------------------------------------- 1 | -- project file for "boot" utilities 2 | packages: . 3 | -------------------------------------------------------------------------------- /parallel/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/Makefile -------------------------------------------------------------------------------- /parallel/OLD/NESL/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/NESL/Makefile -------------------------------------------------------------------------------- /parallel/OLD/NESL/fft.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/NESL/fft.lhs -------------------------------------------------------------------------------- /parallel/OLD/bom/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/bom/Makefile -------------------------------------------------------------------------------- /parallel/OLD/bom/bom.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/bom/bom.hs -------------------------------------------------------------------------------- /parallel/OLD/par001/par001.stdout: -------------------------------------------------------------------------------- 1 | 84000 -------------------------------------------------------------------------------- /parallel/OLD/soda/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/soda/Main.hs -------------------------------------------------------------------------------- /parallel/OLD/soda/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/soda/Makefile -------------------------------------------------------------------------------- /parallel/OLD/soda7/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/OLD/soda7/Main.hs -------------------------------------------------------------------------------- /parallel/OLD/soda7/soda7.stdout: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /parallel/cfd/C_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/C_matrix.hs -------------------------------------------------------------------------------- /parallel/cfd/Data8.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Data8.hs -------------------------------------------------------------------------------- /parallel/cfd/Defs.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Defs.hs -------------------------------------------------------------------------------- /parallel/cfd/Gen_net.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Gen_net.hs -------------------------------------------------------------------------------- /parallel/cfd/Jcb_method.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Jcb_method.hs -------------------------------------------------------------------------------- /parallel/cfd/L_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/L_matrix.hs -------------------------------------------------------------------------------- /parallel/cfd/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Main.hs -------------------------------------------------------------------------------- /parallel/cfd/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Makefile -------------------------------------------------------------------------------- /parallel/cfd/Norm.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Norm.hs -------------------------------------------------------------------------------- /parallel/cfd/Quad_def.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/Quad_def.hs -------------------------------------------------------------------------------- /parallel/cfd/S_Array.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/S_Array.hs -------------------------------------------------------------------------------- /parallel/cfd/S_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/S_matrix.hs -------------------------------------------------------------------------------- /parallel/cfd/TG_iter.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/TG_iter.hs -------------------------------------------------------------------------------- /parallel/cfd/cfd.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/cfd/cfd.stdout -------------------------------------------------------------------------------- /parallel/coins/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/coins/Makefile -------------------------------------------------------------------------------- /parallel/coins/coins.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/coins/coins.hs -------------------------------------------------------------------------------- /parallel/coins/coins.stdout: -------------------------------------------------------------------------------- 1 | 206940 2 | -------------------------------------------------------------------------------- /parallel/dcbm/DCBM.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/DCBM.hs -------------------------------------------------------------------------------- /parallel/dcbm/Delay.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/Delay.hs -------------------------------------------------------------------------------- /parallel/dcbm/Fwif.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/Fwif.hs -------------------------------------------------------------------------------- /parallel/dcbm/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/Main.hs -------------------------------------------------------------------------------- /parallel/dcbm/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/Makefile -------------------------------------------------------------------------------- /parallel/dcbm/Types.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/dcbm/Types.hs -------------------------------------------------------------------------------- /parallel/gray/CSG.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/CSG.hs -------------------------------------------------------------------------------- /parallel/gray/Construct.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Construct.hs -------------------------------------------------------------------------------- /parallel/gray/Data.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Data.hs -------------------------------------------------------------------------------- /parallel/gray/Eval.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Eval.hs -------------------------------------------------------------------------------- /parallel/gray/Geometry.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Geometry.hs -------------------------------------------------------------------------------- /parallel/gray/Interval.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Interval.hs -------------------------------------------------------------------------------- /parallel/gray/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Main.hs -------------------------------------------------------------------------------- /parallel/gray/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Makefile -------------------------------------------------------------------------------- /parallel/gray/Misc.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Misc.hs -------------------------------------------------------------------------------- /parallel/gray/Parse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Parse.hs -------------------------------------------------------------------------------- /parallel/gray/RayTrace.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/RayTrace.hs -------------------------------------------------------------------------------- /parallel/gray/Surface.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/Surface.hs -------------------------------------------------------------------------------- /parallel/gray/foo: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/foo -------------------------------------------------------------------------------- /parallel/gray/foo.gif: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/foo.gif -------------------------------------------------------------------------------- /parallel/gray/galois.gml: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/galois.gml -------------------------------------------------------------------------------- /parallel/gray/gray.ppm: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/gray.ppm -------------------------------------------------------------------------------- /parallel/gray/gray.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/gray/gray.stdout -------------------------------------------------------------------------------- /parallel/linsolv/CRA.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/linsolv/CRA.hs -------------------------------------------------------------------------------- /parallel/linsolv/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/linsolv/Main.hs -------------------------------------------------------------------------------- /parallel/linsolv/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/linsolv/Makefile -------------------------------------------------------------------------------- /parallel/linsolv/Matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/linsolv/Matrix.hs -------------------------------------------------------------------------------- /parallel/mandel/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/mandel/Main.lhs -------------------------------------------------------------------------------- /parallel/mandel/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/mandel/Makefile -------------------------------------------------------------------------------- /parallel/mandel/Mandel.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/mandel/Mandel.lhs -------------------------------------------------------------------------------- /parallel/matmult/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/matmult/Makefile -------------------------------------------------------------------------------- /parallel/matmult/matmult.stdout: -------------------------------------------------------------------------------- 1 | [[Nothing]] 2 | -------------------------------------------------------------------------------- /parallel/minimax/Board.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Board.hs -------------------------------------------------------------------------------- /parallel/minimax/Game.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Game.hs -------------------------------------------------------------------------------- /parallel/minimax/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Main.hs -------------------------------------------------------------------------------- /parallel/minimax/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Makefile -------------------------------------------------------------------------------- /parallel/minimax/Prog.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Prog.hs -------------------------------------------------------------------------------- /parallel/minimax/Tree.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Tree.hs -------------------------------------------------------------------------------- /parallel/minimax/Wins.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/minimax/Wins.hs -------------------------------------------------------------------------------- /parallel/nbody/Future.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/nbody/Future.hs -------------------------------------------------------------------------------- /parallel/nbody/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/nbody/Makefile -------------------------------------------------------------------------------- /parallel/nbody/nbody.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/nbody/nbody.hs -------------------------------------------------------------------------------- /parallel/nbody/nbody.stdout: -------------------------------------------------------------------------------- 1 | 1500 2 | -------------------------------------------------------------------------------- /parallel/parfib/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/parfib/Main.hs -------------------------------------------------------------------------------- /parallel/parfib/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/parfib/Makefile -------------------------------------------------------------------------------- /parallel/parfib/parfib.stdout: -------------------------------------------------------------------------------- 1 | parfib 43 = 1402817465 2 | -------------------------------------------------------------------------------- /parallel/partak/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/partak/Main.hs -------------------------------------------------------------------------------- /parallel/partak/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/partak/Makefile -------------------------------------------------------------------------------- /parallel/partak/partak.stdout: -------------------------------------------------------------------------------- 1 | tak 36 17 8 = 17 2 | -------------------------------------------------------------------------------- /parallel/partree/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/partree/Makefile -------------------------------------------------------------------------------- /parallel/partree/Tree.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/partree/Tree.hs -------------------------------------------------------------------------------- /parallel/partree/partree.stdout: -------------------------------------------------------------------------------- 1 | partree 300 100 = 33972 2 | -------------------------------------------------------------------------------- /parallel/prsa/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/prsa/Main.hs -------------------------------------------------------------------------------- /parallel/prsa/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/prsa/Makefile -------------------------------------------------------------------------------- /parallel/prsa/Rsa.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/prsa/Rsa.hs -------------------------------------------------------------------------------- /parallel/prsa/prsa.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/prsa/prsa.stdout -------------------------------------------------------------------------------- /parallel/queens/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/queens/Main.hs -------------------------------------------------------------------------------- /parallel/queens/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/queens/Makefile -------------------------------------------------------------------------------- /parallel/queens/queens.stdout: -------------------------------------------------------------------------------- 1 | 73712 2 | -------------------------------------------------------------------------------- /parallel/ray/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/ray/Main.lhs -------------------------------------------------------------------------------- /parallel/ray/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/ray/Makefile -------------------------------------------------------------------------------- /parallel/ray/ray.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/ray/ray.stdout -------------------------------------------------------------------------------- /parallel/sumeuler/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/sumeuler/Makefile -------------------------------------------------------------------------------- /parallel/sumeuler/sumeuler.stdout: -------------------------------------------------------------------------------- 1 | sumEuler [0..8000] = 19455781 2 | -------------------------------------------------------------------------------- /parallel/transclos/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/transclos/Main.hs -------------------------------------------------------------------------------- /parallel/warshall/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/parallel/warshall/Makefile -------------------------------------------------------------------------------- /real/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/Makefile -------------------------------------------------------------------------------- /real/anna/AbsConc3.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/AbsConc3.hs -------------------------------------------------------------------------------- /real/anna/AbstractEval2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/AbstractEval2.hs -------------------------------------------------------------------------------- /real/anna/AbstractMisc.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/AbstractMisc.hs -------------------------------------------------------------------------------- /real/anna/AbstractVals2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/AbstractVals2.hs -------------------------------------------------------------------------------- /real/anna/Apply.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Apply.hs -------------------------------------------------------------------------------- /real/anna/BarakiConc3.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/BarakiConc3.hs -------------------------------------------------------------------------------- /real/anna/BarakiMeet.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/BarakiMeet.hs -------------------------------------------------------------------------------- /real/anna/BaseDefs.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/BaseDefs.hs -------------------------------------------------------------------------------- /real/anna/Constructors.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Constructors.hs -------------------------------------------------------------------------------- /real/anna/Dependancy.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Dependancy.hs -------------------------------------------------------------------------------- /real/anna/DomainExpr.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/DomainExpr.hs -------------------------------------------------------------------------------- /real/anna/EtaAbstract.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/EtaAbstract.hs -------------------------------------------------------------------------------- /real/anna/FrontierMisc2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/FrontierMisc2.hs -------------------------------------------------------------------------------- /real/anna/Inverse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Inverse.hs -------------------------------------------------------------------------------- /real/anna/LambdaLift5.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/LambdaLift5.hs -------------------------------------------------------------------------------- /real/anna/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Main.hs -------------------------------------------------------------------------------- /real/anna/MakeDomains.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/MakeDomains.hs -------------------------------------------------------------------------------- /real/anna/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Makefile -------------------------------------------------------------------------------- /real/anna/Monster.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Monster.hs -------------------------------------------------------------------------------- /real/anna/Monstermakefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Monstermakefile -------------------------------------------------------------------------------- /real/anna/MyUtils.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/MyUtils.hs -------------------------------------------------------------------------------- /real/anna/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/anna/Parser2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Parser2.hs -------------------------------------------------------------------------------- /real/anna/PrettyPrint.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/PrettyPrint.hs -------------------------------------------------------------------------------- /real/anna/PrintResults.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/PrintResults.hs -------------------------------------------------------------------------------- /real/anna/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/README -------------------------------------------------------------------------------- /real/anna/ReadTable.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/ReadTable.hs -------------------------------------------------------------------------------- /real/anna/Simplify.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Simplify.hs -------------------------------------------------------------------------------- /real/anna/StrictAn6.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/StrictAn6.hs -------------------------------------------------------------------------------- /real/anna/TExpr2DExpr.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/TExpr2DExpr.hs -------------------------------------------------------------------------------- /real/anna/Testmakefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Testmakefile -------------------------------------------------------------------------------- /real/anna/TypeCheck5.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/TypeCheck5.hs -------------------------------------------------------------------------------- /real/anna/Utils.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/Utils.hs -------------------------------------------------------------------------------- /real/anna/anna.faststdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.faststdin -------------------------------------------------------------------------------- /real/anna/anna.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.faststdout -------------------------------------------------------------------------------- /real/anna/anna.full: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.full -------------------------------------------------------------------------------- /real/anna/anna.postscript: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.postscript -------------------------------------------------------------------------------- /real/anna/anna.prescript: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.prescript -------------------------------------------------------------------------------- /real/anna/anna.slowstdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.slowstdin -------------------------------------------------------------------------------- /real/anna/anna.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.slowstdout -------------------------------------------------------------------------------- /real/anna/anna.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.stdin -------------------------------------------------------------------------------- /real/anna/anna.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/anna.stdout -------------------------------------------------------------------------------- /real/anna/big.sum.out: -------------------------------------------------------------------------------- 1 | 58267 48 2 | -------------------------------------------------------------------------------- /real/anna/nofib_driver: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/anna/nofib_driver -------------------------------------------------------------------------------- /real/bspt/BSPT.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/BSPT.lhs -------------------------------------------------------------------------------- /real/bspt/Euclid.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Euclid.lhs -------------------------------------------------------------------------------- /real/bspt/EuclidGMS.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/EuclidGMS.lhs -------------------------------------------------------------------------------- /real/bspt/GeomNum.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/GeomNum.lhs -------------------------------------------------------------------------------- /real/bspt/Init.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Init.lhs -------------------------------------------------------------------------------- /real/bspt/Input.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Input.lhs -------------------------------------------------------------------------------- /real/bspt/Interface.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Interface.lhs -------------------------------------------------------------------------------- /real/bspt/Interpret.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Interpret.lhs -------------------------------------------------------------------------------- /real/bspt/Libfuns.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Libfuns.lhs -------------------------------------------------------------------------------- /real/bspt/MGRlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/MGRlib.lhs -------------------------------------------------------------------------------- /real/bspt/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Main.hs -------------------------------------------------------------------------------- /real/bspt/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Makefile -------------------------------------------------------------------------------- /real/bspt/Merge.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Merge.lhs -------------------------------------------------------------------------------- /real/bspt/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/bspt/Params.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Params.lhs -------------------------------------------------------------------------------- /real/bspt/Prog.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Prog.hs -------------------------------------------------------------------------------- /real/bspt/Rationals.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Rationals.lhs -------------------------------------------------------------------------------- /real/bspt/Render.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Render.lhs -------------------------------------------------------------------------------- /real/bspt/Stdlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/Stdlib.lhs -------------------------------------------------------------------------------- /real/bspt/bspt.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/bspt.faststdout -------------------------------------------------------------------------------- /real/bspt/bspt.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/bspt.slowstdout -------------------------------------------------------------------------------- /real/bspt/bspt.stdin: -------------------------------------------------------------------------------- 1 | batch 2 | -------------------------------------------------------------------------------- /real/bspt/bspt.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/bspt/bspt.stdout -------------------------------------------------------------------------------- /real/cacheprof/Arch_x86.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/cacheprof/Arch_x86.hs -------------------------------------------------------------------------------- /real/cacheprof/Generics.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/cacheprof/Generics.hs -------------------------------------------------------------------------------- /real/cacheprof/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/cacheprof/Main.hs -------------------------------------------------------------------------------- /real/cacheprof/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/cacheprof/Makefile -------------------------------------------------------------------------------- /real/compress/BinConv.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/BinConv.hs -------------------------------------------------------------------------------- /real/compress/BinTest.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/BinTest.hs -------------------------------------------------------------------------------- /real/compress/Decode.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Decode.hs -------------------------------------------------------------------------------- /real/compress/Defaults.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Defaults.hs -------------------------------------------------------------------------------- /real/compress/Encode.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Encode.hs -------------------------------------------------------------------------------- /real/compress/Lzw.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Lzw.hs -------------------------------------------------------------------------------- /real/compress/Lzw.icl: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Lzw.icl -------------------------------------------------------------------------------- /real/compress/Lzw2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Lzw2.hs -------------------------------------------------------------------------------- /real/compress/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/MAIL -------------------------------------------------------------------------------- /real/compress/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Main.hs -------------------------------------------------------------------------------- /real/compress/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/Makefile -------------------------------------------------------------------------------- /real/compress/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/compress/PTTrees.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/PTTrees.hs -------------------------------------------------------------------------------- /real/compress/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/README.nofib -------------------------------------------------------------------------------- /real/compress/lzw.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress/lzw.c -------------------------------------------------------------------------------- /real/compress2/Encode.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress2/Encode.hs -------------------------------------------------------------------------------- /real/compress2/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress2/Main.hs -------------------------------------------------------------------------------- /real/compress2/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/compress2/Makefile -------------------------------------------------------------------------------- /real/compress2/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/eff/CS/CS.stdout: -------------------------------------------------------------------------------- 1 | CS 2 | -------------------------------------------------------------------------------- /real/eff/CS/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CS/EffBench.hs -------------------------------------------------------------------------------- /real/eff/CS/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CS/Main.hs -------------------------------------------------------------------------------- /real/eff/CS/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CS/Makefile -------------------------------------------------------------------------------- /real/eff/CSD/CSD.stdout: -------------------------------------------------------------------------------- 1 | CSD 2 | -------------------------------------------------------------------------------- /real/eff/CSD/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CSD/EffBench.hs -------------------------------------------------------------------------------- /real/eff/CSD/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CSD/Main.hs -------------------------------------------------------------------------------- /real/eff/CSD/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/CSD/Makefile -------------------------------------------------------------------------------- /real/eff/FS/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/FS/EffBench.hs -------------------------------------------------------------------------------- /real/eff/FS/FS.stdout: -------------------------------------------------------------------------------- 1 | FS 2 | -------------------------------------------------------------------------------- /real/eff/FS/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/FS/Main.hs -------------------------------------------------------------------------------- /real/eff/FS/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/FS/Makefile -------------------------------------------------------------------------------- /real/eff/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/Makefile -------------------------------------------------------------------------------- /real/eff/S/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/S/Main.hs -------------------------------------------------------------------------------- /real/eff/S/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/S/Makefile -------------------------------------------------------------------------------- /real/eff/S/S.stdout: -------------------------------------------------------------------------------- 1 | S 2 | -------------------------------------------------------------------------------- /real/eff/VS/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VS/EffBench.hs -------------------------------------------------------------------------------- /real/eff/VS/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VS/Main.hs -------------------------------------------------------------------------------- /real/eff/VS/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VS/Makefile -------------------------------------------------------------------------------- /real/eff/VS/VS.stdout: -------------------------------------------------------------------------------- 1 | VS 2 | -------------------------------------------------------------------------------- /real/eff/VSD/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSD/EffBench.hs -------------------------------------------------------------------------------- /real/eff/VSD/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSD/Main.hs -------------------------------------------------------------------------------- /real/eff/VSD/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSD/Makefile -------------------------------------------------------------------------------- /real/eff/VSD/VSD.stdout: -------------------------------------------------------------------------------- 1 | VSD 2 | -------------------------------------------------------------------------------- /real/eff/VSM/EffBench.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSM/EffBench.hs -------------------------------------------------------------------------------- /real/eff/VSM/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSM/Main.hs -------------------------------------------------------------------------------- /real/eff/VSM/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/eff/VSM/Makefile -------------------------------------------------------------------------------- /real/eff/VSM/VSM.stdout: -------------------------------------------------------------------------------- 1 | VSM 2 | -------------------------------------------------------------------------------- /real/fem/Basics.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Basics.hs -------------------------------------------------------------------------------- /real/fem/DB_interface.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/DB_interface.hs -------------------------------------------------------------------------------- /real/fem/Database.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Database.hs -------------------------------------------------------------------------------- /real/fem/Degrees.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Degrees.hs -------------------------------------------------------------------------------- /real/fem/Displacement.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Displacement.hs -------------------------------------------------------------------------------- /real/fem/Elemforce.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Elemforce.hs -------------------------------------------------------------------------------- /real/fem/Elemstif.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Elemstif.hs -------------------------------------------------------------------------------- /real/fem/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/MAIL -------------------------------------------------------------------------------- /real/fem/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Main.hs -------------------------------------------------------------------------------- /real/fem/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Makefile -------------------------------------------------------------------------------- /real/fem/Matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Matrix.hs -------------------------------------------------------------------------------- /real/fem/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/fem/Pre_assemble.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Pre_assemble.hs -------------------------------------------------------------------------------- /real/fem/PrintSource.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/PrintSource.hs -------------------------------------------------------------------------------- /real/fem/Printuvwforce.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Printuvwforce.hs -------------------------------------------------------------------------------- /real/fem/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/README -------------------------------------------------------------------------------- /real/fem/VBlldecomp.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/VBlldecomp.hs -------------------------------------------------------------------------------- /real/fem/VBmatrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/VBmatrix.hs -------------------------------------------------------------------------------- /real/fem/Vector.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/Vector.hs -------------------------------------------------------------------------------- /real/fem/data.0: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/data.0 -------------------------------------------------------------------------------- /real/fem/data.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/data.1 -------------------------------------------------------------------------------- /real/fem/data.2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/data.2 -------------------------------------------------------------------------------- /real/fem/data.3: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/data.3 -------------------------------------------------------------------------------- /real/fem/fem.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/fem.stdin -------------------------------------------------------------------------------- /real/fem/inC/FEM_MODEL_DATA: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /real/fem/inC/G.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/G.1 -------------------------------------------------------------------------------- /real/fem/inC/G.2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/G.2 -------------------------------------------------------------------------------- /real/fem/inC/G.3: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/G.3 -------------------------------------------------------------------------------- /real/fem/inC/G.4: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/G.4 -------------------------------------------------------------------------------- /real/fem/inC/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/README -------------------------------------------------------------------------------- /real/fem/inC/TIMING: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/TIMING -------------------------------------------------------------------------------- /real/fem/inC/bar_2d.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/bar_2d.c -------------------------------------------------------------------------------- /real/fem/inC/data: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/data -------------------------------------------------------------------------------- /real/fem/inC/data.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/data.1 -------------------------------------------------------------------------------- /real/fem/inC/data.2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/data.2 -------------------------------------------------------------------------------- /real/fem/inC/data.3: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/data.3 -------------------------------------------------------------------------------- /real/fem/inC/data.4: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/data.4 -------------------------------------------------------------------------------- /real/fem/inC/database: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/database -------------------------------------------------------------------------------- /real/fem/inC/fem.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/fem.c -------------------------------------------------------------------------------- /real/fem/inC/read_data.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/read_data.c -------------------------------------------------------------------------------- /real/fem/inC/run: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/run -------------------------------------------------------------------------------- /real/fem/inC/vblldecomp.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fem/inC/vblldecomp.c -------------------------------------------------------------------------------- /real/fluid/Asb_routs.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Asb_routs.hs -------------------------------------------------------------------------------- /real/fluid/C_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/C_matrix.hs -------------------------------------------------------------------------------- /real/fluid/Chl_decomp.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Chl_decomp.hs -------------------------------------------------------------------------------- /real/fluid/Chl_method.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Chl_method.hs -------------------------------------------------------------------------------- /real/fluid/Chl_routs.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Chl_routs.hs -------------------------------------------------------------------------------- /real/fluid/Defs.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Defs.hs -------------------------------------------------------------------------------- /real/fluid/Elefac.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Elefac.hs -------------------------------------------------------------------------------- /real/fluid/Input_proc.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Input_proc.hs -------------------------------------------------------------------------------- /real/fluid/Jcb_method.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Jcb_method.hs -------------------------------------------------------------------------------- /real/fluid/L_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/L_matrix.hs -------------------------------------------------------------------------------- /real/fluid/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Main.hs -------------------------------------------------------------------------------- /real/fluid/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Makefile -------------------------------------------------------------------------------- /real/fluid/Min_degree.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Min_degree.hs -------------------------------------------------------------------------------- /real/fluid/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/fluid/Norm.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Norm.hs -------------------------------------------------------------------------------- /real/fluid/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/README -------------------------------------------------------------------------------- /real/fluid/S_Array.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/S_Array.hs -------------------------------------------------------------------------------- /real/fluid/S_matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/S_matrix.hs -------------------------------------------------------------------------------- /real/fluid/TG_iter.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/TG_iter.hs -------------------------------------------------------------------------------- /real/fluid/Tol_cal.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/Tol_cal.hs -------------------------------------------------------------------------------- /real/fluid/chan.hed: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/chan.hed -------------------------------------------------------------------------------- /real/fluid/fluid.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/fluid.stdin -------------------------------------------------------------------------------- /real/fluid/res8: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fluid/res8 -------------------------------------------------------------------------------- /real/fulsom/Bah.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Bah.hs -------------------------------------------------------------------------------- /real/fulsom/Csg.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Csg.hs -------------------------------------------------------------------------------- /real/fulsom/Interval.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Interval.hs -------------------------------------------------------------------------------- /real/fulsom/Kolor.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Kolor.hs -------------------------------------------------------------------------------- /real/fulsom/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/MAIL -------------------------------------------------------------------------------- /real/fulsom/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Main.hs -------------------------------------------------------------------------------- /real/fulsom/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Makefile -------------------------------------------------------------------------------- /real/fulsom/Matrix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Matrix.hs -------------------------------------------------------------------------------- /real/fulsom/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/fulsom/Oct.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Oct.hs -------------------------------------------------------------------------------- /real/fulsom/Patchlevel.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Patchlevel.hs -------------------------------------------------------------------------------- /real/fulsom/Quad.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Quad.hs -------------------------------------------------------------------------------- /real/fulsom/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/README.nofib -------------------------------------------------------------------------------- /real/fulsom/Raster.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Raster.hs -------------------------------------------------------------------------------- /real/fulsom/Shapes.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Shapes.hs -------------------------------------------------------------------------------- /real/fulsom/Types.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Types.hs -------------------------------------------------------------------------------- /real/fulsom/Vector.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/Vector.hs -------------------------------------------------------------------------------- /real/fulsom/fulsom.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/fulsom/fulsom.stdout -------------------------------------------------------------------------------- /real/gamteb/Compton.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Compton.hs -------------------------------------------------------------------------------- /real/gamteb/Consts.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Consts.hs -------------------------------------------------------------------------------- /real/gamteb/Distance.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Distance.hs -------------------------------------------------------------------------------- /real/gamteb/GamtebMain.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/GamtebMain.hs -------------------------------------------------------------------------------- /real/gamteb/GamtebType.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/GamtebType.hs -------------------------------------------------------------------------------- /real/gamteb/InitTable.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/InitTable.hs -------------------------------------------------------------------------------- /real/gamteb/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Main.hs -------------------------------------------------------------------------------- /real/gamteb/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Makefile -------------------------------------------------------------------------------- /real/gamteb/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/gamteb/Output.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Output.hs -------------------------------------------------------------------------------- /real/gamteb/Pair.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Pair.hs -------------------------------------------------------------------------------- /real/gamteb/PhotoElec.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/PhotoElec.hs -------------------------------------------------------------------------------- /real/gamteb/RoulSplit.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/RoulSplit.hs -------------------------------------------------------------------------------- /real/gamteb/TransPort.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/TransPort.hs -------------------------------------------------------------------------------- /real/gamteb/Utils.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/Utils.hs -------------------------------------------------------------------------------- /real/gamteb/gamteb.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/gamteb.stdout -------------------------------------------------------------------------------- /real/gamteb/inLML/consts.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/inLML/consts.m -------------------------------------------------------------------------------- /real/gamteb/inLML/gamteb.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/inLML/gamteb.m -------------------------------------------------------------------------------- /real/gamteb/inLML/output.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/inLML/output.m -------------------------------------------------------------------------------- /real/gamteb/inLML/pair.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/inLML/pair.m -------------------------------------------------------------------------------- /real/gamteb/inLML/utils.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/inLML/utils.m -------------------------------------------------------------------------------- /real/gamteb/results/gm2048: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/gm2048 -------------------------------------------------------------------------------- /real/gamteb/results/gm4096: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/gm4096 -------------------------------------------------------------------------------- /real/gamteb/results/gm6000: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/gm6000 -------------------------------------------------------------------------------- /real/gamteb/results/gm7000: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/gm7000 -------------------------------------------------------------------------------- /real/gamteb/results/pm2048: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/pm2048 -------------------------------------------------------------------------------- /real/gamteb/results/pm4096: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/pm4096 -------------------------------------------------------------------------------- /real/gamteb/results/pm6000: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/pm6000 -------------------------------------------------------------------------------- /real/gamteb/results/pm7000: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gamteb/results/pm7000 -------------------------------------------------------------------------------- /real/gg/Activity.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Activity.hs -------------------------------------------------------------------------------- /real/gg/GRIP.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/GRIP.hs -------------------------------------------------------------------------------- /real/gg/Graph.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Graph.hs -------------------------------------------------------------------------------- /real/gg/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Main.hs -------------------------------------------------------------------------------- /real/gg/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Makefile -------------------------------------------------------------------------------- /real/gg/Msg.Header: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Msg.Header -------------------------------------------------------------------------------- /real/gg/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/gg/PSlib.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/PSlib.hs -------------------------------------------------------------------------------- /real/gg/Parse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Parse.hs -------------------------------------------------------------------------------- /real/gg/Pool.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Pool.hs -------------------------------------------------------------------------------- /real/gg/Report.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Report.tex -------------------------------------------------------------------------------- /real/gg/Spark.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/Spark.hs -------------------------------------------------------------------------------- /real/gg/StdLib.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/StdLib.hs -------------------------------------------------------------------------------- /real/gg/example/README.nofib: -------------------------------------------------------------------------------- 1 | This is an *actually useful* program from Iain Checkland at York. 2 | -------------------------------------------------------------------------------- /real/gg/example/Report.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/example/Report.tex -------------------------------------------------------------------------------- /real/gg/example/report: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/example/report -------------------------------------------------------------------------------- /real/gg/gg.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.1 -------------------------------------------------------------------------------- /real/gg/gg.faststdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.faststdin -------------------------------------------------------------------------------- /real/gg/gg.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.faststdout -------------------------------------------------------------------------------- /real/gg/gg.slowstdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.slowstdin -------------------------------------------------------------------------------- /real/gg/gg.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.slowstdout -------------------------------------------------------------------------------- /real/gg/gg.stderr: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /real/gg/gg.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.stdin -------------------------------------------------------------------------------- /real/gg/gg.stdin-2.Z: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.stdin-2.Z -------------------------------------------------------------------------------- /real/gg/gg.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/gg.stdout -------------------------------------------------------------------------------- /real/gg/report: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/gg/report -------------------------------------------------------------------------------- /real/grep/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/Main.lhs -------------------------------------------------------------------------------- /real/grep/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/Makefile -------------------------------------------------------------------------------- /real/grep/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/grep/Parsers.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/Parsers.hs -------------------------------------------------------------------------------- /real/grep/StringMatch.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/StringMatch.hs -------------------------------------------------------------------------------- /real/grep/grep.faststdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.faststdin -------------------------------------------------------------------------------- /real/grep/grep.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.faststdout -------------------------------------------------------------------------------- /real/grep/grep.slowstdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.slowstdin -------------------------------------------------------------------------------- /real/grep/grep.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.slowstdout -------------------------------------------------------------------------------- /real/grep/grep.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.stdin -------------------------------------------------------------------------------- /real/grep/grep.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/grep/grep.stdout -------------------------------------------------------------------------------- /real/hidden/Comparing.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Comparing.hs -------------------------------------------------------------------------------- /real/hidden/Cross.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Cross.hs -------------------------------------------------------------------------------- /real/hidden/EdgePlate.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/EdgePlate.hs -------------------------------------------------------------------------------- /real/hidden/Geometric.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Geometric.hs -------------------------------------------------------------------------------- /real/hidden/Hide.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Hide.hs -------------------------------------------------------------------------------- /real/hidden/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/MAIL -------------------------------------------------------------------------------- /real/hidden/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Main.hs -------------------------------------------------------------------------------- /real/hidden/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Makefile -------------------------------------------------------------------------------- /real/hidden/Matrices.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Matrices.hs -------------------------------------------------------------------------------- /real/hidden/Memo.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Memo.hs -------------------------------------------------------------------------------- /real/hidden/MyIO.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/MyIO.hs -------------------------------------------------------------------------------- /real/hidden/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/hidden/Numbers.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Numbers.hs -------------------------------------------------------------------------------- /real/hidden/Postscript.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Postscript.hs -------------------------------------------------------------------------------- /real/hidden/Preds.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Preds.hs -------------------------------------------------------------------------------- /real/hidden/Rotate.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Rotate.lhs -------------------------------------------------------------------------------- /real/hidden/Solve.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Solve.hs -------------------------------------------------------------------------------- /real/hidden/Vectors.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/Vectors.hs -------------------------------------------------------------------------------- /real/hidden/etc/nbpip.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/etc/nbpip.c -------------------------------------------------------------------------------- /real/hidden/hidden.stderr: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hidden/hidden.stderr -------------------------------------------------------------------------------- /real/hidden/hidden.stdin: -------------------------------------------------------------------------------- 1 | 2,10,3 2 | quit 3 | -------------------------------------------------------------------------------- /real/hpg/Config.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Config.lhs -------------------------------------------------------------------------------- /real/hpg/Env.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Env.lhs -------------------------------------------------------------------------------- /real/hpg/GenExp.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/GenExp.lhs -------------------------------------------------------------------------------- /real/hpg/GenType.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/GenType.lhs -------------------------------------------------------------------------------- /real/hpg/GenVal.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/GenVal.lhs -------------------------------------------------------------------------------- /real/hpg/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/MAIL -------------------------------------------------------------------------------- /real/hpg/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Main.lhs -------------------------------------------------------------------------------- /real/hpg/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Makefile -------------------------------------------------------------------------------- /real/hpg/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/hpg/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/README.nofib -------------------------------------------------------------------------------- /real/hpg/Types.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Types.lhs -------------------------------------------------------------------------------- /real/hpg/Utils.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/Utils.lhs -------------------------------------------------------------------------------- /real/hpg/hpg.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/hpg.1 -------------------------------------------------------------------------------- /real/hpg/hpg.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/hpg.faststdout -------------------------------------------------------------------------------- /real/hpg/hpg.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/hpg.slowstdout -------------------------------------------------------------------------------- /real/hpg/hpg.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/hpg.stdout -------------------------------------------------------------------------------- /real/hpg/hpg.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/hpg.tex -------------------------------------------------------------------------------- /real/hpg/intro.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/intro.tex -------------------------------------------------------------------------------- /real/hpg/outro.tex: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/hpg/outro.tex -------------------------------------------------------------------------------- /real/infer/Environment.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Environment.hs -------------------------------------------------------------------------------- /real/infer/FiniteMap.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/FiniteMap.hs -------------------------------------------------------------------------------- /real/infer/Infer.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Infer.hs -------------------------------------------------------------------------------- /real/infer/InferMonad.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/InferMonad.hs -------------------------------------------------------------------------------- /real/infer/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Main.hs -------------------------------------------------------------------------------- /real/infer/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Makefile -------------------------------------------------------------------------------- /real/infer/MaybeM.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/MaybeM.hs -------------------------------------------------------------------------------- /real/infer/MyList.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/MyList.hs -------------------------------------------------------------------------------- /real/infer/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/infer/Parse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Parse.hs -------------------------------------------------------------------------------- /real/infer/Shows.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Shows.hs -------------------------------------------------------------------------------- /real/infer/State.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/State.hs -------------------------------------------------------------------------------- /real/infer/StateX.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/StateX.hs -------------------------------------------------------------------------------- /real/infer/Substitution.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Substitution.hs -------------------------------------------------------------------------------- /real/infer/Term.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Term.hs -------------------------------------------------------------------------------- /real/infer/TestTerm.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/TestTerm.hs -------------------------------------------------------------------------------- /real/infer/TestType.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/TestType.hs -------------------------------------------------------------------------------- /real/infer/Type.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/Type.hs -------------------------------------------------------------------------------- /real/infer/infer.faststdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/infer.faststdin -------------------------------------------------------------------------------- /real/infer/infer.slowstdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/infer.slowstdin -------------------------------------------------------------------------------- /real/infer/infer.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/infer.stdin -------------------------------------------------------------------------------- /real/infer/infer.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/infer/infer.stdout -------------------------------------------------------------------------------- /real/lift/LambdaLift.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/LambdaLift.lhs -------------------------------------------------------------------------------- /real/lift/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/Main.lhs -------------------------------------------------------------------------------- /real/lift/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/Makefile -------------------------------------------------------------------------------- /real/lift/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/lift/Print.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/Print.lhs -------------------------------------------------------------------------------- /real/lift/Test.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/Test.hs -------------------------------------------------------------------------------- /real/lift/Utilities.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/Utilities.lhs -------------------------------------------------------------------------------- /real/lift/lift.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/lift.faststdout -------------------------------------------------------------------------------- /real/lift/lift.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/lift.slowstdout -------------------------------------------------------------------------------- /real/lift/lift.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/lift/lift.stdout -------------------------------------------------------------------------------- /real/linear/AbsCg.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/AbsCg.lhs -------------------------------------------------------------------------------- /real/linear/Absmatlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Absmatlib.lhs -------------------------------------------------------------------------------- /real/linear/Cg.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Cg.lhs -------------------------------------------------------------------------------- /real/linear/Input.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Input.lhs -------------------------------------------------------------------------------- /real/linear/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Main.lhs -------------------------------------------------------------------------------- /real/linear/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Makefile -------------------------------------------------------------------------------- /real/linear/Matlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Matlib.lhs -------------------------------------------------------------------------------- /real/linear/Matrix.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Matrix.lhs -------------------------------------------------------------------------------- /real/linear/Misc.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Misc.lhs -------------------------------------------------------------------------------- /real/linear/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/linear/Utils.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/Utils.lhs -------------------------------------------------------------------------------- /real/linear/linear.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/linear/linear.stdout -------------------------------------------------------------------------------- /real/maillist/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/maillist/Main.hs -------------------------------------------------------------------------------- /real/maillist/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/maillist/Makefile -------------------------------------------------------------------------------- /real/mkhprog/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/mkhprog/Main.lhs -------------------------------------------------------------------------------- /real/mkhprog/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/mkhprog/Makefile -------------------------------------------------------------------------------- /real/mkhprog/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/mkhprog/mkhprog.1: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/mkhprog/mkhprog.1 -------------------------------------------------------------------------------- /real/parser/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/parser/Main.hs -------------------------------------------------------------------------------- /real/parser/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/parser/Makefile -------------------------------------------------------------------------------- /real/parser/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/parser/parser.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/parser/parser.stdin -------------------------------------------------------------------------------- /real/parser/parser.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/parser/parser.stdout -------------------------------------------------------------------------------- /real/pic/ChargeDensity.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/ChargeDensity.hs -------------------------------------------------------------------------------- /real/pic/Consts.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Consts.hs -------------------------------------------------------------------------------- /real/pic/ElecField.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/ElecField.hs -------------------------------------------------------------------------------- /real/pic/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Main.hs -------------------------------------------------------------------------------- /real/pic/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Makefile -------------------------------------------------------------------------------- /real/pic/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/pic/Pic.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Pic.hs -------------------------------------------------------------------------------- /real/pic/PicType.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/PicType.hs -------------------------------------------------------------------------------- /real/pic/Potential.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Potential.hs -------------------------------------------------------------------------------- /real/pic/PushParticle.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/PushParticle.hs -------------------------------------------------------------------------------- /real/pic/Utils.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/Utils.hs -------------------------------------------------------------------------------- /real/pic/inId/doc.culler: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/inId/doc.culler -------------------------------------------------------------------------------- /real/pic/inId/doc.olaf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/inId/doc.olaf -------------------------------------------------------------------------------- /real/pic/inId/pic88.id: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/inId/pic88.id -------------------------------------------------------------------------------- /real/pic/inId/pic_cul.id: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/inId/pic_cul.id -------------------------------------------------------------------------------- /real/pic/inId/pic_olaf.id: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/pic/inId/pic_olaf.id -------------------------------------------------------------------------------- /real/prolog/Engine.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Engine.hs -------------------------------------------------------------------------------- /real/prolog/Examples: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Examples -------------------------------------------------------------------------------- /real/prolog/Interact.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Interact.hs -------------------------------------------------------------------------------- /real/prolog/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Main.hs -------------------------------------------------------------------------------- /real/prolog/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Makefile -------------------------------------------------------------------------------- /real/prolog/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/prolog/Parse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Parse.hs -------------------------------------------------------------------------------- /real/prolog/PrologData.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/PrologData.hs -------------------------------------------------------------------------------- /real/prolog/PureEngine.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/PureEngine.hs -------------------------------------------------------------------------------- /real/prolog/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/README.nofib -------------------------------------------------------------------------------- /real/prolog/StackEngine.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/StackEngine.hs -------------------------------------------------------------------------------- /real/prolog/Subst.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Subst.hs -------------------------------------------------------------------------------- /real/prolog/Version.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/Version.hs -------------------------------------------------------------------------------- /real/prolog/prolog.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/prolog.stdin -------------------------------------------------------------------------------- /real/prolog/prolog.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/prolog/prolog.stdout -------------------------------------------------------------------------------- /real/reptile/ALT_output: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/ALT_output -------------------------------------------------------------------------------- /real/reptile/Diff.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Diff.hs -------------------------------------------------------------------------------- /real/reptile/Drawfuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Drawfuns.hs -------------------------------------------------------------------------------- /real/reptile/Geomfuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Geomfuns.hs -------------------------------------------------------------------------------- /real/reptile/Help.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Help.hs -------------------------------------------------------------------------------- /real/reptile/Interstate.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Interstate.hs -------------------------------------------------------------------------------- /real/reptile/Layout.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Layout.hs -------------------------------------------------------------------------------- /real/reptile/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/MAIL -------------------------------------------------------------------------------- /real/reptile/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Main.hs -------------------------------------------------------------------------------- /real/reptile/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Makefile -------------------------------------------------------------------------------- /real/reptile/Mgrfuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Mgrfuns.hs -------------------------------------------------------------------------------- /real/reptile/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/reptile/Progfuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Progfuns.hs -------------------------------------------------------------------------------- /real/reptile/Psfuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Psfuns.hs -------------------------------------------------------------------------------- /real/reptile/Rational.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Rational.hs -------------------------------------------------------------------------------- /real/reptile/Tilefuns.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/Tilefuns.hs -------------------------------------------------------------------------------- /real/reptile/ghc_output: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/ghc_output -------------------------------------------------------------------------------- /real/reptile/hbc_output: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/hbc_output -------------------------------------------------------------------------------- /real/reptile/reptile.faststdin: -------------------------------------------------------------------------------- 1 | K.V043Q02S0a . -------------------------------------------------------------------------------- /real/reptile/reptile.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/reptile.stdin -------------------------------------------------------------------------------- /real/reptile/york_output: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/reptile/york_output -------------------------------------------------------------------------------- /real/rsa/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/Main.hs -------------------------------------------------------------------------------- /real/rsa/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/Makefile -------------------------------------------------------------------------------- /real/rsa/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/rsa/Rsa.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/Rsa.hs -------------------------------------------------------------------------------- /real/rsa/rsa.faststdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.faststdin -------------------------------------------------------------------------------- /real/rsa/rsa.faststdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.faststdout -------------------------------------------------------------------------------- /real/rsa/rsa.slowstdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.slowstdin -------------------------------------------------------------------------------- /real/rsa/rsa.slowstdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.slowstdout -------------------------------------------------------------------------------- /real/rsa/rsa.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.stdin -------------------------------------------------------------------------------- /real/rsa/rsa.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/rsa/rsa.stdout -------------------------------------------------------------------------------- /real/scs/LinearAlgebra.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/LinearAlgebra.hs -------------------------------------------------------------------------------- /real/scs/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/Main.hs -------------------------------------------------------------------------------- /real/scs/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/Makefile -------------------------------------------------------------------------------- /real/scs/Parse.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/Parse.hs -------------------------------------------------------------------------------- /real/scs/ParseLib.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/ParseLib.hs -------------------------------------------------------------------------------- /real/scs/RandomFix.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/RandomFix.hs -------------------------------------------------------------------------------- /real/scs/Simulate.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/Simulate.hs -------------------------------------------------------------------------------- /real/scs/Types.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/scs/Types.hs -------------------------------------------------------------------------------- /real/scs/scs.stdout: -------------------------------------------------------------------------------- 1 | "Done" 2 | -------------------------------------------------------------------------------- /real/symalg/Ast.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Ast.hs -------------------------------------------------------------------------------- /real/symalg/BasicNumber.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/BasicNumber.hs -------------------------------------------------------------------------------- /real/symalg/Env.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Env.hs -------------------------------------------------------------------------------- /real/symalg/Eval.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Eval.hs -------------------------------------------------------------------------------- /real/symalg/Lexer.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Lexer.hs -------------------------------------------------------------------------------- /real/symalg/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Main.hs -------------------------------------------------------------------------------- /real/symalg/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Makefile -------------------------------------------------------------------------------- /real/symalg/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/symalg/Op.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Op.hs -------------------------------------------------------------------------------- /real/symalg/Parser.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Parser.hs -------------------------------------------------------------------------------- /real/symalg/Print.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/Print.hs -------------------------------------------------------------------------------- /real/symalg/RealM.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/RealM.hs -------------------------------------------------------------------------------- /real/symalg/symalg.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/symalg.stdin -------------------------------------------------------------------------------- /real/symalg/symalg.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/symalg/symalg.stdout -------------------------------------------------------------------------------- /real/veritas/Auto.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Auto.hs -------------------------------------------------------------------------------- /real/veritas/Build_Tm.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Build_Tm.lhs -------------------------------------------------------------------------------- /real/veritas/Dcore.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Dcore.hs -------------------------------------------------------------------------------- /real/veritas/Display.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Display.hs -------------------------------------------------------------------------------- /real/veritas/Editor.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Editor.hs -------------------------------------------------------------------------------- /real/veritas/Edlib.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Edlib.lhs -------------------------------------------------------------------------------- /real/veritas/Getops.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Getops.hs -------------------------------------------------------------------------------- /real/veritas/Globals.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Globals.hs -------------------------------------------------------------------------------- /real/veritas/Goals.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Goals.hs -------------------------------------------------------------------------------- /real/veritas/Kernel.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Kernel.hs -------------------------------------------------------------------------------- /real/veritas/Lookup.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Lookup.hs -------------------------------------------------------------------------------- /real/veritas/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Main.hs -------------------------------------------------------------------------------- /real/veritas/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Makefile -------------------------------------------------------------------------------- /real/veritas/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /real/veritas/Parse.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Parse.lhs -------------------------------------------------------------------------------- /real/veritas/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/README -------------------------------------------------------------------------------- /real/veritas/Sub_Core1.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Sub_Core1.hs -------------------------------------------------------------------------------- /real/veritas/Sub_Core2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Sub_Core2.hs -------------------------------------------------------------------------------- /real/veritas/Sub_Core3.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Sub_Core3.hs -------------------------------------------------------------------------------- /real/veritas/Sub_Core4.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Sub_Core4.hs -------------------------------------------------------------------------------- /real/veritas/Tacticals.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Tacticals.hs -------------------------------------------------------------------------------- /real/veritas/Tactics.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Tactics.hs -------------------------------------------------------------------------------- /real/veritas/Tags.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Tags.hs -------------------------------------------------------------------------------- /real/veritas/ThmTactics.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/ThmTactics.hs -------------------------------------------------------------------------------- /real/veritas/Token.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Token.lhs -------------------------------------------------------------------------------- /real/veritas/Tree.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Tree.hs -------------------------------------------------------------------------------- /real/veritas/Type_defs.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Type_defs.lhs -------------------------------------------------------------------------------- /real/veritas/Unparse.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Unparse.lhs -------------------------------------------------------------------------------- /real/veritas/Vtslib.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/Vtslib.hs -------------------------------------------------------------------------------- /real/veritas/grip-in: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/grip-in -------------------------------------------------------------------------------- /real/veritas/veritas.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/real/veritas/veritas.stdin -------------------------------------------------------------------------------- /runstdtest/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/runstdtest/Makefile -------------------------------------------------------------------------------- /runstdtest/runstdtest.prl: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/runstdtest/runstdtest.prl -------------------------------------------------------------------------------- /shootout/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/Makefile -------------------------------------------------------------------------------- /shootout/README.md: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/README.md -------------------------------------------------------------------------------- /shootout/fannkuch-redux/fannkuch-redux.faststdout: -------------------------------------------------------------------------------- 1 | 73196 2 | Pfannkuchen(10) = 38 3 | -------------------------------------------------------------------------------- /shootout/fannkuch-redux/fannkuch-redux.stdout: -------------------------------------------------------------------------------- 1 | 556355 2 | Pfannkuchen(11) = 51 3 | -------------------------------------------------------------------------------- /shootout/fasta/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/fasta/Main.hs -------------------------------------------------------------------------------- /shootout/fasta/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/fasta/Makefile -------------------------------------------------------------------------------- /shootout/fasta/fasta-c.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/fasta/fasta-c.c -------------------------------------------------------------------------------- /shootout/n-body/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/n-body/Main.hs -------------------------------------------------------------------------------- /shootout/n-body/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/n-body/Makefile -------------------------------------------------------------------------------- /shootout/pidigits/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/pidigits/Main.hs -------------------------------------------------------------------------------- /shootout/pidigits/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/shootout/pidigits/Makefile -------------------------------------------------------------------------------- /shootout/spectral-norm/spectral-norm.faststdout: -------------------------------------------------------------------------------- 1 | 1.274224144 2 | -------------------------------------------------------------------------------- /shootout/spectral-norm/spectral-norm.stdout: -------------------------------------------------------------------------------- 1 | 1.274224153 2 | -------------------------------------------------------------------------------- /smp/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/Makefile -------------------------------------------------------------------------------- /smp/callback001/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback001/Main.hs -------------------------------------------------------------------------------- /smp/callback001/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback001/Makefile -------------------------------------------------------------------------------- /smp/callback001/cbits.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback001/cbits.c -------------------------------------------------------------------------------- /smp/callback001/cbits.h: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback001/cbits.h -------------------------------------------------------------------------------- /smp/callback002/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback002/Main.hs -------------------------------------------------------------------------------- /smp/callback002/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback002/Makefile -------------------------------------------------------------------------------- /smp/callback002/cbits.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback002/cbits.c -------------------------------------------------------------------------------- /smp/callback002/cbits.h: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/callback002/cbits.h -------------------------------------------------------------------------------- /smp/chan/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/chan/Makefile -------------------------------------------------------------------------------- /smp/chan/chan.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/chan/chan.hs -------------------------------------------------------------------------------- /smp/sieve/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/sieve/Makefile -------------------------------------------------------------------------------- /smp/sieve/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/sieve/README -------------------------------------------------------------------------------- /smp/sieve/sieve.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/sieve/sieve.hs -------------------------------------------------------------------------------- /smp/smpbench.sh: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/smpbench.sh -------------------------------------------------------------------------------- /smp/stm001/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/stm001/Makefile -------------------------------------------------------------------------------- /smp/stm001/StmTest.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/stm001/StmTest.hs -------------------------------------------------------------------------------- /smp/stm002/StmTest2.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/stm002/StmTest2.hs -------------------------------------------------------------------------------- /smp/systolic/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/systolic/Main.hs -------------------------------------------------------------------------------- /smp/tchan/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/tchan/Makefile -------------------------------------------------------------------------------- /smp/tchan/tchan.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/tchan/tchan.hs -------------------------------------------------------------------------------- /smp/threads001/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads001/Main.hs -------------------------------------------------------------------------------- /smp/threads001/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads001/Makefile -------------------------------------------------------------------------------- /smp/threads001/threads001.stdout: -------------------------------------------------------------------------------- 1 | done -------------------------------------------------------------------------------- /smp/threads002/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads002/Main.hs -------------------------------------------------------------------------------- /smp/threads002/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads002/Makefile -------------------------------------------------------------------------------- /smp/threads003/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads003/Main.hs -------------------------------------------------------------------------------- /smp/threads003/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads003/Makefile -------------------------------------------------------------------------------- /smp/threads004/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads004/Main.hs -------------------------------------------------------------------------------- /smp/threads004/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads004/Makefile -------------------------------------------------------------------------------- /smp/threads005/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads005/Main.hs -------------------------------------------------------------------------------- /smp/threads006/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads006/Main.hs -------------------------------------------------------------------------------- /smp/threads006/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads006/Makefile -------------------------------------------------------------------------------- /smp/threads007/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads007/Main.hs -------------------------------------------------------------------------------- /smp/threads007/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/smp/threads007/Makefile -------------------------------------------------------------------------------- /spectral/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/Makefile -------------------------------------------------------------------------------- /spectral/ansi/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/ansi/Main.hs -------------------------------------------------------------------------------- /spectral/ansi/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/ansi/Makefile -------------------------------------------------------------------------------- /spectral/ansi/ansi.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/ansi/ansi.stdout -------------------------------------------------------------------------------- /spectral/ansi/blub: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/ansi/blub -------------------------------------------------------------------------------- /spectral/atom/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/atom/Main.hs -------------------------------------------------------------------------------- /spectral/atom/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/atom/Makefile -------------------------------------------------------------------------------- /spectral/atom/atom.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/atom/atom.stdout -------------------------------------------------------------------------------- /spectral/awards/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/awards/Main.hs -------------------------------------------------------------------------------- /spectral/awards/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/awards/Makefile -------------------------------------------------------------------------------- /spectral/awards/QSort.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/awards/QSort.hs -------------------------------------------------------------------------------- /spectral/banner/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/banner/Main.hs -------------------------------------------------------------------------------- /spectral/banner/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/banner/Makefile -------------------------------------------------------------------------------- /spectral/banner/banner.stdin.template: -------------------------------------------------------------------------------- 1 | Hello. 2 | Is this not a great banner? 3 | -------------------------------------------------------------------------------- /spectral/boyer/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer/Main.lhs -------------------------------------------------------------------------------- /spectral/boyer/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer/Makefile -------------------------------------------------------------------------------- /spectral/boyer2/Checker.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer2/Checker.hs -------------------------------------------------------------------------------- /spectral/boyer2/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer2/Main.hs -------------------------------------------------------------------------------- /spectral/boyer2/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer2/Makefile -------------------------------------------------------------------------------- /spectral/boyer2/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/boyer2/README -------------------------------------------------------------------------------- /spectral/calendar/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/calendar/Main.hs -------------------------------------------------------------------------------- /spectral/calendar/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/calendar/Makefile -------------------------------------------------------------------------------- /spectral/cichelli/Auxil.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cichelli/Auxil.hs -------------------------------------------------------------------------------- /spectral/cichelli/Key.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cichelli/Key.lhs -------------------------------------------------------------------------------- /spectral/cichelli/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cichelli/Main.hs -------------------------------------------------------------------------------- /spectral/cichelli/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cichelli/Makefile -------------------------------------------------------------------------------- /spectral/cichelli/Prog.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cichelli/Prog.hs -------------------------------------------------------------------------------- /spectral/circsim/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/circsim/Main.lhs -------------------------------------------------------------------------------- /spectral/circsim/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/circsim/Makefile -------------------------------------------------------------------------------- /spectral/clausify/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/clausify/Main.hs -------------------------------------------------------------------------------- /spectral/clausify/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/clausify/Makefile -------------------------------------------------------------------------------- /spectral/cryptarithm1/cryptarithm1.faststdout: -------------------------------------------------------------------------------- 1 | [[1,9,4,2,5,3,0,7,6,8]] 2 | -------------------------------------------------------------------------------- /spectral/cse/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cse/Main.hs -------------------------------------------------------------------------------- /spectral/cse/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cse/Makefile -------------------------------------------------------------------------------- /spectral/cse/StateMonad.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/cse/StateMonad.hs -------------------------------------------------------------------------------- /spectral/cse/cse.faststdout: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /spectral/cse/cse.slowstdout: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /spectral/cse/cse.stdout: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /spectral/dom-lt/Dom.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/dom-lt/Dom.hs -------------------------------------------------------------------------------- /spectral/dom-lt/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/dom-lt/Main.hs -------------------------------------------------------------------------------- /spectral/dom-lt/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/dom-lt/Makefile -------------------------------------------------------------------------------- /spectral/dom-lt/dom-lt.faststdout: -------------------------------------------------------------------------------- 1 | 133008 2 | -------------------------------------------------------------------------------- /spectral/dom-lt/dom-lt.slowstdout: -------------------------------------------------------------------------------- 1 | 83076683 2 | -------------------------------------------------------------------------------- /spectral/dom-lt/dom-lt.stdout: -------------------------------------------------------------------------------- 1 | 2238783 2 | -------------------------------------------------------------------------------- /spectral/eliza/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/eliza/Main.hs -------------------------------------------------------------------------------- /spectral/eliza/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/eliza/Makefile -------------------------------------------------------------------------------- /spectral/eliza/eliza.stdin: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/eliza/eliza.stdin -------------------------------------------------------------------------------- /spectral/expert/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Main.hs -------------------------------------------------------------------------------- /spectral/expert/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Makefile -------------------------------------------------------------------------------- /spectral/expert/Match.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Match.hs -------------------------------------------------------------------------------- /spectral/expert/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/README -------------------------------------------------------------------------------- /spectral/expert/Result.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Result.hs -------------------------------------------------------------------------------- /spectral/expert/Search.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Search.hs -------------------------------------------------------------------------------- /spectral/expert/Table.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/expert/Table.hs -------------------------------------------------------------------------------- /spectral/fft2/Fourier.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/Fourier.lhs -------------------------------------------------------------------------------- /spectral/fft2/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/MAIL -------------------------------------------------------------------------------- /spectral/fft2/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/Main.lhs -------------------------------------------------------------------------------- /spectral/fft2/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/Makefile -------------------------------------------------------------------------------- /spectral/fft2/README.nofib: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/README.nofib -------------------------------------------------------------------------------- /spectral/fft2/fft.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/fft.c -------------------------------------------------------------------------------- /spectral/fft2/fft2.stdout: -------------------------------------------------------------------------------- 1 | -------------------------------------------------------------------------------- /spectral/fft2/fourier.f: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/fourier.f -------------------------------------------------------------------------------- /spectral/fft2/fourier.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/fourier.m -------------------------------------------------------------------------------- /spectral/fft2/old/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fft2/old/Makefile -------------------------------------------------------------------------------- /spectral/fibheaps/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fibheaps/Main.lhs -------------------------------------------------------------------------------- /spectral/fibheaps/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fibheaps/Makefile -------------------------------------------------------------------------------- /spectral/fibheaps/orig: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fibheaps/orig -------------------------------------------------------------------------------- /spectral/fish/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fish/Main.hs -------------------------------------------------------------------------------- /spectral/fish/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/fish/Makefile -------------------------------------------------------------------------------- /spectral/gcd/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/gcd/Main.hs -------------------------------------------------------------------------------- /spectral/gcd/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/gcd/Makefile -------------------------------------------------------------------------------- /spectral/gcd/gcd.faststdout: -------------------------------------------------------------------------------- 1 | 5201 2 | -------------------------------------------------------------------------------- /spectral/gcd/gcd.slowstdout: -------------------------------------------------------------------------------- 1 | 6351 2 | -------------------------------------------------------------------------------- /spectral/gcd/gcd.stdout: -------------------------------------------------------------------------------- 1 | 5601 2 | -------------------------------------------------------------------------------- /spectral/hartel/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/hartel/Makefile -------------------------------------------------------------------------------- /spectral/hartel/listcompr/listcompr.faststdout: -------------------------------------------------------------------------------- 1 | 1252000 2 | -------------------------------------------------------------------------------- /spectral/hartel/listcompr/listcompr.slowstdout: -------------------------------------------------------------------------------- 1 | 3323. -------------------------------------------------------------------------------- /spectral/hartel/listcompr/listcompr.stdout: -------------------------------------------------------------------------------- 1 | 12520000 2 | -------------------------------------------------------------------------------- /spectral/hartel/listcopy/listcopy.faststdout: -------------------------------------------------------------------------------- 1 | 1252000 2 | -------------------------------------------------------------------------------- /spectral/hartel/listcopy/listcopy.slowstdout: -------------------------------------------------------------------------------- 1 | 3323. -------------------------------------------------------------------------------- /spectral/hartel/listcopy/listcopy.stdout: -------------------------------------------------------------------------------- 1 | 12520000 2 | -------------------------------------------------------------------------------- /spectral/hartel/transform/transform.faststdout: -------------------------------------------------------------------------------- 1 | 1061680 2 | -------------------------------------------------------------------------------- /spectral/hartel/transform/transform.slowstdout: -------------------------------------------------------------------------------- 1 | 53015625 2 | -------------------------------------------------------------------------------- /spectral/hartel/transform/transform.stdout: -------------------------------------------------------------------------------- 1 | 10603125 2 | -------------------------------------------------------------------------------- /spectral/hartel/typecheck/typecheck.faststdout: -------------------------------------------------------------------------------- 1 | 7261000/119500 2 | -------------------------------------------------------------------------------- /spectral/integer/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/integer/Main.hs -------------------------------------------------------------------------------- /spectral/integer/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/integer/Makefile -------------------------------------------------------------------------------- /spectral/knights/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/Main.lhs -------------------------------------------------------------------------------- /spectral/knights/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/Makefile -------------------------------------------------------------------------------- /spectral/knights/Queue.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/Queue.lhs -------------------------------------------------------------------------------- /spectral/knights/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/README -------------------------------------------------------------------------------- /spectral/knights/Sort.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/Sort.lhs -------------------------------------------------------------------------------- /spectral/knights/root.lit: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/knights/root.lit -------------------------------------------------------------------------------- /spectral/lambda/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/lambda/Main.hs -------------------------------------------------------------------------------- /spectral/lambda/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/lambda/Makefile -------------------------------------------------------------------------------- /spectral/lcss/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/lcss/Main.hs -------------------------------------------------------------------------------- /spectral/lcss/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/lcss/Makefile -------------------------------------------------------------------------------- /spectral/lcss/lcss.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/lcss/lcss.stdout -------------------------------------------------------------------------------- /spectral/life/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/life/Main.hs -------------------------------------------------------------------------------- /spectral/life/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/life/Makefile -------------------------------------------------------------------------------- /spectral/life/life.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/life/life.stdout -------------------------------------------------------------------------------- /spectral/life/life.test: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/life/life.test -------------------------------------------------------------------------------- /spectral/mandel/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel/MAIL -------------------------------------------------------------------------------- /spectral/mandel/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel/Main.hs -------------------------------------------------------------------------------- /spectral/mandel/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel/Makefile -------------------------------------------------------------------------------- /spectral/mandel/Mandel.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel/Mandel.lhs -------------------------------------------------------------------------------- /spectral/mandel/root.lit: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel/root.lit -------------------------------------------------------------------------------- /spectral/mandel2/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel2/Main.hs -------------------------------------------------------------------------------- /spectral/mandel2/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mandel2/Makefile -------------------------------------------------------------------------------- /spectral/mate/Board.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Board.hs -------------------------------------------------------------------------------- /spectral/mate/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Main.hs -------------------------------------------------------------------------------- /spectral/mate/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Makefile -------------------------------------------------------------------------------- /spectral/mate/Move.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Move.hs -------------------------------------------------------------------------------- /spectral/mate/Problem.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Problem.hs -------------------------------------------------------------------------------- /spectral/mate/README: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/README -------------------------------------------------------------------------------- /spectral/mate/Solution.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/Solution.hs -------------------------------------------------------------------------------- /spectral/mate/mate.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/mate/mate.stdout -------------------------------------------------------------------------------- /spectral/minimax/Board.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Board.hs -------------------------------------------------------------------------------- /spectral/minimax/Game.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Game.hs -------------------------------------------------------------------------------- /spectral/minimax/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Main.hs -------------------------------------------------------------------------------- /spectral/minimax/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Makefile -------------------------------------------------------------------------------- /spectral/minimax/Prog.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Prog.hs -------------------------------------------------------------------------------- /spectral/minimax/Tree.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Tree.hs -------------------------------------------------------------------------------- /spectral/minimax/Wins.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/minimax/Wins.hs -------------------------------------------------------------------------------- /spectral/para/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/Main.lhs -------------------------------------------------------------------------------- /spectral/para/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/Makefile -------------------------------------------------------------------------------- /spectral/para/c++/Para.C: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Para.C -------------------------------------------------------------------------------- /spectral/para/c++/Para.h: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Para.h -------------------------------------------------------------------------------- /spectral/para/c++/Part2.C: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Part2.C -------------------------------------------------------------------------------- /spectral/para/c++/Queue.C: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Queue.C -------------------------------------------------------------------------------- /spectral/para/c++/Queue.h: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Queue.h -------------------------------------------------------------------------------- /spectral/para/c++/Thin.C: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Thin.C -------------------------------------------------------------------------------- /spectral/para/c++/Thin.h: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/Thin.h -------------------------------------------------------------------------------- /spectral/para/c++/cout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/cout -------------------------------------------------------------------------------- /spectral/para/c++/crowd: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/crowd -------------------------------------------------------------------------------- /spectral/para/c++/part2: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/para/c++/part2 -------------------------------------------------------------------------------- /spectral/power/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/power/Main.hs -------------------------------------------------------------------------------- /spectral/power/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/power/Makefile -------------------------------------------------------------------------------- /spectral/pretty/CharSeq.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/pretty/CharSeq.hs -------------------------------------------------------------------------------- /spectral/pretty/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/pretty/Main.hs -------------------------------------------------------------------------------- /spectral/pretty/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/pretty/Makefile -------------------------------------------------------------------------------- /spectral/pretty/Pretty.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/pretty/Pretty.hs -------------------------------------------------------------------------------- /spectral/primetest/Readme: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/primetest/Readme -------------------------------------------------------------------------------- /spectral/puzzle/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/puzzle/Main.hs -------------------------------------------------------------------------------- /spectral/puzzle/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/puzzle/Makefile -------------------------------------------------------------------------------- /spectral/rewrite/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/rewrite/Main.lhs -------------------------------------------------------------------------------- /spectral/rewrite/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/rewrite/Makefile -------------------------------------------------------------------------------- /spectral/rewrite/rewrite.stdout: -------------------------------------------------------------------------------- 1 | True 2 | -------------------------------------------------------------------------------- /spectral/scc/Digraph.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/scc/Digraph.hs -------------------------------------------------------------------------------- /spectral/scc/Digraph.m: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/scc/Digraph.m -------------------------------------------------------------------------------- /spectral/scc/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/scc/Main.hs -------------------------------------------------------------------------------- /spectral/scc/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/scc/Makefile -------------------------------------------------------------------------------- /spectral/scc/scc.stdout: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/scc/scc.stdout -------------------------------------------------------------------------------- /spectral/simple/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/simple/MAIL -------------------------------------------------------------------------------- /spectral/simple/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/simple/Main.hs -------------------------------------------------------------------------------- /spectral/simple/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/simple/Makefile -------------------------------------------------------------------------------- /spectral/simple/simple.c: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/simple/simple.c -------------------------------------------------------------------------------- /spectral/simple/simple.f: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/simple/simple.f -------------------------------------------------------------------------------- /spectral/sorting/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/sorting/Main.hs -------------------------------------------------------------------------------- /spectral/sorting/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/sorting/Makefile -------------------------------------------------------------------------------- /spectral/sorting/NofibUtils.hs: -------------------------------------------------------------------------------- 1 | ../../common/NofibUtils.hs -------------------------------------------------------------------------------- /spectral/sorting/Sort.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/sorting/Sort.hs -------------------------------------------------------------------------------- /spectral/sphere/Main.lhs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/sphere/Main.lhs -------------------------------------------------------------------------------- /spectral/sphere/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/sphere/Makefile -------------------------------------------------------------------------------- /spectral/treejoin/MAIL: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/treejoin/MAIL -------------------------------------------------------------------------------- /spectral/treejoin/Main.hs: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/treejoin/Main.hs -------------------------------------------------------------------------------- /spectral/treejoin/Makefile: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/ghc/nofib/HEAD/spectral/treejoin/Makefile --------------------------------------------------------------------------------