mirror of
https://github.com/Jaxan/ons-hs.git
synced 2025-04-27 22:57:44 +02:00
Made the teacher actually do something nontrivial
This commit is contained in:
parent
ce0fdd8e54
commit
b273931b9c
3 changed files with 127 additions and 27 deletions
15
app/IO.hs
15
app/IO.hs
|
@ -56,3 +56,18 @@ instance FromStr a => FromStr [a] where
|
||||||
where
|
where
|
||||||
(a, str2) = fromStr str
|
(a, str2) = fromStr str
|
||||||
(l, emptyStr) = fromStr (dropWhile isSpace str2)
|
(l, emptyStr) = fromStr (dropWhile isSpace str2)
|
||||||
|
|
||||||
|
newtype MQ a = MQ a
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
instance ToStr a => ToStr (MQ a) where
|
||||||
|
toStr (MQ a) = "MQ \"" <> toStr a <> "\""
|
||||||
|
|
||||||
|
-- totally a hack, should do proper parsing at some point
|
||||||
|
instance FromStr a => FromStr (MQ a) where
|
||||||
|
fromStr ('M':'Q':str) = let (a, rem) = fromStr (clean str) in (MQ a, rem)
|
||||||
|
where
|
||||||
|
trim str = dropWhile isSpace str
|
||||||
|
takeQ ('\"':rem) = rem
|
||||||
|
takeQ rem = error $ "parse error for MQ: " <> rem
|
||||||
|
clean = reverse . takeQ . trim . reverse . takeQ . trim
|
||||||
|
|
|
@ -153,9 +153,7 @@ learn mq eq = do
|
||||||
-- Here is the teacher: just pose the queries in the terminal
|
-- Here is the teacher: just pose the queries in the terminal
|
||||||
askMember :: _ => Word a -> IO Bool
|
askMember :: _ => Word a -> IO Bool
|
||||||
askMember w = do
|
askMember w = do
|
||||||
putStr "MQ \""
|
putStrLn (toStr (MQ w))
|
||||||
putStr (toStr w)
|
|
||||||
putStrLn "\""
|
|
||||||
hFlush stdout
|
hFlush stdout
|
||||||
a <- getLine
|
a <- getLine
|
||||||
case a of
|
case a of
|
||||||
|
|
135
app/Teacher.hs
135
app/Teacher.hs
|
@ -1,29 +1,116 @@
|
||||||
import System.IO (hFlush, stderr, stdout, hPutStrLn)
|
{-# LANGUAGE ImportQualifiedPost #-}
|
||||||
|
|
||||||
|
import System.IO (hFlush, hPutStrLn, stderr, stdout)
|
||||||
|
|
||||||
|
import Data.IORef
|
||||||
|
import Data.Maybe (isJust)
|
||||||
|
import System.Exit (exitFailure)
|
||||||
|
import System.IO
|
||||||
|
|
||||||
|
import ExampleAutomata
|
||||||
|
import IO
|
||||||
|
import Nominal (Atom)
|
||||||
|
import OrbitList qualified
|
||||||
|
import Support (Rat (..))
|
||||||
|
|
||||||
|
data Example
|
||||||
|
= Fifo Int
|
||||||
|
| DoubleWord Int
|
||||||
|
|
||||||
-- TODO: Actually implement interesting languages... Not sure yet how I want
|
|
||||||
-- to do equivalence queries. Maybe let the teacher respond with a test
|
|
||||||
-- query to the learner?
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main =
|
||||||
|
let ex = Fifo 2
|
||||||
|
in case ex of
|
||||||
|
Fifo n -> teach "FIFO" (fifoFun n) (fifoCex n)
|
||||||
|
DoubleWord n -> teach "ATOMS" (doubleFun n) (doubleCex n)
|
||||||
|
|
||||||
|
teach :: (ToStr a, FromStr a, Show a) => String -> ([a] -> Bool) -> [[a]] -> IO ()
|
||||||
|
teach alphStr fun cexes = do
|
||||||
|
-- Set up some counters
|
||||||
|
countMQ <- newIORef (0 :: Int)
|
||||||
|
countEQ <- newIORef (0 :: Int)
|
||||||
|
cexChecks <- newIORef cexes
|
||||||
|
|
||||||
|
let
|
||||||
|
-- Helper functions for answering/logging
|
||||||
|
log str = hPutStrLn stderr str
|
||||||
|
answer str = hPutStrLn stdout str >> hFlush stdout
|
||||||
|
|
||||||
|
-- Parsing the commands from the learner
|
||||||
|
act message =
|
||||||
|
case message of
|
||||||
|
"ALPHABET" -> handleAlphabet
|
||||||
|
('M' : 'Q' : _) -> handleMQ message
|
||||||
|
('E' : 'Q' : _) -> handleEQ message
|
||||||
|
_ -> do
|
||||||
|
hPutStrLn stderr "Invalid command"
|
||||||
|
exitFailure
|
||||||
|
|
||||||
|
handleAlphabet = answer alphStr
|
||||||
|
|
||||||
|
handleMQ str = do
|
||||||
|
let (MQ word, _) = fromStr str
|
||||||
|
acc = fun word
|
||||||
|
answer $ if acc then "Y" else "N"
|
||||||
|
|
||||||
|
modifyIORef countMQ succ
|
||||||
|
n <- readIORef countMQ
|
||||||
|
log $ "MQ " <> show n <> ": " <> str <> " -> " <> show acc -- <> " (parsed as " <> show word <> ")"
|
||||||
|
|
||||||
|
handleEQ str = do
|
||||||
|
modifyIORef countEQ succ
|
||||||
|
n <- readIORef countEQ
|
||||||
|
log $ "EQ " <> show n <> ": " <> str
|
||||||
|
|
||||||
|
-- Currently, we handle equivalence queries very lazily: we simply pose
|
||||||
|
-- a possible counterexample to the learner (which it might actually do
|
||||||
|
-- correctly). There is no guarantee is will work.
|
||||||
|
possibleCexes <- readIORef cexChecks
|
||||||
|
case possibleCexes of
|
||||||
|
[] -> do
|
||||||
|
log " -> Y"
|
||||||
|
answer "Y"
|
||||||
|
(c : cs) -> do
|
||||||
|
log $ " -> N " <> toStr c
|
||||||
|
-- TODO: make this syntax the same as for MQs
|
||||||
|
answer $ "N " <> toStr c
|
||||||
|
writeIORef cexChecks cs
|
||||||
|
|
||||||
|
-- Lazily answer all queries, until the stream is closed
|
||||||
messages <- lines <$> getContents
|
messages <- lines <$> getContents
|
||||||
mapM_ act messages
|
mapM_ act messages
|
||||||
|
|
||||||
|
-- Then output some statistics
|
||||||
|
m <- readIORef countMQ
|
||||||
|
e <- readIORef countEQ
|
||||||
|
hPutStrLn stderr $ "Total number of MQ: " <> show m
|
||||||
|
hPutStrLn stderr $ "Total number of EQ: " <> show e
|
||||||
|
|
||||||
|
-- examples from https://gitlab.science.ru.nl/moerman/nominal-learning-ons/-/blob/master/examples.hpp
|
||||||
|
-- Note: we do not implement them as state machines. Instead we implement them
|
||||||
|
-- as functions, to really make the point that this is "black box learning".
|
||||||
|
|
||||||
|
fifoFun :: Int -> [FifoA] -> Bool
|
||||||
|
fifoFun n = acc . foldl' step (Just [])
|
||||||
where
|
where
|
||||||
act message =
|
step Nothing _ = Nothing
|
||||||
case message of
|
step (Just ls) (Put a)
|
||||||
"ALPHABET" -> handleAlphabet
|
| length ls >= n = Nothing
|
||||||
str -> case take 2 message of
|
| otherwise = Just (ls <> [a])
|
||||||
"MQ" -> handleMQ (drop 3 message)
|
step (Just []) (Get a) = Nothing
|
||||||
"EQ" -> handleEQ (drop 3 message)
|
step (Just (x : xs)) (Get a)
|
||||||
handleAlphabet = do
|
| a == x = Just xs
|
||||||
putStrLn "ATOMS"
|
| otherwise = Nothing
|
||||||
hFlush stdout
|
acc = isJust
|
||||||
handleMQ str = do
|
|
||||||
-- accepts any string
|
fifoCex :: Int -> [[FifoA]]
|
||||||
putStrLn "Y"
|
fifoCex n = concatMap dw [1 .. n]
|
||||||
hPutStrLn stderr $ "MQ received: " <> str
|
where
|
||||||
hFlush stdout
|
dw k = [fmap Put w <> fmap Get w | w <- OrbitList.toList (OrbitList.repeatRationals k)]
|
||||||
handleEQ str = do
|
|
||||||
-- immediately accepts the hypothesis
|
doubleFun :: Int -> [Atom] -> Bool
|
||||||
putStrLn "Y"
|
doubleFun 0 w = w == []
|
||||||
hPutStrLn stderr $ "EQ received: " <> str
|
doubleFun n w = let (l, r) = splitAt n w in w /= [] && l == r
|
||||||
hFlush stdout
|
|
||||||
|
doubleCex :: Int -> [[Atom]]
|
||||||
|
doubleCex n = [w <> w | w <- OrbitList.toList (OrbitList.repeatRationals n)]
|
||||||
|
|
Loading…
Add table
Reference in a new issue