Last active
March 22, 2021 15:56
-
-
Save LeventErkok/66594d8e94dc0ab2ebffffe4fdabccc9 to your computer and use it in GitHub Desktop.
To Mock a Mockingbird puzzle in Haskell/SBV
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- A Haskell solution to: | |
-- | |
-- https://stackoverflow.com/questions/53711168/modelling-a-logic-puzzle | |
-- | |
{-# LANGUAGE TemplateHaskell #-} | |
{-# LANGUAGE StandaloneDeriving #-} | |
{-# LANGUAGE DeriveDataTypeable #-} | |
{-# LANGUAGE DeriveAnyClass #-} | |
import Data.SBV | |
import Data.List | |
data Color = R | Y | B | |
mkSymbolicEnumeration ''Color | |
type Flower = SInteger | |
col :: Flower -> SColor | |
col = uninterpret "col" | |
validPick :: SInteger -> Flower -> Flower -> Flower -> SBool | |
validPick n i j k = distinct [i, j, k] .&& sAll ok [i, j, k] | |
where ok x = inRange x (1, n) | |
count :: Color -> [Flower] -> SInteger | |
count c fs = sum [ite (col f .== literal c) 1 0 | f <- fs] | |
puzzle :: Goal | |
puzzle = do n <- sInteger "N" | |
let valid = validPick n | |
ef1 <- exists "ef1_modelIgnore" | |
ef2 <- exists "ef2_modelIgnore" | |
ef3 <- exists "ef3_modelIgnore" | |
af1 <- forall "af1" | |
af2 <- forall "af2" | |
af3 <- forall "af3" | |
constrain $ valid ef1 ef2 ef3 | |
constrain $ map col [ef1, ef2, ef3] .== map literal [R, Y, B] | |
constrain $ valid af1 af2 af3 .=> count R [af1, af2, af3] .>= 1 | |
constrain $ valid af1 af2 af3 .=> count Y [af1, af2, af3] .>= 1 | |
constrain $ valid af1 af2 af3 .=> count B [af1, af2, af3] .== 1 | |
-- *Main> main | |
-- Solution #1: | |
-- N = 3 :: Integer | |
-- This is the only solution. (Unique up to prefix existentials.) | |
main :: IO () | |
main = print =<< allSatWith cfg puzzle | |
where cfg = z3{satTrackUFs=False, isNonModelVar = ("_modelIgnore" `isSuffixOf`)} |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment