----------------------------------------------------------------------------- -- Copyright 2019, Advise-Me project team. This file is distributed under -- the terms of the Apache License 2.0. For more information, see the files -- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution. ----------------------------------------------------------------------------- -- | -- Maintainer : bastiaan.heeren@ou.nl -- Stability : provisional -- Portability : portable (depends on ghc) -- ----------------------------------------------------------------------------- module Recognize.Model.Result where import Data.Semigroup -- | Describes the possible results of the predicate of a constraint data Result = Success -- ^ The predicate was true | Failure -- ^ The predicate was false | Unknown -- ^ We don't know whether the predicate is true or false deriving (Eq, Show) instance Semigroup Result where Success <> Success = Success Success <> r2 = r2 r1 <> Success = r1 Unknown <> Unknown = Unknown _ <> Failure = Failure Failure <> _ = Failure instance Monoid Result where mempty = Success mappend = (<>) resultToBool :: Result -> Maybe Bool resultToBool Success = Just True resultToBool Failure = Just False resultToBool Unknown = Nothing isUnknown :: Result -> Bool isUnknown Unknown = True isUnknown _ = False negate :: Result -> Result negate Success = Failure negate Failure = Success negate Unknown = Unknown