module Ideas.Common.Exercise
(
Exercise(..), emptyExercise, makeExercise
, prettyPrinterContext, isReady, isSuitable
, ruleset, getRule, ruleOrderingWith
, Status(..), isPublic, isPrivate
, Examples, Difficulty(..), readDifficulty
, level, mapExamples, examplesContext
, inContext, withoutContext
, useTypeable, castFrom, castTo
, setProperty, getProperty, setPropertyF, getPropertyF
, simpleGenerator, useGenerator, randomTerm, randomTerms
, showDerivation, showDerivations, printDerivation, printDerivations
, diffEnvironment, defaultDerivation, allDerivations
) where
import Data.Char
import Data.List
import Data.Maybe
import Data.Ord
import Ideas.Common.Classes
import Ideas.Common.Context
import Ideas.Common.Derivation
import Ideas.Common.Environment
import Ideas.Common.Id
import Ideas.Common.Predicate
import Ideas.Common.Rewriting
import Ideas.Common.Rule
import Ideas.Common.Strategy hiding (not, fail, repeat, replicate)
import Ideas.Common.View
import Ideas.Utils.Prelude (ShowString(..))
import Ideas.Utils.Typeable
import System.Random
import Test.QuickCheck hiding (label)
import Test.QuickCheck.Gen
import Test.QuickCheck.Random (QCGen)
import qualified Data.Map as M
import qualified Ideas.Common.Strategy as S
data Exercise a =
NewExercise
{
exerciseId :: Id
, status :: Status
, parser :: String -> Either String a
, prettyPrinter :: a -> String
, equivalence :: Context a -> Context a -> Bool
, similarity :: Context a -> Context a -> Bool
, suitable :: Predicate a
, ready :: Predicate a
, strategy :: LabeledStrategy (Context a)
, canBeRestarted :: Bool
, extraRules :: [Rule (Context a)]
, ruleOrdering :: Rule (Context a) -> Rule (Context a) -> Ordering
, navigation :: a -> ContextNavigator a
, examples :: Examples a
, randomExercise :: Maybe (QCGen -> Maybe Difficulty -> a)
, testGenerator :: Maybe (Gen a)
, hasTermView :: Maybe (View Term a)
, hasTypeable :: Maybe (IsTypeable a)
, properties :: M.Map Id (Dynamic a)
}
instance Eq (Exercise a) where
e1 == e2 = getId e1 == getId e2
instance Ord (Exercise a) where
compare = comparing getId
instance Apply Exercise where
applyAll ex = mapMaybe fromContext . applyAll (strategy ex) . inContext ex
instance HasId (Exercise a) where
getId = exerciseId
changeId f ex = ex { exerciseId = f (exerciseId ex) }
emptyExercise :: Exercise a
emptyExercise = NewExercise
{
exerciseId = mempty
, status = Experimental
, parser = const (Left "<<no parser>>")
, prettyPrinter = const "<<no pretty-printer>>"
, equivalence = \_ _ -> True
, similarity = \_ _ -> True
, ready = true
, suitable = true
, hasTermView = Nothing
, hasTypeable = Nothing
, properties = M.empty
, strategy = label "Fail" S.fail
, navigation = noNavigator
, canBeRestarted = True
, extraRules = []
, ruleOrdering = compareId
, testGenerator = Nothing
, randomExercise = Nothing
, examples = []
}
makeExercise :: (Show a, Eq a, IsTerm a) => Exercise a
makeExercise = emptyExercise
{ prettyPrinter = show
, similarity = (==)
, hasTermView = Just termView
}
prettyPrinterContext :: Exercise a -> Context a -> String
prettyPrinterContext ex =
maybe "<<invalid term>>" (prettyPrinter ex) . fromContext
isReady :: Exercise a -> a -> Bool
isReady = evalPredicate . ready
isSuitable :: Exercise a -> a -> Bool
isSuitable = evalPredicate . suitable
ruleset :: Exercise a -> [Rule (Context a)]
ruleset ex = nub (sortBy (ruleOrdering ex) list)
where
list = extraRules ex ++ rulesInStrategy (strategy ex)
getRule :: Monad m => Exercise a -> Id -> m (Rule (Context a))
getRule ex a =
case filter ((a ==) . getId) (ruleset ex) of
[hd] -> return hd
[] -> fail $ "Could not find ruleid " ++ showId a
_ -> fail $ "Ambiguous ruleid " ++ showId a
ruleOrderingWith :: HasId b => [b] -> Rule a -> Rule a -> Ordering
ruleOrderingWith bs r1 r2 =
let xs = map getId bs in
case (elemIndex (getId r1) xs, elemIndex (getId r2) xs) of
(Just i, Just j ) -> i `compare` j
(Just _, Nothing) -> LT
(Nothing, Just _ ) -> GT
(Nothing, Nothing) -> compareId r1 r2
data Status
= Stable
| Provisional
| Alpha
| Experimental
deriving (Show, Eq)
isPublic :: Exercise a -> Bool
isPublic ex = status ex `elem` [Stable, Provisional]
isPrivate :: Exercise a -> Bool
isPrivate = not . isPublic
type Examples a = [(Difficulty, a)]
data Difficulty = VeryEasy | Easy | Medium | Difficult | VeryDifficult
deriving (Eq, Ord, Enum)
instance Show Difficulty where
show = (xs !!) . fromEnum
where
xs = ["very_easy", "easy", "medium", "difficult", "very_difficult"]
instance Read Difficulty where
readsPrec _ s =
case concatMap f txt of
"veryeasy" -> [(VeryEasy, xs)]
"easy" -> [(Easy, xs)]
"medium" -> [(Medium, xs)]
"difficult" -> [(Difficult, xs)]
"verydifficult" -> [(VeryDifficult, xs)]
_ -> []
where
(txt, xs) = span p (dropWhile isSpace s)
p c = isAlpha c || c `elem` "_-"
f c = [toLower c | c `notElem` "_-"]
readDifficulty :: String -> Maybe Difficulty
readDifficulty s =
case filter p [VeryEasy .. VeryDifficult] of
[a] -> Just a
_ -> Nothing
where
normal = filter isAlpha . map toLower
p = (== normal s) . normal . show
level :: Difficulty -> [a] -> Examples a
level = zip . repeat
mapExamples :: (a -> b) -> Examples a -> Examples b
mapExamples f = map (second f)
examplesContext :: Exercise a -> Examples (Context a)
examplesContext ex = mapExamples (inContext ex) (examples ex)
inContext :: Exercise a -> a -> Context a
inContext ex = newContext . navigation ex
withoutContext :: (a -> a -> Bool) -> Context a -> Context a -> Bool
withoutContext f a b = fromMaybe False (fromContextWith2 f a b)
instance HasTypeable Exercise where
getTypeable = hasTypeable
useTypeable :: Typeable a => Maybe (IsTypeable a)
useTypeable = Just typeable
setProperty :: (IsId n, Typeable val) => n -> val -> Exercise a -> Exercise a
setProperty key a = insertProperty key (Dyn (cast a))
setPropertyF :: (IsId n, Typeable f) => n -> f a -> Exercise a -> Exercise a
setPropertyF key a = insertProperty key (DynF (castF a))
insertProperty :: IsId n => n -> Dynamic a -> Exercise a -> Exercise a
insertProperty key d ex =
ex { properties = M.insert (newId key) d (properties ex) }
getProperty :: (IsId n, Typeable val) => n -> Exercise a -> Maybe val
getProperty key ex = lookupProperty key ex >>= \d ->
case d of
Dyn m -> m
_ -> Nothing
getPropertyF :: (IsId n, Typeable f) => n -> Exercise a -> Maybe (f a)
getPropertyF key ex = lookupProperty key ex >>= \d ->
case d of
DynF m -> m
_ -> Nothing
lookupProperty :: IsId n => n -> Exercise a -> Maybe (Dynamic a)
lookupProperty key = M.lookup (newId key) . properties
data Dynamic a = Dyn (forall b . Typeable b => Maybe b)
| DynF (forall f . Typeable f => Maybe (f a))
castF :: (Typeable f, Typeable g) => f a -> Maybe (g a)
castF = fmap fromIdentity . gcast1 . Identity
newtype Identity a = Identity { fromIdentity :: a}
simpleGenerator :: Gen a -> Maybe (QCGen -> Maybe Difficulty -> a)
simpleGenerator = useGenerator . const
useGenerator :: (Maybe Difficulty -> Gen a) -> Maybe (QCGen -> Maybe Difficulty -> a)
useGenerator makeGen = Just (\rng -> rec rng . makeGen)
where
rec rng (MkGen f) = a
where
(size, r) = randomR (0, 100) rng
a = f r size
randomTerm :: QCGen -> Exercise a -> Maybe Difficulty -> Maybe a
randomTerm rng ex mdif =
case randomExercise ex of
Just f -> return (f rng mdif)
Nothing
| null xs -> Nothing
| otherwise -> Just (snd (xs !! i))
where
xs = filter p (examples ex)
p (d, _) = maybe True (==d) mdif
i = fst (randomR (0, length xs 1) rng)
randomTerms :: QCGen -> Exercise a -> Maybe Difficulty -> [a]
randomTerms rng ex mdif = rec rng
where
rec a = maybe id (:) (randomTerm a ex mdif) (rec (snd (next a)))
showDerivation :: Exercise a -> a -> String
showDerivation ex a =
case defaultDerivation ex a of
Just d -> showThisDerivation d ex
Nothing -> "no derivation"
showDerivations :: Exercise a -> a -> String
showDerivations ex a = unlines
[ "Derivation #" ++ show i ++ "\n" ++ showThisDerivation d ex
| (i, d) <- zip [1::Int ..] (allDerivations ex a)
]
printDerivation :: Exercise a -> a -> IO ()
printDerivation ex = putStrLn . showDerivation ex
printDerivations :: Exercise a -> a -> IO ()
printDerivations ex = putStrLn . showDerivations ex
showThisDerivation :: Derivation (Rule b, Environment) (Context a) -> Exercise a -> String
showThisDerivation d ex = show (present der) ++ extra
where
der = diffEnvironment d
extra =
case fromContext (lastTerm der) of
Nothing -> "<<invalid term>>"
Just b | isReady ex b -> ""
| otherwise -> "<<not ready>>"
present = biMap (ShowString . f) (ShowString . prettyPrinterContext ex)
f ((r, local), global) = showId r ++ part local ++ part global
where
newl = "\n "
part env | noBindings env = ""
| otherwise = newl ++ show env
diffEnvironment :: HasEnvironment a => Derivation s a -> Derivation (s, Environment) a
diffEnvironment = updateSteps $ \old a new ->
let keep x = not (getId x == newId "location" || x `elem` list)
list = bindings old
in (a, makeEnvironment $ filter keep $ bindings new)
defaultDerivation :: Exercise a -> a -> Maybe (Derivation (Rule (Context a), Environment) (Context a))
defaultDerivation ex = listToMaybe . allDerivations ex
allDerivations :: Exercise a -> a -> [Derivation (Rule (Context a), Environment) (Context a)]
allDerivations ex =
derivationList (ruleOrdering ex) (strategy ex) . inContext ex