haskell-te: 3a099d82da4395b16064646161d9a91a29d73647

     1: { bash, checkStderr, fail, gnugrep, gnused, haskellPackages, haveVar, jq,
     2:   makeWrapper, mkBin, nix, nixEnv, pipeToNix, runCommand, testData, timeout,
     3:   withDeps, withNix, wrap, writeScript }:
     4: 
     5: with builtins;
     6: with rec {
     7:   getCmd = wrap {
     8:     name   = "getCmd";
     9:     paths  = [
    10:       bash jq nix
    11:       (haskellPackages.ghcWithPackages (h: [ h.mlspec h.nix-eval ]))
    12:     ];
    13:     vars   = nixEnv // {
    14:       code = writeScript "getCmd.hs" ''
    15:         {-# LANGUAGE OverloadedStrings #-}
    16:         import           Data.Aeson
    17:         import qualified Data.ByteString.Lazy.Char8 as BS
    18:         import           MLSpec.Theory
    19:         import           Language.Eval.Internal
    20: 
    21:         render ts x = "main = do { eqs <- quickSpecAndSimplify (" ++
    22:                         withoutUndef' (renderWithVariables x ts)  ++
    23:                         "); mapM_ print eqs; }"
    24: 
    25:         -- Reads JSON from stdin, outputs a QuickSpec signature and associated
    26:         -- shell and Nix commands for running it
    27:         main = do
    28:           projects <- getProjects <$> getContents
    29:           let t = case projects of
    30:                        [t] -> t
    31:                        _   -> let l = show (length projects)
    32:                                in error ("Got " ++ l ++ " projects")
    33: 
    34:           rendered <- renderTheory t
    35:           let (ts, x) = case rendered of
    36:                              Just (ts, x) -> (ts, x)
    37:                              Nothing      -> let msg = "Failed to render "
    38:                                               in error (msg ++ show t)
    39: 
    40:           BS.putStrLn (encode (object [
    41:               "runner" .= unwords ("runhaskell" : flagsOf x),
    42:               "env"    .= pkgOf x,
    43:               "code"   .= buildInput (render ts) x
    44:             ]))
    45:       '';
    46:     };
    47:     script = ''
    48:       #!${bash}/bin/bash
    49:       jq 'map(select(.quickspecable))' | runhaskell "$code"
    50:     '';
    51:   };
    52: 
    53:   keepJson  = mkBin {
    54:     name   = "keepJson";
    55:     paths  = [ bash gnugrep jq ];
    56:     script = ''
    57:       #!${bash}/bin/bash
    58:       set -e
    59: 
    60:       # Strip out cruft that QuickSpec puts on stdout. Since this is just a
    61:       # filter, we don't actually care if grep finds anything or not; hence
    62:       # we use '|| true' to avoid signalling an error
    63:       function strip {
    64:         grep -v '^Depth' || true
    65:       }
    66: 
    67:       strip | jq -s '.'
    68:     '';
    69:   };
    70: 
    71:   runner = wrap {
    72:     name   = "quickspecRunner";
    73:     paths  = [ bash checkStderr haveVar keepJson timeout ];
    74:     vars   = { NIX_EVAL_HASKELL_PKGS = toString ./quickspecEnv.nix; };
    75:     script = ''
    76:       #!${bash}/bin/bash
    77:       set -e
    78:       set -o pipefail
    79: 
    80:       haveVar CMD
    81:       haveVar HASKELL_CODE
    82:       haveVar NIX_EVAL_HASKELL_PKGS
    83:       haveVar OUT_DIRS
    84: 
    85:       function run {
    86:         # Let users choose time/memory limits by wrapping in withTimout
    87:         withTimeout $CMD 2> >(checkStderr)
    88:       }
    89: 
    90:       run < "$HASKELL_CODE" | keepJson
    91:     '';
    92:   };
    93: 
    94:   generateCode = mkBin {
    95:     name   = "genQuickspecRunner";
    96:     paths  = [
    97:       (haskellPackages.ghcWithPackages (h: [ h.mlspec h.nix-eval ]))
    98:       fail haveVar jq nix pipeToNix
    99:     ];
   100:     vars   = nixEnv // {
   101:       inherit getCmd runner;
   102:       NIX_EVAL_HASKELL_PKGS = builtins.toString ./quickspecEnv.nix;
   103:       mkCmd = writeScript "quickspec-builder.nix" ''
   104:         with builtins;
   105:         assert getEnv "NIXENV"   != "" || abort "No NIXENV set";
   106:         assert getEnv "OUT_DIRS" != "" || abort "No OUT_DIRS set";
   107:         assert getEnv "CMD"      != "" || abort "No CMD set";
   108:         (import ${toString ./..} {}).wrap {
   109:           name  = "quickspec-runner";
   110:           paths = [ (import (toFile "env.nix" (getEnv "NIXENV"))) ];
   111:           vars  = {
   112:             CMD          = getEnv("CMD");
   113:             HASKELL_CODE = getEnv("HASKELL_CODE");
   114:             OUT_DIRS     = getEnv("OUT_DIRS");
   115:           };
   116:           file  = getEnv("runner");
   117:         }
   118:       '';
   119:     };
   120:     script = ''
   121:       #!${bash}/bin/bash
   122:       set -e
   123:       set -o pipefail
   124: 
   125:       haveVar OUT_DIRS
   126: 
   127:       ALL=$(cat)
   128:        QS=$(echo "$ALL" | jq 'map(select(.quickspecable))')
   129: 
   130:       function die {
   131:         echo -e "Given:\n$ALL\n" 1>&2
   132:         echo -e "Chosen:\n$QS\n" 1>&2
   133:         fail "$@"
   134:       }
   135: 
   136:       echo "$QS" | jq -e 'length | . > 0' > /dev/null ||
   137:         die "Nothing quickspecable"
   138: 
   139:       # Get the required environment, code and Haskell command
   140:       GENERATED=$(echo "$QS" | "$getCmd") ||
   141:         die "Couldn't generate QuickSpec code"
   142: 
   143:       [[ -n "$GENERATED" ]] || fail "Empty GENERATED"
   144: 
   145:       # Store code in a file since it may be too big for an env var
   146:       HASKELL_CODE=$(echo "$GENERATED" | jq -r '.code'  | pipeToNix "qsCode.hs")
   147:             NIXENV=$(echo "$GENERATED" | jq -r '.env'   )
   148:                CMD=$(echo "$GENERATED" | jq -r '.runner')
   149: 
   150:       export  HASKELL_CODE
   151:       haveVar HASKELL_CODE
   152:       export  NIXENV
   153:       haveVar NIXENV
   154:       export  CMD
   155:       haveVar CMD
   156: 
   157:       # Encapsulate the command and code into a standalone script
   158:       nix-build --no-out-link --show-trace -E 'import (builtins.getEnv "mkCmd")'
   159:     '';
   160:   };
   161: 
   162:   tests = rec {
   163:     runner = runCommand "test-theory-runner"
   164:       (withNix {
   165:         asts        = (testData.asts         {}).test-theory;
   166:         OUT_DIRS    = toJSON [(testData.haskellNixed {}).test-theory];
   167:         buildInputs = [ generateCode ];
   168:       })
   169:       ''
   170:         R=$(genQuickspecRunner < "$asts")
   171:         ln -s "$R" "$out"
   172:       '';
   173: 
   174:     env = runCommand "test-theory-env" { inherit runner; } ''
   175:       grep -v '^exec ' < "$runner" > "$out"
   176:     '';
   177: 
   178:     code = runCommand "code.hs"
   179:       {
   180:         inherit env;
   181:         buildInputs = [ fail ];
   182:       }
   183:       ''
   184:         source "$env"
   185:         [[ -e "$HASKELL_CODE" ]] || fail "HASKELL_CODE ($HASKELL_CODE) not found"
   186:         ln -s "$HASKELL_CODE" "$out"
   187:       '';
   188: 
   189:     countVars = with { ticks = "''"; }; writeScript "countVars.hs" ''
   190:       -- TODO: We don't need all of these
   191:       import Test.QuickSpec
   192:       import Test.QuickSpec.Signature
   193:       import Data.Digest.Murmur32
   194:       import Data.Serialize
   195:       import MLSpec.Helper
   196:       import A
   197:       import IfCxt
   198:       import Test.QuickCheck
   199:       import Test.RuntimeArbitrary
   200:       import Prelude
   201:       import GHC.Types
   202:       import qualified Test.Feat as F
   203: 
   204:       mkIfCxtInstances ${ticks}F.Enumerable
   205:       mkIfCxtInstances ${ticks}Ord
   206:       mkIfCxtInstances ${ticks}CoArbitrary
   207:       mkIfCxtInstances ${ticks}Arbitrary
   208: 
   209:       func1 = ("Unary",   Test.RuntimeArbitrary.getArbGen
   210:                             [Prelude.undefined :: ((->) Prelude.Integer
   211:                                                         Prelude.Integer)])
   212:       func2 = ("Binary",  Test.RuntimeArbitrary.getArbGen
   213:                             [Prelude.undefined :: ((->) Prelude.Integer
   214:                                                         ((->) Prelude.Integer
   215:                                                               Prelude.Integer))])
   216:       ints  = ("Integer", Test.RuntimeArbitrary.getArbGen
   217:                             [Prelude.undefined :: (Prelude.Integer)])
   218:       pairs = ("Pair",    Test.RuntimeArbitrary.getArbGen
   219:                             [Prelude.undefined :: ((A.Pair) Prelude.Integer)])
   220: 
   221:       check (t, l) = case l of
   222:         [] -> error ("No Arbitrary instance for " ++ t)
   223:         _  -> return ()
   224: 
   225:       main = sequence [
   226:           check ints
   227:         , check pairs
   228:         , check func1
   229:         , check func2
   230:         , putStrLn "Found Arbitrary instances"
   231:         ]
   232:     '';
   233: 
   234:     askForVariables = runCommand "ask-for-vars"
   235:       {
   236:         inherit code;
   237:         buildInputs = [ fail ];
   238:       }
   239:       ''
   240:         set -e
   241:         echo "Checking Haskell code requests vars for appropriate types" 1>&2
   242: 
   243:         # Find where we're adding variables to the signature and get their types
   244:         # This parsing is pretty fragile; if it breaks, it might be worth using
   245:         # haskell-src-exts or similar.
   246:         TYPES=$(grep -A 2 'MLSpec.Helper.addVars' < "$code" |
   247:                 grep 'getArbGen'                            |
   248:                 grep -o ':: .*\]'                           |
   249:                 grep -o ' .*[^]]'                           |
   250:                 grep -o '[^ ].*[^ ]'                        )
   251: 
   252:         for TYPE in Prelude.Integer '(A.Pair) Prelude.Integer'
   253:         do
   254:           echo "$TYPES" | grep -F "$TYPE" > /dev/null ||
   255:             fail "Didn't ask for variables of type '$TYPE'"
   256:         done
   257: 
   258:         echo "pass" > "$out"
   259:       '';
   260: 
   261:     haveGenerators = runCommand "have-generators"
   262:       {
   263:         inherit countVars env;
   264:         buildInputs = [ generateCode ];
   265:       }
   266:       ''
   267:         set -e
   268:         echo "Checking that we can find Arbitrary instances" 1>&2
   269:         source "$env"
   270:         $CMD < "$countVars"
   271:         echo "pass" > "$out"
   272:       '';
   273:   };
   274: };
   275: withDeps [ tests.askForVariables tests.haveGenerators ] generateCode

Generated by git2html.