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.Birthday

Description

This is a formalization of the Cheryl's birthday problem, which went viral in April 2015. (See http://www.nytimes.com/2015/04/15/science/a-math-problem-from-singapore-goes-viral-when-is-cheryls-birthday.html.)

Here's the puzzle:

Albert and Bernard just met Cheryl. "When’s your birthday?" Albert asked Cheryl.

Cheryl thought a second and said, "I’m not going to tell you, but I’ll give you some clues." She wrote down a list of 10 dates:

  May 15, May 16, May 19
  June 17, June 18
  July 14, July 16
  August 14, August 15, August 17

"My birthday is one of these," she said.

Then Cheryl whispered in Albert’s ear the month — and only the month — of her birthday. To Bernard, she whispered the day, and only the day. 
“Can you figure it out now?” she asked Albert.

Albert: I don’t know when your birthday is, but I know Bernard doesn’t know, either.
Bernard: I didn’t know originally, but now I do.
Albert: Well, now I know, too!

When is Cheryl’s birthday?

NB. Thanks to Amit Goel for suggesting the formalization strategy used in here.

Synopsis

Types and values

data Month Source #

Months. We only put in the months involved in the puzzle for simplicity

Constructors

May 
Jun 
Jul 
Aug 

Instances

Instances details
Data Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

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

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

toConstr :: Month -> Constr #

dataTypeOf :: Month -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Show Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Eq Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

(==) :: Month -> Month -> Bool #

(/=) :: Month -> Month -> Bool #

Ord Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

compare :: Month -> Month -> Ordering #

(<) :: Month -> Month -> Bool #

(<=) :: Month -> Month -> Bool #

(>) :: Month -> Month -> Bool #

(>=) :: Month -> Month -> Bool #

max :: Month -> Month -> Month #

min :: Month -> Month -> Month #

SymVal Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

HasKind Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

SatModel Month Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

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

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

data Day Source #

Days. Again, only the ones mentioned in the puzzle.

Constructors

D14 
D15 
D16 
D17 
D18 
D19 

Instances

Instances details
Data Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

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

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

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Show Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Eq Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Ord Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

SymVal Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

HasKind Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

SatModel Day Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.Birthday

Methods

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

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

type SMonth = SBV Month Source #

Symbolic version of the type Month.

sMay :: SBV Month Source #

Symbolic version of the constructor May.

sJun :: SBV Month Source #

Symbolic version of the constructor Jun.

sJul :: SBV Month Source #

Symbolic version of the constructor Jul.

sAug :: SBV Month Source #

Symbolic version of the constructor Aug.

type SDay = SBV Day Source #

Symbolic version of the type Day.

sD14 :: SBV Day Source #

Symbolic version of the constructor D14.

sD15 :: SBV Day Source #

Symbolic version of the constructor D15.

sD16 :: SBV Day Source #

Symbolic version of the constructor D16.

sD17 :: SBV Day Source #

Symbolic version of the constructor D17.

sD18 :: SBV Day Source #

Symbolic version of the constructor D18.

sD19 :: SBV Day Source #

Symbolic version of the constructor D19.

data Birthday Source #

Represent the birthday as a record

Constructors

BD SMonth SDay 

mkBirthday :: Symbolic Birthday Source #

Make a valid symbolic birthday

valid :: Birthday -> SBool Source #

Is this a valid birthday? i.e., one that was declared by Cheryl to be a possibility.

The puzzle

puzzle :: ConstraintSet Source #

Encode the conversation as given in the puzzle.

NB. Lee Pike pointed out that not all the constraints are actually necessary! (Private communication.) The puzzle still has a unique solution if the statements a1 and b1 (i.e., Albert and Bernard saying they themselves do not know the answer) are removed. To experiment you can simply comment out those statements and observe that there still is a unique solution. Thanks to Lee for pointing this out! In fact, it is instructive to assert the conversation line-by-line, and see how the search-space gets reduced in each step.

cheryl :: IO () Source #

Find all solutions to the birthday problem. We have:

>>> cheryl
Solution #1:
  birthMonth = Jul :: Month
  birthDay   = D16 :: Day
This is the only solution.