{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}

-- | Facilities for reading Futhark test programs.  A Futhark test
-- program is an ordinary Futhark program where an initial comment
-- block specifies input- and output-sets.
module Futhark.Test
  ( module Futhark.Test.Spec,
    valuesFromByteString,
    FutharkExe (..),
    getValues,
    getValuesBS,
    valuesAsVars,
    V.compareValues,
    checkResult,
    testRunReferenceOutput,
    getExpectedResult,
    compileProgram,
    runProgram,
    readResults,
    ensureReferenceOutput,
    determineTuning,
    binaryName,
    futharkServerCfg,
    V.Mismatch,
    V.Value,
    V.valueText,
  )
where

import Codec.Compression.GZip
import Codec.Compression.Zlib.Internal (DecompressError)
import Control.Applicative
import Control.Exception (catch)
import qualified Control.Exception.Base as E
import Control.Monad
import Control.Monad.Except
import qualified Data.Binary as Bin
import qualified Data.ByteString as SBS
import qualified Data.ByteString.Lazy as BS
import Data.Char
import Data.Maybe
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import qualified Futhark.Script as Script
import Futhark.Server
import Futhark.Server.Values
import Futhark.Test.Spec
import qualified Futhark.Test.Values as V
import Futhark.Util (isEnvVarAtLeast, pmapIO)
import Futhark.Util.Pretty (prettyOneLine, prettyText, prettyTextOneLine)
import System.Directory
import System.Exit
import System.FilePath
import System.IO (IOMode (..), hClose, hFileSize, withFile)
import System.IO.Error
import System.IO.Temp
import System.Process.ByteString (readProcessWithExitCode)
import Prelude

-- | Try to parse a several values from a byte string.  The 'String'
-- parameter is used for error messages.
valuesFromByteString :: String -> BS.ByteString -> Either String [V.Value]
valuesFromByteString :: String -> ByteString -> Either String [Value]
valuesFromByteString String
srcname =
  Either String [Value]
-> ([Value] -> Either String [Value])
-> Maybe [Value]
-> Either String [Value]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String [Value]
forall a b. a -> Either a b
Left (String -> Either String [Value])
-> String -> Either String [Value]
forall a b. (a -> b) -> a -> b
$ String
"Cannot parse values from '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
srcname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'") [Value] -> Either String [Value]
forall a b. b -> Either a b
Right (Maybe [Value] -> Either String [Value])
-> (ByteString -> Maybe [Value])
-> ByteString
-> Either String [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe [Value]
V.readValues

-- | The @futhark@ executable we are using.  This is merely a wrapper
-- around the underlying file path, because we will be using a lot of
-- different file paths here, and it is easy to mix them up.
newtype FutharkExe = FutharkExe FilePath
  deriving (FutharkExe -> FutharkExe -> Bool
(FutharkExe -> FutharkExe -> Bool)
-> (FutharkExe -> FutharkExe -> Bool) -> Eq FutharkExe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FutharkExe -> FutharkExe -> Bool
$c/= :: FutharkExe -> FutharkExe -> Bool
== :: FutharkExe -> FutharkExe -> Bool
$c== :: FutharkExe -> FutharkExe -> Bool
Eq, Eq FutharkExe
Eq FutharkExe
-> (FutharkExe -> FutharkExe -> Ordering)
-> (FutharkExe -> FutharkExe -> Bool)
-> (FutharkExe -> FutharkExe -> Bool)
-> (FutharkExe -> FutharkExe -> Bool)
-> (FutharkExe -> FutharkExe -> Bool)
-> (FutharkExe -> FutharkExe -> FutharkExe)
-> (FutharkExe -> FutharkExe -> FutharkExe)
-> Ord FutharkExe
FutharkExe -> FutharkExe -> Bool
FutharkExe -> FutharkExe -> Ordering
FutharkExe -> FutharkExe -> FutharkExe
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FutharkExe -> FutharkExe -> FutharkExe
$cmin :: FutharkExe -> FutharkExe -> FutharkExe
max :: FutharkExe -> FutharkExe -> FutharkExe
$cmax :: FutharkExe -> FutharkExe -> FutharkExe
>= :: FutharkExe -> FutharkExe -> Bool
$c>= :: FutharkExe -> FutharkExe -> Bool
> :: FutharkExe -> FutharkExe -> Bool
$c> :: FutharkExe -> FutharkExe -> Bool
<= :: FutharkExe -> FutharkExe -> Bool
$c<= :: FutharkExe -> FutharkExe -> Bool
< :: FutharkExe -> FutharkExe -> Bool
$c< :: FutharkExe -> FutharkExe -> Bool
compare :: FutharkExe -> FutharkExe -> Ordering
$ccompare :: FutharkExe -> FutharkExe -> Ordering
$cp1Ord :: Eq FutharkExe
Ord, Int -> FutharkExe -> String -> String
[FutharkExe] -> String -> String
FutharkExe -> String
(Int -> FutharkExe -> String -> String)
-> (FutharkExe -> String)
-> ([FutharkExe] -> String -> String)
-> Show FutharkExe
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FutharkExe] -> String -> String
$cshowList :: [FutharkExe] -> String -> String
show :: FutharkExe -> String
$cshow :: FutharkExe -> String
showsPrec :: Int -> FutharkExe -> String -> String
$cshowsPrec :: Int -> FutharkExe -> String -> String
Show)

-- | Get the actual core Futhark values corresponding to a 'Values'
-- specification.  The first 'FilePath' is the path of the @futhark@
-- executable, and the second is the directory which file paths are
-- read relative to.
getValues :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m [V.Value]
getValues :: FutharkExe -> String -> Values -> m [Value]
getValues FutharkExe
_ String
_ (Values [Value]
vs) = [Value] -> m [Value]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Value]
vs
getValues FutharkExe
futhark String
dir Values
v = do
  ByteString
