mirror of
https://github.com/Jaxan/nominal-lstar.git
synced 2025-04-27 14:47:45 +02:00
Added feature to start with a bigger table
This commit is contained in:
parent
56ad54ecb0
commit
df7a45fb69
6 changed files with 26 additions and 24 deletions
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# language RecordWildCards #-}
|
||||||
module AbstractLStar where
|
module AbstractLStar where
|
||||||
|
|
||||||
import ObservationTable
|
import ObservationTable
|
||||||
|
@ -59,19 +59,21 @@ learn makeComplete handleCounterExample constructHypothesis teacher s =
|
||||||
eqloop s2 h = case equivalent teacher h of
|
eqloop s2 h = case equivalent teacher h of
|
||||||
Nothing -> trace "Yes" $ h
|
Nothing -> trace "Yes" $ h
|
||||||
Just ces -> trace "No" $
|
Just ces -> trace "No" $
|
||||||
case isTrue . isEmpty $ realces h ces of
|
if isTrue . isEmpty $ realces h ces
|
||||||
True -> eqloop s2 h
|
then eqloop s2 h
|
||||||
False ->
|
else
|
||||||
let s3 = handleCounterExample teacher s2 ces in
|
let s3 = handleCounterExample teacher s2 ces in
|
||||||
learn makeComplete handleCounterExample constructHypothesis teacher s3
|
learn makeComplete handleCounterExample constructHypothesis teacher s3
|
||||||
realces h ces = NLambda.filter (\(ce, a) -> a `neq` accepts h ce) $ membership teacher ces
|
realces h ces = NLambda.filter (\(ce, a) -> a `neq` accepts h ce) $ membership teacher ces
|
||||||
|
|
||||||
-- Initial state is always the same in our case
|
-- Initialise with the trivial table
|
||||||
constructEmptyState :: LearnableAlphabet i => Teacher i -> State i
|
-- We allow to initialise with all words of length <= k,n for rows and columns
|
||||||
constructEmptyState teacher =
|
-- Normally one should take k = n = 0
|
||||||
|
constructEmptyState :: LearnableAlphabet i => Int -> Int -> Teacher i -> State i
|
||||||
|
constructEmptyState k n teacher =
|
||||||
let aa = Teacher.alphabet teacher in
|
let aa = Teacher.alphabet teacher in
|
||||||
let ss = singleton [] in
|
let ss = replicateSetUntil k aa in
|
||||||
let ssa = pairsWith (\s a -> s ++ [a]) ss aa in
|
let ssa = pairsWith (\s a -> s ++ [a]) ss aa in
|
||||||
let ee = singleton [] in
|
let ee = replicateSetUntil n aa in
|
||||||
let t = fillTable teacher (ss `union` ssa) ee in
|
let t = fillTable teacher (ss `union` ssa) ee in
|
||||||
State{..}
|
State{..}
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# language RecordWildCards #-}
|
||||||
module Angluin where
|
module Angluin where
|
||||||
|
|
||||||
import AbstractLStar
|
import AbstractLStar
|
||||||
|
@ -8,8 +8,8 @@ import Teacher
|
||||||
import Data.List (inits, tails)
|
import Data.List (inits, tails)
|
||||||
import Debug.Trace
|
import Debug.Trace
|
||||||
import NLambda
|
import NLambda
|
||||||
|
import Prelude (Bool (..), Maybe (..), fst, id, show, ($), (++), (.))
|
||||||
import qualified Prelude hiding ()
|
import qualified Prelude hiding ()
|
||||||
import Prelude (Bool(..), Maybe(..), id, ($), (.), (++), fst, show)
|
|
||||||
|
|
||||||
justOne :: (Contextual a, NominalType a) => Set a -> Set a
|
justOne :: (Contextual a, NominalType a) => Set a -> Set a
|
||||||
justOne s = mapFilter id . orbit [] . element $ s
|
justOne s = mapFilter id . orbit [] . element $ s
|
||||||
|
@ -70,12 +70,12 @@ makeCompleteAngluin = makeCompleteWith [closednessTest, consistencyTestDirect]
|
||||||
-- Default: use counter examples in columns, which is slightly faster
|
-- Default: use counter examples in columns, which is slightly faster
|
||||||
learnAngluin :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
learnAngluin :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
||||||
learnAngluin teacher = learn makeCompleteAngluin useCounterExampleMP constructHypothesis teacher initial
|
learnAngluin teacher = learn makeCompleteAngluin useCounterExampleMP constructHypothesis teacher initial
|
||||||
where initial = constructEmptyState teacher
|
where initial = constructEmptyState 0 0 teacher
|
||||||
|
|
||||||
-- The "classical" version, where counter examples are added as rows
|
-- The "classical" version, where counter examples are added as rows
|
||||||
learnAngluinRows :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
learnAngluinRows :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
||||||
learnAngluinRows teacher = learn makeCompleteAngluin useCounterExampleAngluin constructHypothesis teacher initial
|
learnAngluinRows teacher = learn makeCompleteAngluin useCounterExampleAngluin constructHypothesis teacher initial
|
||||||
where initial = constructEmptyState teacher
|
where initial = constructEmptyState 0 0 teacher
|
||||||
|
|
||||||
|
|
||||||
-- Below are some variations of the above functions with different
|
-- Below are some variations of the above functions with different
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# language RecordWildCards #-}
|
||||||
module Bollig where
|
module Bollig where
|
||||||
|
|
||||||
import AbstractLStar
|
import AbstractLStar
|
||||||
|
@ -9,11 +9,11 @@ import Teacher
|
||||||
import Data.List (tails)
|
import Data.List (tails)
|
||||||
import Debug.Trace
|
import Debug.Trace
|
||||||
import NLambda
|
import NLambda
|
||||||
|
import Prelude (Bool (..), Int, Maybe (..), fst, show, ($), (++), (.))
|
||||||
import qualified Prelude hiding ()
|
import qualified Prelude hiding ()
|
||||||
import Prelude (Bool(..), Maybe(..), ($), (.), (++), fst, show)
|
|
||||||
|
|
||||||
rowUnion :: NominalType i => Set (BRow i) -> BRow i
|
rowUnion :: NominalType i => Set (BRow i) -> BRow i
|
||||||
rowUnion set = Prelude.uncurry union . setTrueFalse . partition (\(_, f) -> f) $ map (\is -> (is, exists fromBool (mapFilter (\(is2, b) -> maybeIf (is `eq` is2) b) flatSet))) allIs
|
rowUnion set = Prelude.uncurry union . setTrueFalse . partition snd $ map (\is -> (is, exists fromBool (mapFilter (\(is2, b) -> maybeIf (is `eq` is2) b) flatSet))) allIs
|
||||||
where
|
where
|
||||||
flatSet = sum set
|
flatSet = sum set
|
||||||
allIs = map fst flatSet
|
allIs = map fst flatSet
|
||||||
|
@ -28,7 +28,7 @@ sublang :: NominalType i => BRow i -> BRow i -> Formula
|
||||||
sublang r1 r2 = forAll fromBool $ pairsWithFilter (\(i1, f1) (i2, f2) -> maybeIf (i1 `eq` i2) (f1 `boolImplies` f2)) r1 r2
|
sublang r1 r2 = forAll fromBool $ pairsWithFilter (\(i1, f1) (i2, f2) -> maybeIf (i1 `eq` i2) (f1 `boolImplies` f2)) r1 r2
|
||||||
|
|
||||||
sublangs :: NominalType i => BRow i -> Set (BRow i) -> Set (BRow i)
|
sublangs :: NominalType i => BRow i -> Set (BRow i) -> Set (BRow i)
|
||||||
sublangs r set = filter (\r2 -> r2 `sublang` r) set
|
sublangs r = filter (`sublang` r)
|
||||||
|
|
||||||
rfsaClosednessTest2 :: LearnableAlphabet i => State i -> TestResult i
|
rfsaClosednessTest2 :: LearnableAlphabet i => State i -> TestResult i
|
||||||
rfsaClosednessTest2 State{..} = case solve (isEmpty defect) of
|
rfsaClosednessTest2 State{..} = case solve (isEmpty defect) of
|
||||||
|
@ -69,6 +69,6 @@ constructHypothesisBollig State{..} = automaton q a d i f
|
||||||
makeCompleteBollig :: LearnableAlphabet i => TableCompletionHandler i
|
makeCompleteBollig :: LearnableAlphabet i => TableCompletionHandler i
|
||||||
makeCompleteBollig = makeCompleteWith [rfsaClosednessTest2, rfsaConsistencyTest]
|
makeCompleteBollig = makeCompleteWith [rfsaClosednessTest2, rfsaConsistencyTest]
|
||||||
|
|
||||||
learnBollig :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
learnBollig :: LearnableAlphabet i => Int -> Int -> Teacher i -> Automaton (BRow i) i
|
||||||
learnBollig teacher = learn makeCompleteBollig useCounterExampleMP constructHypothesisBollig teacher initial
|
learnBollig k n teacher = learn makeCompleteBollig useCounterExampleMP constructHypothesisBollig teacher initial
|
||||||
where initial = constructEmptyState teacher
|
where initial = constructEmptyState k n teacher
|
||||||
|
|
|
@ -38,7 +38,7 @@ mainExample learnerName teacherName autName = do
|
||||||
let h = case read learnerName of
|
let h = case read learnerName of
|
||||||
NomLStar -> learnAngluinRows teacher
|
NomLStar -> learnAngluinRows teacher
|
||||||
NomLStarCol -> learnAngluin teacher
|
NomLStarCol -> learnAngluin teacher
|
||||||
NomNLStar -> learnBollig teacher
|
NomNLStar -> learnBollig 1 1 teacher
|
||||||
print h
|
print h
|
||||||
|
|
||||||
mainWithIO :: String -> IO ()
|
mainWithIO :: String -> IO ()
|
||||||
|
@ -47,7 +47,7 @@ mainWithIO learnerName = do
|
||||||
let h = case read learnerName of
|
let h = case read learnerName of
|
||||||
NomLStar -> learnAngluinRows t
|
NomLStar -> learnAngluinRows t
|
||||||
NomLStarCol -> learnAngluin t
|
NomLStarCol -> learnAngluin t
|
||||||
NomNLStar -> learnBollig t
|
NomNLStar -> learnBollig 0 0 t
|
||||||
print h
|
print h
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -18,7 +18,7 @@ learn alphSet = do
|
||||||
let h = case read learnerName of
|
let h = case read learnerName of
|
||||||
NomLStar -> learnAngluinRows t
|
NomLStar -> learnAngluinRows t
|
||||||
NomLStarCol -> learnAngluin t
|
NomLStarCol -> learnAngluin t
|
||||||
NomNLStar -> learnBollig t
|
NomNLStar -> learnBollig 0 0 t
|
||||||
hPrint stderr h
|
hPrint stderr h
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -57,4 +57,4 @@ makeCompleteNonDet = makeCompleteWith [nonDetClosednessTest]
|
||||||
-- Default: use counter examples in columns, which is slightly faster
|
-- Default: use counter examples in columns, which is slightly faster
|
||||||
learnNonDet :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
learnNonDet :: LearnableAlphabet i => Teacher i -> Automaton (BRow i) i
|
||||||
learnNonDet teacher = learn makeCompleteNonDet useCounterExampleMP constructHypothesisNonDet teacher initial
|
learnNonDet teacher = learn makeCompleteNonDet useCounterExampleMP constructHypothesisNonDet teacher initial
|
||||||
where initial = constructEmptyState teacher
|
where initial = constructEmptyState 0 0 teacher
|
||||||
|
|
Loading…
Add table
Reference in a new issue