{-# LANGUAGE OverloadedStrings, Trustworthy #-} -- | -- Maintainer : Ricky Elrod -- Stability : stable -- -- Contains data types/constructors for individual sandbox runs. -- For example, the compile step will produce a 'SandboxResult', which is -- defined in this module. The execution/evaluation step will also produce a -- 'SandboxResult'. module Evalso.Cruncher.SandboxResult (SandboxResult (..)) where import Control.Applicative import Control.Monad (mzero) import Data.Aeson hiding (Result) import Data.Text (Text) -- | Describes the result we get back after performing an evaluation (or -- compilation). This is almost always wrapped in 'IO'. data SandboxResult = SandboxResult { stdout :: Text , stderr :: Text , wallTime :: Int , exitCode :: Int } deriving (Eq, Show) instance ToJSON SandboxResult where toJSON (SandboxResult stdout' stderr' wallTime' exitCode') = object [ "stdout" .= stdout' , "stderr" .= stderr' , "wallTime" .= wallTime' , "exitCode" .= exitCode' ] instance FromJSON SandboxResult where parseJSON (Object v) = SandboxResult <$> v .: "stdout" <*> v .: "stderr" <*> v .: "wallTime" <*> v .: "exitCode" parseJSON _ = mzero