s <- FutharkExe -> String -> Values -> m ByteString
forall (m :: * -> *).
(MonadFail m, MonadIO m) =>
FutharkExe -> String -> Values -> m ByteString
getValuesBS FutharkExe
futhark String
dir Values
v
  case String -> ByteString -> Either String [Value]
valuesFromByteString (Values -> String
fileName Values
v) ByteString
s of
    Left String
e -> String -> m [Value]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
    Right [Value]
vs -> [Value] -> m [Value]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Value]
vs
  where
    fileName :: Values -> String
fileName Values {} = String
"<values>"
    fileName GenValues {} = String
"<randomly generated>"
    fileName ScriptValues {} = String
"<FutharkScript expression>"
    fileName (InFile String
f) = String
f
    fileName (ScriptFile String
f) = String
f

readAndDecompress :: FilePath -> IO (Either DecompressError BS.ByteString)
readAndDecompress :: String -> IO (Either DecompressError ByteString)
readAndDecompress String
file = IO ByteString -> IO (Either DecompressError ByteString)
forall e a. Exception e => IO a -> IO (Either e a)
E.try (IO ByteString -> IO (Either DecompressError ByteString))
-> IO ByteString -> IO (Either DecompressError ByteString)
forall a b. (a -> b) -> a -> b
$ do
  ByteString
s <- String -> IO ByteString
BS.readFile String
file
  ByteString -> IO ByteString
forall a. a -> IO a
E.evaluate (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
decompress ByteString
s

-- | Extract a pretty representation of some 'Values'.  In the IO
-- monad because this might involve reading from a file.  There is no
-- guarantee that the resulting byte string yields a readable value.
getValuesBS :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m BS.ByteString
getValuesBS :: FutharkExe -> String -> Values -> m ByteString
getValuesBS FutharkExe
_ String
_ (Values [Value]
vs) =
  ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BS.fromStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Value -> Text) -> [Value] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Value -> Text
V.valueText [Value]
vs
getValuesBS FutharkExe
_ String
dir (InFile String
file) =
  case String -> String
takeExtension String
file of
    String
".gz" -> IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
      Either DecompressError ByteString
s <- String -> IO (Either DecompressError ByteString)
readAndDecompress String
file'
      case Either DecompressError ByteString
s of
        Left DecompressError
e -> String -> IO ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ByteString) -> String -> IO ByteString
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. Show a => a -> String
show String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ DecompressError -> String
forall a. Show a => a -> String
show DecompressError
e
        Right ByteString
s' -> ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
s'
    String
_ -> IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
BS.readFile String
file'
  where
    file' :: String
file' = String
dir String -> String -> String
</> String
file
getValuesBS FutharkExe
futhark String
dir (GenValues [GenValue]
gens) =
  [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString) -> m [ByteString] -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GenValue -> m ByteString) -> [GenValue] -> m [ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FutharkExe -> String -> GenValue -> m ByteString
forall (m :: * -> *).
MonadIO m =>
FutharkExe -> String -> GenValue -> m ByteString
getGenBS FutharkExe
futhark String
dir) [GenValue]
gens
getValuesBS FutharkExe
_ String
_ (ScriptValues Exp
e) =
  String -> m ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ByteString) -> String -> m ByteString
forall a b. (a -> b) -> a -> b
$ String
"Cannot get values from FutharkScript expression: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Exp -> String
forall a. Pretty a => a -> String
prettyOneLine Exp
e
getValuesBS FutharkExe
_ String
_ (ScriptFile String
f) =
  String -> m ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ByteString) -> String -> m ByteString
forall a b. (a -> b) -> a -> b
$ String
"Cannot get values from FutharkScript file: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
f

valueAsVar ::
  (MonadError T.Text m, MonadIO m) =>
  Server ->
  VarName ->
  V.Value ->
  m ()
valueAsVar :: Server -> Text -> Value -> m ()
valueAsVar Server
server Text
v Value
val =
  IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ()) -> IO (Maybe CmdFailure) -> m ()
forall a b. (a -> b) -> a -> b
$ Server -> Text -> Value -> IO (Maybe CmdFailure)
putValue Server
server Text
v Value
val

-- Frees the expression on error.
scriptValueAsVars ::
  (MonadError T.Text m, MonadIO m) =>
  Server ->
  [(VarName, TypeName)] ->
  Script.ExpValue ->
  m ()
scriptValueAsVars :: Server -> [(Text, Text)] -> ExpValue -> m ()
scriptValueAsVars Server
server [(Text, Text)]
names_and_types ExpValue
val
  | [ExpValue]
vals <- ExpValue -> [ExpValue]
forall v. Compound v -> [Compound v]
V.unCompound ExpValue
val,
    [(Text, Text)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, Text)]
names_and_types Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [ExpValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpValue]
vals,
    Just [m ()]
loads <- ((Text, Text) -> ExpValue -> Maybe (m ()))
-> [(Text, Text)] -> [ExpValue] -> Maybe [m ()]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (Text, Text) -> ExpValue -> Maybe (m ())
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
(Text, Text) -> ExpValue -> Maybe (m ())
f [(Text, Text)]
names_and_types [ExpValue]
vals =
    [m ()] -> m ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [m ()]
loads
  where
    f :: (Text, Text) -> ExpValue -> Maybe (m ())
f (Text
v, Text
t0) (V.ValueAtom (Script.SValue Text
t1 ValOrVar
sval))
      | Text
t0 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
t1 =
        m () -> Maybe (m ())
forall a. a -> Maybe a
Just (m () -> Maybe (m ())) -> m () -> Maybe (m ())
forall a b. (a -> b) -> a -> b
$ case ValOrVar
sval of
          Script.VVar Text
oldname ->
            IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ()) -> IO (Maybe CmdFailure) -> m ()
forall a b. (a -> b) -> a -> b
$ Server -> Text -> Text -> IO (Maybe CmdFailure)
cmdRename Server
server Text
oldname Text
v
          Script.VVal Value
sval' ->
            Server -> Text -> Value -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
Server -> Text -> Value -> m ()
valueAsVar Server
server Text
v Value
sval'
    f (Text, Text)
_ ExpValue
_ = Maybe (m ())
forall a. Maybe a
Nothing
scriptValueAsVars Server
server [(Text, Text)]
names_and_types ExpValue
val = do
  IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ()) -> IO (Maybe CmdFailure) -> m ()
forall a b. (a -> b) -> a -> b
$ Server -> [Text] -> IO (Maybe CmdFailure)
cmdFree Server
server ([Text] -> IO (Maybe CmdFailure))
-> [Text] -> IO (Maybe CmdFailure)
forall a b. (a -> b) -> a -> b
$ Set Text -> [Text]
forall a. Set a -> [a]
S.toList (Set Text -> [Text]) -> Set Text -> [Text]
forall a b. (a -> b) -> a -> b
$ ExpValue -> Set Text
Script.serverVarsInValue ExpValue
val
  Text -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$
    Text
"Expected value of type: "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound Text -> Text
forall a. Pretty a => a -> Text
prettyTextOneLine ([Compound Text] -> Compound Text
forall v. [Compound v] -> Compound v
V.mkCompound (((Text, Text) -> Compound Text)
-> [(Text, Text)] -> [Compound Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Compound Text
forall v. v -> Compound v
V.ValueAtom (Text -> Compound Text)
-> ((Text, Text) -> Text) -> (Text, Text) -> Compound Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> b
snd) [(Text, Text)]
names_and_types))
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\nBut got value of type:  "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ScriptValueType -> Text
forall a. Pretty a => a -> Text
prettyTextOneLine ((ScriptValue ValOrVar -> ScriptValueType)
-> ExpValue -> Compound ScriptValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScriptValue ValOrVar -> ScriptValueType
forall v. ScriptValue v -> ScriptValueType
Script.scriptValueType ExpValue
val)
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
notes
  where
    notes :: Text
notes = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Maybe Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Text, Text) -> Maybe Text
forall a. (a, Text) -> Maybe Text
note [(Text, Text)]
names_and_types
    note :: (a, Text) -> Maybe Text
note (a
_, Text
t)
      | Text
"(" Text -> Text -> Bool
`T.isPrefixOf` Text
t =
        Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$
          Text
"\nNote: expected type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall a. Pretty a => a -> Text
prettyText Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is an opaque tuple that cannot be constructed\n"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in FutharkScript.  Consider using type annotations to give it a proper name."
      | Text
"{" Text -> Text -> Bool
`T.isPrefixOf` Text
t =
        Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$
          Text
"\nNote: expected type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall a. Pretty a => a -> Text
prettyText Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is an opaque record that cannot be constructed\n"
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in FutharkScript.  Consider using type annotations to give it a proper name."
      | Bool
otherwise =
        Maybe Text
forall a. Maybe a
Nothing

-- | Make the provided 'Values' available as server-side variables.
-- This may involve arbitrary server-side computation.  Error
-- detection... dubious.
valuesAsVars ::
  (MonadError T.Text m, MonadIO m) =>
  Server ->
  [(VarName, TypeName)] ->
  FutharkExe ->
  FilePath ->
  Values ->
  m ()
valuesAsVars :: Server -> [(Text, Text)] -> FutharkExe -> String -> Values -> m ()
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
_ String
dir (InFile String
file)
  | String -> String
takeExtension String
file String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
".gz" = do
    Either DecompressError ByteString
s <- IO (Either DecompressError ByteString)
-> m (Either DecompressError ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either DecompressError ByteString)
 -> m (Either DecompressError ByteString))
-> IO (Either DecompressError ByteString)
-> m (Either DecompressError ByteString)
forall a b. (a -> b) -> a -> b
$ String -> IO (Either DecompressError ByteString)
readAndDecompress (String -> IO (Either DecompressError ByteString))
-> String -> IO (Either DecompressError ByteString)
forall a b. (a -> b) -> a -> b
$ String
dir String -> String -> String
</> String
file
    case Either DecompressError ByteString
s of
      Left DecompressError
e ->
        Text -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. Show a => a -> String
show String
file String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> DecompressError -> String
forall a. Show a => a -> String
show DecompressError
e
      Right ByteString
s' ->
        IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ())
-> ((String -> Handle -> IO (Maybe CmdFailure))
    -> IO (Maybe CmdFailure))
-> (String -> Handle -> IO (Maybe CmdFailure))
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> (String -> Handle -> IO (Maybe CmdFailure))
-> IO (Maybe CmdFailure)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"futhark-input" ((String -> Handle -> IO (Maybe CmdFailure)) -> m ())
-> (String -> Handle -> IO (Maybe CmdFailure)) -> m ()
forall a b. (a -> b) -> a -> b
$ \String
tmpf Handle
tmpf_h -> do
          Handle -> ByteString -> IO ()
BS.hPutStr Handle
tmpf_h ByteString
s'
          Handle -> IO ()
hClose Handle
tmpf_h
          Server -> String -> [(Text, Text)] -> IO (Maybe CmdFailure)
cmdRestore Server
server String
tmpf [(Text, Text)]
names_and_types
  | Bool
otherwise =
    IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ()) -> IO (Maybe CmdFailure) -> m ()
forall a b. (a -> b) -> a -> b
$ Server -> String -> [(Text, Text)] -> IO (Maybe CmdFailure)
cmdRestore Server
server (String
dir String -> String -> String
</> String
file) [(Text, Text)]
names_and_types
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
futhark String
dir (GenValues [GenValue]
gens) = do
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([GenValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GenValue]
gens Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [(Text, Text)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, Text)]
names_and_types) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    Text -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError Text
"Mismatch between number of expected and generated values."
  [String]
