module SMCDEL.Examples.SumAndProduct where import Data.List import Data.Maybe import SMCDEL.Language import SMCDEL.Internal.Help import SMCDEL.Symbolic.S5 -- possible pairs 1 Form xIs n = booloutofForm (powerset xProps !! n) xProps yIs n = booloutofForm (powerset yProps !! n) yProps sIs n = booloutofForm (powerset sProps !! n) sProps pIs n = booloutofForm (powerset pProps !! n) pProps xyAre :: (Int,Int) -> Form xyAre (n,m) = Conj [ xIs n, yIs m ] sapKnStruct :: KnowStruct sapKnStruct = KnS sapAllProps law obs where law = boolBddOf $ Disj [ Conj [ xyAre (x,y), sIs (x+y), pIs (x*y) ] | (x,y) <- pairs ] obs = [ (alice, sProps), (bob, pProps) ] sapKnows :: Agent -> Form sapKnows i = Disj [ K i (xyAre p) | p <- pairs ] sapForm1, sapForm2, sapForm3 :: Form sapForm1 = K alice $ Neg (sapKnows bob) -- Sum: I knew that you didn't know the numbers. sapForm2 = sapKnows bob -- Product: Now I know the two numbers sapForm3 = sapKnows alice -- Sum: Now I know the two numbers too sapProtocol :: Form sapProtocol = Conj [ sapForm1 , PubAnnounce sapForm1 sapForm2 , PubAnnounce sapForm1 (PubAnnounce sapForm2 sapForm3) ] sapSolutions :: [[Prp]] sapSolutions = whereViaBdd sapKnStruct sapProtocol sapExplainState :: [Prp] -> String sapExplainState truths = concat [ "x = ", explain xProps , ", y = ", explain yProps , ", x+y = ", explain sProps , " and x*y = ", explain pProps ] where explain = show . nmbr truths nmbr :: [Prp] -> [Prp] -> Int nmbr truths varProps = fromMaybe (error "Value not found") $ elemIndex (varProps `intersect` truths) (powerset varProps)