sbv-10.9: SMT Based Verification: Symbolic Haskell theorem prover using SMT solving.
Copyright(c) Levent Erkok
LicenseBSD3
Maintainererkokl@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Description

From Raymond Smullyan: On a fictional island, all inhabitants are either knights, who always tell the truth, or knaves, who always lie. John and Bill are residents of the island of knights and knaves. John and Bill make several utterances. Determine which one is a knave or a knight, depending on their answers.

Synopsis

Documentation

data Inhabitant Source #

Inhabitants of the island, as an uninterpreted sort

Instances

Instances details
Data Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inhabitant -> c Inhabitant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inhabitant #

toConstr :: Inhabitant -> Constr #

dataTypeOf :: Inhabitant -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inhabitant) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inhabitant) #

gmapT :: (forall b. Data b => b -> b) -> Inhabitant -> Inhabitant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inhabitant -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inhabitant -> r #

gmapQ :: (forall d. Data d => d -> u) -> Inhabitant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Inhabitant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inhabitant -> m Inhabitant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inhabitant -> m Inhabitant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inhabitant -> m Inhabitant #

Read Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Show Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SymVal Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

HasKind Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SatModel Inhabitant Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

parseCVs :: [CV] -> Maybe (Inhabitant, [CV]) Source #

cvtModel :: (Inhabitant -> Maybe b) -> Maybe (Inhabitant, [CV]) -> Maybe (b, [CV]) Source #

type SInhabitant = SBV Inhabitant Source #

Symbolic version of the type Inhabitant.

data Identity Source #

Each inhabitant is either a knave or a knight

Constructors

Knave 
Knight 

Instances

Instances details
Data Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity -> c Identity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Identity #

toConstr :: Identity -> Constr #

dataTypeOf :: Identity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Identity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identity) #

gmapT :: (forall b. Data b => b -> b) -> Identity -> Identity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity -> m Identity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity -> m Identity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity -> m Identity #

Read Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Show Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Eq Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Ord Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SymVal Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

HasKind Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SatModel Identity Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

parseCVs :: [CV] -> Maybe (Identity, [CV]) Source #

cvtModel :: (Identity -> Maybe b) -> Maybe (Identity, [CV]) -> Maybe (b, [CV]) Source #

type SIdentity = SBV Identity Source #

Symbolic version of the type Identity.

sKnave :: SBV Identity Source #

Symbolic version of the constructor Knave.

sKnight :: SBV Identity Source #

Symbolic version of the constructor Knight.

data Statement Source #

Statements are utterances which are either true or false

Constructors

Truth 
Falsity 

Instances

Instances details
Data Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement -> c Statement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Statement #

toConstr :: Statement -> Constr #

dataTypeOf :: Statement -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Statement) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Statement) #

gmapT :: (forall b. Data b => b -> b) -> Statement -> Statement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement -> r #

gmapQ :: (forall d. Data d => d -> u) -> Statement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

Read Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Show Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Eq Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Ord Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SymVal Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

HasKind Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

SatModel Statement Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.KnightsAndKnaves

Methods

parseCVs :: [CV] -> Maybe (Statement, [CV]) Source #

cvtModel :: (Statement -> Maybe b) -> Maybe (Statement, [CV]) -> Maybe (b, [CV]) Source #

type SStatement = SBV Statement Source #

Symbolic version of the type Statement.

sTruth :: SBV Statement Source #

Symbolic version of the constructor Truth.

sFalsity :: SBV Statement Source #

Symbolic version of the constructor Falsity.

john :: SInhabitant Source #

John is an inhabitant of the island.

bill :: SInhabitant Source #

Bill is an inhabitant of the island.

is :: SInhabitant -> SIdentity -> SStatement Source #

The connective is makes a statement about an inhabitant regarding his/her identity.

says :: SInhabitant -> SStatement -> SBool Source #

The connective says makes a predicate from what an inhabitant states

holds :: SStatement -> SBool Source #

The connective holds is will be true if the statement is true

and :: SStatement -> SStatement -> SStatement Source #

The connective and creates the conjunction of two statements

not :: SStatement -> SStatement Source #

The connective not negates a statement

iff :: SStatement -> SStatement -> SStatement Source #

The connective iff creates a statement that equates the truth values of its argument statements

puzzle :: IO () Source #

Encode Smullyan's puzzle. We have:

>>> puzzle
Question 1.
  John says, We are both knaves
    Then, John is: Knave
    And,  Bill is: Knight
Question 2.
  John says If (and only if) Bill is a knave, then I am a knave.
  Bill says We are of different kinds.
    Then, John is: Knave
    And,  Bill is: Knight