gen_fs <- (GenValue -> m String) -> [GenValue] -> m [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FutharkExe -> String -> GenValue -> m String
forall (m :: * -> *).
MonadIO m =>
FutharkExe -> String -> GenValue -> m String
getGenFile FutharkExe
futhark String
dir) [GenValue]
gens
  [(String, (Text, Text))]
-> ((String, (Text, Text)) -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([String] -> [(Text, Text)] -> [(String, (Text, Text))]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
gen_fs [(Text, Text)]
names_and_types) (((String, (Text, Text)) -> m ()) -> m ())
-> ((String, (Text, Text)) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \(String
file, (Text
v, Text
t)) ->
    IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ()) -> IO (Maybe CmdFailure) -> m ()
forall a b. (a -> b) -> a -> b
$ Server -> String -> [(Text, Text)] -> IO (Maybe CmdFailure)
cmdRestore Server
server (String
dir String -> String -> String
</> String
file) [(Text
v, Text
t)]
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
_ String
_ (Values [Value]
vs) = do
  let types :: [Text]
types = ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text) -> Text
forall a b. (a, b) -> b
snd [(Text, Text)]
names_and_types
      vs_types :: [Text]
vs_types = (Value -> Text) -> [Value] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (ValueType -> Text
V.valueTypeTextNoDims (ValueType -> Text) -> (Value -> ValueType) -> Value -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ValueType
V.valueType) [Value]
vs
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Text]
types [Text] -> [Text] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text]
vs_types) (m () -> m ()) -> ([Text] -> m ()) -> [Text] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m ()) -> ([Text] -> Text) -> [Text] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> m ()) -> [Text] -> m ()
forall a b. (a -> b) -> a -> b
$
    [ Text
"Expected input of types: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
forall a. Pretty a => a -> Text
prettyTextOneLine [Text]
types,
      Text
"Provided input of types: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
forall a. Pretty a => a -> Text
prettyTextOneLine [Text]
vs_types
    ]
  IO (Maybe CmdFailure) -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
IO (Maybe CmdFailure) -> m ()
cmdMaybe (IO (Maybe CmdFailure) -> m ())
-> ((String -> Handle -> IO (Maybe CmdFailure))
    -> IO (Maybe CmdFailure))
-> (String -> Handle -> IO (Maybe CmdFailure))
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> (String -> Handle -> IO (Maybe CmdFailure))
-> IO (Maybe CmdFailure)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"futhark-input" ((String -> Handle -> IO (Maybe CmdFailure)) -> m ())
-> (String -> Handle -> IO (Maybe CmdFailure)) -> m ()
forall a b. (a -> b) -> a -> b
$ \String
tmpf Handle
tmpf_h -> do
    (Value -> IO ()) -> [Value] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> ByteString -> IO ()
BS.hPutStr Handle
tmpf_h (ByteString -> IO ()) -> (Value -> ByteString) -> Value -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ByteString
forall a. Binary a => a -> ByteString
Bin.encode) [Value]
vs
    Handle -> IO ()
hClose Handle
tmpf_h
    Server -> String -> [(Text, Text)] -> IO (Maybe CmdFailure)
cmdRestore Server
server String
tmpf [(Text, Text)]
names_and_types
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
_ String
_ (ScriptValues Exp
e) =
  Server -> (ScriptServer -> m ()) -> m ()
forall (m :: * -> *) a.
MonadIO m =>
Server -> (ScriptServer -> m a) -> m a
Script.withScriptServer' Server
server ((ScriptServer -> m ()) -> m ()) -> (ScriptServer -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ScriptServer
server' -> do
    ExpValue
e_v <- EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue
Script.evalExp EvalBuiltin m
forall e (m :: * -> *) p a.
(MonadError e m, Semigroup e, IsString e) =>
e -> p -> m a
noBuiltin ScriptServer
server' Exp
e
    Server -> [(Text, Text)] -> ExpValue -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
Server -> [(Text, Text)] -> ExpValue -> m ()
scriptValueAsVars Server
server [(Text, Text)]
names_and_types ExpValue
e_v
  where
    noBuiltin :: e -> p -> m a
noBuiltin e
f p
_ = do
      e -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (e -> m a) -> e -> m a
forall a b. (a -> b) -> a -> b
$ e
"Unknown builtin procedure: " e -> e -> e
forall a. Semigroup a => a -> a -> a
<> e
f
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
futhark String
dir (ScriptFile String
f) = do
  Exp
e <-
    (Text -> m Exp) -> (Exp -> m Exp) -> Either Text Exp -> m Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> m Exp
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError Exp -> m Exp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text Exp -> m Exp)
-> (Text -> Either Text Exp) -> Text -> m Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text -> Either Text Exp
Script.parseExpFromText String
f
      (Text -> m Exp) -> m Text -> m Exp
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO Text
T.readFile (String
dir String -> String -> String
</> String
f))
  Server -> [(Text, Text)] -> FutharkExe -> String -> Values -> m ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
Server -> [(Text, Text)] -> FutharkExe -> String -> Values -> m ()
valuesAsVars Server
server [(Text, Text)]
names_and_types FutharkExe
futhark String
dir (Exp -> Values
ScriptValues Exp
e)

-- | There is a risk of race conditions when multiple programs have
-- identical 'GenValues'.  In such cases, multiple threads in 'futhark
-- test' might attempt to create the same file (or read from it, while
-- something else is constructing it).  This leads to a mess.  To
-- avoid this, we create a temporary file, and only when it is
-- complete do we move it into place.  It would be better if we could
-- use file locking, but that does not work on some file systems.  The
-- approach here seems robust enough for now, but certainly it could
-- be made even better.  The race condition that remains should mostly
-- result in duplicate work, not crashes or data corruption.
getGenFile :: MonadIO m => FutharkExe -> FilePath -> GenValue -> m FilePath
getGenFile :: FutharkExe -> String -> GenValue -> m String
getGenFile FutharkExe
futhark String
dir GenValue
gen = do
  IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
dir String -> String -> String
</> String
"data"
  Bool
exists_and_proper_size <-
    IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$
      String -> IOMode -> (Handle -> IO Bool) -> IO Bool
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile (String
dir String -> String -> String
</> String
file) IOMode
ReadMode ((Integer -> Bool) -> IO Integer -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== GenValue -> Integer
genFileSize GenValue
gen) (IO Integer -> IO Bool)
-> (Handle -> IO Integer) -> Handle -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO Integer
hFileSize)
        IO Bool -> (IOError -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \IOError
ex ->
          if IOError -> Bool
isDoesNotExistError IOError
ex
            then Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
            else IOError -> IO Bool
forall a e. Exception e => e -> a
E.throw IOError
ex
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists_and_proper_size (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
      ByteString
s <- FutharkExe -> [GenValue] -> IO ByteString
genValues FutharkExe
futhark [GenValue
gen]
      String -> String -> (String -> Handle -> IO ()) -> IO ()
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> String -> (String -> Handle -> m a) -> m a
withTempFile (String
dir String -> String -> String
</> String
"data") (GenValue -> String
genFileName GenValue
gen) ((String -> Handle -> IO ()) -> IO ())
-> (String -> Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
tmpfile Handle
h -> do
        Handle -> IO ()
hClose Handle
h -- We will be writing and reading this ourselves.
        String -> ByteString -> IO ()
SBS.writeFile String
tmpfile ByteString
s
        String -> String -> IO ()
renameFile String
tmpfile (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
dir String -> String -> String
</> String
file
  String -> m String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
file
  where
    file :: String
file = String
"data" String -> String -> String
</> GenValue -> String
genFileName GenValue
gen

getGenBS :: MonadIO m => FutharkExe -> FilePath -> GenValue -> m BS.ByteString
getGenBS :: FutharkExe -> String -> GenValue -> m ByteString
getGenBS FutharkExe
futhark String
dir GenValue
gen = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString)
-> (String -> IO ByteString) -> String -> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ByteString
BS.readFile (String -> IO ByteString)
-> (String -> String) -> String -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
dir String -> String -> String
</>) (String -> m ByteString) -> m String -> m ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FutharkExe -> String -> GenValue -> m String
forall (m :: * -> *).
MonadIO m =>
FutharkExe -> String -> GenValue -> m String
getGenFile FutharkExe
futhark String
dir GenValue
gen

genValues :: FutharkExe -> [GenValue] -> IO SBS.ByteString
genValues :: FutharkExe -> [GenValue] -> IO ByteString
genValues (FutharkExe String
futhark) [GenValue]
gens = do
  (ExitCode
code, ByteString
stdout, ByteString
stderr) <- String
-> [String] -> ByteString -> IO (ExitCode, ByteString, ByteString)
readProcessWithExitCode String
futhark (String
"dataset" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
args) ByteString
forall a. Monoid a => a
mempty
  case ExitCode
code of
    ExitCode
ExitSuccess ->
      ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
stdout
    ExitFailure Int
e ->
      String -> IO ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ByteString) -> String -> IO ByteString
forall a b. (a -> b) -> a -> b
$
        String
"'futhark dataset' failed with exit code " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
e String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" and stderr:\n"
          String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Word8 -> Char) -> [Word8] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (ByteString -> [Word8]
SBS.unpack ByteString
stderr)
  where
    args :: [String]
args = String
"-b" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (GenValue -> [String]) -> [GenValue] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GenValue -> [String]
argForGen [GenValue]
gens
    argForGen :: GenValue -> [String]
argForGen GenValue
g = [String
"-g", GenValue -> String
genValueType GenValue
g]

genFileName :: GenValue -> FilePath
genFileName :: GenValue -> String
genFileName GenValue
gen = GenValue -> String
genValueType GenValue
gen String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".in"

-- | Compute the expected size of the file.  We use this to check
-- whether an existing file is broken/truncated.
genFileSize :: GenValue -> Integer
genFileSize :: GenValue -> Integer
genFileSize = GenValue -> Integer
genSize
  where
    header_size :: Int
header_size = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4 -- 'b' <version> <num_dims> <type>
    genSize :: GenValue -> Integer
genSize (GenValue (V.ValueType [Int]
ds PrimType
t)) =
      Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$
        Int
header_size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
ds Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8
          Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [Int]
ds Int -> Int -> Int
forall a. Num a => a -> a -> a
* PrimType -> Int
V.primTypeBytes PrimType
t
    genSize (GenPrim Value
v) =
      Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Int
header_size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product (Value -> [Int]
V.valueShape Value
v) Int -> Int -> Int
forall a. Num a => a -> a -> a
* PrimType -> Int
V.primTypeBytes (Value -> PrimType
V.valueElemType Value
v)

-- | When/if generating a reference output file for this run, what
-- should it be called?  Includes the "data/" folder.
testRunReferenceOutput :: FilePath -> T.Text -> TestRun -> FilePath
testRunReferenceOutput :: String -> Text -> TestRun -> String
testRunReferenceOutput String
prog Text
entry TestRun
tr =
  String
"data"
    String -> String -> String
</> String -> String
takeBaseName String
prog
    String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
":"
    String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
entry
    String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"-"
    String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
clean (TestRun -> String
runDescription TestRun
tr)
    String -> String -> String
<.> String
"out"
  where
    clean :: Char -> Char
clean Char
'/' = Char
'_' -- Would this ever happen?
    clean Char
' ' = Char
'_'
    clean Char
c = Char
c

-- | Get the values corresponding to an expected result, if any.
getExpectedResult ::
  (MonadFail m, MonadIO m) =>
  FutharkExe ->
  FilePath ->
  T.Text ->
  TestRun ->
  m (ExpectedResult [V.Value])
getExpectedResult :: FutharkExe
-> String -> Text -> TestRun -> m (ExpectedResult [Value])
getExpectedResult FutharkExe
futhark String
prog Text
entry TestRun
tr =
  case TestRun -> ExpectedResult Success
runExpectedResult TestRun
tr of
    (Succeeds (Just (SuccessValues Values
vals))) ->
      Maybe [Value] -> ExpectedResult [Value]
forall values. Maybe values -> ExpectedResult values
Succeeds (Maybe [Value] -> ExpectedResult [Value])
-> ([Value] -> Maybe [Value]) -> [Value] -> ExpectedResult [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Maybe [Value]
forall a. a -> Maybe a
Just ([Value] -> ExpectedResult [Value])
-> m [Value] -> m (ExpectedResult [Value])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FutharkExe -> String -> Values -> m [Value]
forall (m :: * -> *).
(MonadFail m, MonadIO m) =>
FutharkExe -> String -> Values -> m [Value]
getValues FutharkExe
futhark (String -> String
takeDirectory String
prog) Values
vals
    Succeeds (Just Success
SuccessGenerateValues) ->
      FutharkExe
-> String -> Text -> TestRun -> m (ExpectedResult [Value])
forall (m :: * -> *).
(MonadFail m, MonadIO m) =>
FutharkExe
-> String -> Text -> TestRun -> m (ExpectedResult [Value])
getExpectedResult FutharkExe
futhark String
prog Text
entry TestRun
tr'
      where
        tr' :: TestRun
tr' =
          TestRun
tr
            { runExpectedResult :: ExpectedResult Success
runExpectedResult =
                Maybe Success -> ExpectedResult Success
forall values. Maybe values -> ExpectedResult values
Succeeds (Maybe Success -> ExpectedResult Success)
-> (String -> Maybe Success) -> String -> ExpectedResult Success
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Success -> Maybe Success
forall a. a -> Maybe a
Just (Success -> Maybe Success)
-> (String -> Success) -> String -> Maybe Success
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Values -> Success
SuccessValues (Values -> Success) -> (String -> Values) -> String -> Success
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Values
InFile (String -> ExpectedResult Success)
-> String -> ExpectedResult Success
forall a b. (a -> b) -> a -> b
$
                  String -> Text -> TestRun -> String
testRunReferenceOutput String
prog Text
entry TestRun
tr
            }
    Succeeds Maybe Success
Nothing ->
      ExpectedResult [Value] -> m (ExpectedResult [Value])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpectedResult [Value] -> m (ExpectedResult [Value]))
-> ExpectedResult [Value] -> m (ExpectedResult [Value])
forall a b. (a -> b) -> a -> b
$ Maybe [Value] -> ExpectedResult [Value]
forall values. Maybe values -> ExpectedResult values
Succeeds Maybe [Value]
forall a. Maybe a
Nothing
    RunTimeFailure ExpectedError
err ->
      ExpectedResult [Value] -> m (ExpectedResult [Value])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExpectedResult [Value] -> m (ExpectedResult [Value]))
-> ExpectedResult [Value] -> m (ExpectedResult [Value])
forall a b. (a -> b) -> a -> b
$ ExpectedError -> ExpectedResult [Value]
forall values. ExpectedError -> ExpectedResult values
RunTimeFailure ExpectedError
err

-- | The name we use for compiled programs.
binaryName :: FilePath -> FilePath
binaryName :: String -> String
binaryName = String -> String
dropExtension

-- | @compileProgram extra_options futhark backend program@ compiles
-- @program@ with the command @futhark backend extra-options...@, and
-- returns stdout and stderr of the compiler.  Throws an IO exception
-- containing stderr if compilation fails.
compileProgram ::
  (MonadIO m, MonadError [T.Text] m) =>
  [String] ->
  FutharkExe ->
  String ->
  FilePath ->
  m (SBS.ByteString, SBS.ByteString)
compileProgram :: [String]
-> FutharkExe -> String -> String -> m (ByteString, ByteString)
compileProgram [String]
extra_options (FutharkExe String
futhark) String
backend String
program = do
  (ExitCode
futcode, ByteString
stdout, ByteString
stderr) <- IO (ExitCode, ByteString, ByteString)
-> m (ExitCode, ByteString, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ExitCode, ByteString, ByteString)
 -> m (ExitCode, ByteString, ByteString))
-> IO (ExitCode, ByteString, ByteString)
-> m (ExitCode, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ String
-> [String] -> ByteString -> IO (ExitCode, ByteString, ByteString)
readProcessWithExitCode String
futhark (String
backend String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
options) ByteString
""
  case ExitCode
futcode of
    ExitFailure Int
127 -> [Text] -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError [Text -> Text
forall a. (Semigroup a, IsString a) => a -> a
progNotFound (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
futhark]
    ExitFailure Int
_ -> [Text] -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError [ByteString -> Text
T.decodeUtf8 ByteString
stderr]
    ExitCode
ExitSuccess -> () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  (ByteString, ByteString) -> m (ByteString, ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
stdout, ByteString
stderr)
  where
    binOutputf :: String
binOutputf = String -> String
binaryName String
program
    options :: [String]
options = [String
program, String
"-o", String
binOutputf] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extra_options
    progNotFound :: a -> a
progNotFound a
s = a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
": command not found"

-- | @runProgram futhark runner extra_options prog entry input@ runs the
-- Futhark program @prog@ (which must have the @.fut@ suffix),
-- executing the @entry@ entry point and providing @input@ on stdin.
-- The program must have been compiled in advance with
-- 'compileProgram'.  If @runner@ is non-null, then it is used as
-- "interpreter" for the compiled program (e.g. @python@ when using
-- the Python backends).  The @extra_options@ are passed to the
-- program.
runProgram ::
  FutharkExe ->
  FilePath ->
  [String] ->
  String ->
  T.Text ->
  Values ->
  IO (ExitCode, SBS.ByteString, SBS.ByteString)
runProgram :: FutharkExe
-> String
-> [String]
-> String
-> Text
-> Values
-> IO (ExitCode, ByteString, ByteString)
runProgram FutharkExe
futhark String
runner [String]
extra_options String
prog Text
entry Values
input = do
  let progbin :: String
progbin = String -> String
binaryName String
prog
      dir :: String
dir = String -> String
takeDirectory String
prog
      binpath :: String
binpath = String
"." String -> String -> String
</> String
progbin
      entry_options :: [String]
entry_options = [String
"-e", Text -> String
T.unpack Text
entry]

      (String
to_run, [String]
to_run_args)
        | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
runner = (String
binpath, [String]
entry_options [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extra_options)
        | Bool
otherwise = (String
runner, String
binpath String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
entry_options [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extra_options)

  ByteString
input' <- FutharkExe -> String -> Values -> IO ByteString
forall (m :: * -> *).
(MonadFail m, MonadIO m) =>
FutharkExe -> String -> Values -> m ByteString
getValuesBS FutharkExe
futhark String
dir Values
input
  IO (ExitCode, ByteString, ByteString)
-> IO (ExitCode, ByteString, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ExitCode, ByteString, ByteString)
 -> IO (ExitCode, ByteString, ByteString))
-> IO (ExitCode, ByteString, ByteString)
-> IO (ExitCode, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ String
-> [String] -> ByteString -> IO (ExitCode, ByteString, ByteString)
readProcessWithExitCode String
to_run [String]
to_run_args (ByteString -> IO (ExitCode, ByteString, ByteString))
-> ByteString -> IO (ExitCode, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BS.toStrict ByteString
input'

-- | Read the given variables from a running server.
readResults ::
  (MonadIO m, MonadError T.Text m) =>
  Server ->
  [VarName] ->
  m [V.Value]
readResults :: Server -> [Text] -> m [Value]
readResults Server
server =
  (Text -> m Value) -> [Text] -> m [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Text -> m Value)
-> (Value -> m Value) -> Either Text Value -> m Value
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> m Value
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError Value -> m Value
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text Value -> m Value)
-> (Text -> m (Either Text Value)) -> Text -> m Value
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< IO (Either Text Value) -> m (Either Text Value)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either Text Value) -> m (Either Text Value))
-> (Text -> IO (Either Text Value))
-> Text
-> m (Either Text Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Server -> Text -> IO (Either Text Value)
getValue Server
server)

-- | Ensure that any reference output files exist, or create them (by
-- compiling the program with the reference compiler and running it on
-- the input) if necessary.
ensureReferenceOutput ::
  (MonadIO m, MonadError [T.Text] m) =>
  Maybe Int ->
  FutharkExe ->
  String ->
  FilePath ->
  [InputOutputs] ->
  m ()
ensureReferenceOutput :: Maybe Int
-> FutharkExe -> String -> String -> [InputOutputs] -> m ()
ensureReferenceOutput Maybe Int
concurrency FutharkExe
futhark String
compiler String
prog [InputOutputs]
ios = do
  [(Text, TestRun)]
missing <- ((Text, TestRun) -> m Bool)
-> [(Text, TestRun)] -> m [(Text, TestRun)]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (Text, TestRun) -> m Bool
forall (m :: * -> *). MonadIO m => (Text, TestRun) -> m Bool
isReferenceMissing ([(Text, TestRun)] -> m [(Text, TestRun)])
-> [(Text, TestRun)] -> m [(Text, TestRun)]
forall a b. (a -> b) -> a -> b
$ (InputOutputs -> [(Text, TestRun)])
-> [InputOutputs] -> [(Text, TestRun)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap InputOutputs -> [(Text, TestRun)]
entryAndRuns [InputOutputs]
ios

  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([(Text, TestRun)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Text, TestRun)]
missing) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    m (ByteString, ByteString) -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m (ByteString, ByteString) -> m ())
-> m (ByteString, ByteString) -> m ()
forall a b. (a -> b) -> a -> b
$ [String]
-> FutharkExe -> String -> String -> m (ByteString, ByteString)
forall (m :: * -> *).
(MonadIO m, MonadError [Text] m) =>
[String]
-> FutharkExe -> String -> String -> m (ByteString, ByteString)
compileProgram [] FutharkExe
futhark String
compiler String
prog

    [Either [Text] ()]
res <- IO [Either [Text] ()] -> m [Either [Text] ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Either [Text] ()] -> m [Either [Text] ()])
-> IO [Either [Text] ()] -> m [Either [Text] ()]
forall a b. (a -> b) -> a -> b
$
      (((Text, TestRun) -> IO (Either [Text] ()))
 -> [(Text, TestRun)] -> IO [Either [Text] ()])
-> [(Text, TestRun)]
-> ((Text, TestRun) -> IO (Either [Text] ()))
-> IO [Either [Text] ()]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe Int
-> ((Text, TestRun) -> IO (Either [Text] ()))
-> [(Text, TestRun)]
-> IO [Either [Text] ()]
forall a b. Maybe Int -> (a -> IO b) -> [a] -> IO [b]
pmapIO Maybe Int
concurrency) [(Text, TestRun)]
missing (((Text, TestRun) -> IO (Either [Text] ()))
 -> IO [Either [Text] ()])
-> ((Text, TestRun) -> IO (Either [Text] ()))
-> IO [Either [Text] ()]
forall a b. (a -> b) -> a -> b
$ \(Text
entry, TestRun
tr) -> do
        (ExitCode
code, ByteString
stdout, ByteString
stderr) <- FutharkExe
-> String
-> [String]
-> String
-> Text
-> Values
-> IO (ExitCode, ByteString, ByteString)
runProgram FutharkExe
futhark String
"" [String
"-b"] String
prog Text
entry (Values -> IO (ExitCode, ByteString, ByteString))
-> Values -> IO (ExitCode, ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ TestRun -> Values
runInput TestRun
tr
        case ExitCode
code of
          ExitFailure Int
e ->
            Either [Text] () -> IO (Either [Text] ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either [Text] () -> IO (Either [Text] ()))
-> Either [Text] () -> IO (Either [Text] ())
forall a b. (a -> b) -> a -> b
$
              [Text] -> Either [Text] ()
forall a b. a -> Either a b
Left
                [ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
                    String
"Reference dataset generation failed with exit code "
                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
e
                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" and stderr:\n"
                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Word8 -> Char) -> [Word8] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (ByteString -> [Word8]
SBS.unpack ByteString
stderr)
                ]
          ExitCode
ExitSuccess -> do
            let f :: String
f = (Text, TestRun) -> String
file (Text
entry, TestRun
tr)
            IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
takeDirectory String
f
            String -> ByteString -> IO ()
SBS.writeFile String
f ByteString
stdout
            Either [Text] () -> IO (Either [Text] ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either [Text] () -> IO (Either [Text] ()))
-> Either [Text] () -> IO (Either [Text] ())
forall a b. (a -> b) -> a -> b
$ () -> Either [Text] ()
forall a b. b -> Either a b
Right ()

    case [Either [Text] ()] -> Either [Text] ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Either [Text] ()]
res of
      Left [Text]
err -> [Text] -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError [Text]
err
      Right () -> () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  where
    file :: (Text, TestRun) -> String
file (Text
entry, TestRun
tr) =
      String -> String
takeDirectory String
prog String -> String -> String
</> String -> Text -> TestRun -> String
testRunReferenceOutput String
prog Text
entry TestRun
tr

    entryAndRuns :: InputOutputs -> [(Text, TestRun)]
entryAndRuns (InputOutputs Text
entry [TestRun]
rts) = (TestRun -> (Text, TestRun)) -> [TestRun] -> [(Text, TestRun)]
forall a b. (a -> b) -> [a] -> [b]
map (Text
entry,) [TestRun]
rts

    isReferenceMissing :: (Text, TestRun) -> m Bool
isReferenceMissing (Text
entry, TestRun
tr)
      | Succeeds (Just Success
SuccessGenerateValues) <- TestRun -> ExpectedResult Success
runExpectedResult TestRun
tr =
        IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$
          (UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
(<) (UTCTime -> UTCTime -> Bool) -> IO UTCTime -> IO (UTCTime -> Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO UTCTime
getModificationTime ((Text, TestRun) -> String
file (Text
entry, TestRun
tr)) IO (UTCTime -> Bool) -> IO UTCTime -> IO Bool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> IO UTCTime
getModificationTime String
prog)
            IO Bool -> (IOError -> IO Bool) -> IO Bool
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\IOError
e -> if IOError -> Bool
isDoesNotExistError IOError
e then Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True else IOError -> IO Bool
forall a e. Exception e => e -> a
E.throw IOError
e)
      | Bool
otherwise =
        Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False

-- | Determine the --tuning options to pass to the program.  The first
-- argument is the extension of the tuning file, or 'Nothing' if none
-- should be used.
determineTuning :: MonadIO m => Maybe FilePath -> FilePath -> m ([String], String)
determineTuning :: Maybe String -> String -> m ([String], String)
determineTuning Maybe String
Nothing String
_ = ([String], String) -> m ([String], String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], String
forall a. Monoid a => a
mempty)
determineTuning (Just String
ext) String
program = do
  Bool
exists <- IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist (String
program String -> String -> String
<.> String
ext)
  if Bool
exists
    then
      ([String], String) -> m ([String], String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
        ( [String
"--tuning", String
program String -> String -> String
<.> String
ext],
          String
" (using " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String -> String
takeFileName (String
program String -> String -> String
<.> String
ext) String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
")"
        )
    else ([String], String) -> m ([String], String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], String
" (no tuning file)")

-- | Check that the result is as expected, and write files and throw
-- an error if not.
checkResult ::
  (MonadError T.Text m, MonadIO m) =>
  FilePath ->
  [V.Value] ->
  [V.Value] ->
  m ()
checkResult :: String -> [Value] -> [Value] -> m ()
checkResult String
program [Value]
expected_vs [Value]
actual_vs =
  case Tolerance -> [Value] -> [Value] -> [Mismatch]
V.compareSeveralValues (Double -> Tolerance
V.Tolerance Double
0.002) [Value]
actual_vs [Value]
expected_vs of
    Mismatch
mismatch : [Mismatch]
mismatches -> do
      let actualf :: String
actualf = String
program String -> String -> String
<.> String
"actual"
          expectedf :: String
expectedf = String
program String -> String -> String
<.> String
"expected"
      IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
BS.writeFile String
actualf (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ (Value -> ByteString) -> [Value] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map Value -> ByteString
forall a. Binary a => a -> ByteString
Bin.encode [Value]
actual_vs
      IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
BS.writeFile String
expectedf (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ (Value -> ByteString) -> [Value] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map Value -> ByteString
forall a. Binary a => a -> ByteString
Bin.encode [Value]
expected_vs
      Text -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$
        String -> Text
T.pack String
actualf Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" and " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
expectedf
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" do not match:\n"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Mismatch -> String
forall a. Show a => a -> String
show Mismatch
mismatch)
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> if [Mismatch] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Mismatch]
mismatches
            then Text
forall a. Monoid a => a
mempty
            else Text
"\n...and " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Pretty a => a -> Text
prettyText ([Mismatch] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Mismatch]
mismatches) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" other mismatches."
    [] ->
      () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

-- | Create a Futhark server configuration suitable for use when
-- testing/benchmarking Futhark programs.
futharkServerCfg :: FilePath -> [String] -> ServerCfg
futharkServerCfg :: String -> [String] -> ServerCfg
futharkServerCfg String
prog [String]
opts =
  (String -> [String] -> ServerCfg
newServerCfg String
prog [String]
opts)
    { cfgDebug :: Bool
cfgDebug = String -> Int -> Bool
isEnvVarAtLeast String
"FUTHARK_COMPILER_DEBUGGING" Int
1
    }