{-# LANGUAGE OverloadedStrings #-}
module Documentation.SBV.Examples.Strings.RegexCrossword where
import Data.List (genericLength, transpose)
import Data.SBV
import Data.SBV.Control
import qualified Data.SBV.String as S
import qualified Data.SBV.RegExp as R
solveCrossword :: [R.RegExp] -> [R.RegExp] -> IO [String]
solveCrossword rowRegExps colRegExps = runSMT $ do
let numRows = genericLength rowRegExps
numCols = genericLength colRegExps
let mkRow rowRegExp = do row <- free_
constrain $ row `R.match` rowRegExp
constrain $ S.length row .== literal numCols
return row
rows <- mapM mkRow rowRegExps
let mkCol colRegExp = do col <- free_
constrain $ col `R.match` colRegExp
constrain $ S.length col .== literal numRows
return col
cols <- mapM mkCol colRegExps
let rowss = [[r .!! literal i | i <- [0..numCols-1]] | r <- rows]
let colss = transpose [[c .!! literal i | i <- [0..numRows-1]] | c <- cols]
constrain $ bAnd $ zipWith (.==) (concat rowss) (concat colss)
query $ do cs <- checkSat
case cs of
Unk -> error "Solver returned unknown!"
Unsat -> error "There are no solutions to this puzzle!"
Sat -> mapM getValue rows
puzzle1 :: IO [String]
puzzle1 = solveCrossword rs cs
where rs = [ R.KStar (R.oneOf "NOTAD")
, "WEL" + "BAL" + "EAR"
]
cs = [ "UB" + "IE" + "AW"
, R.KStar (R.oneOf "TUBE")
, R.oneOf "BORF" * R.All
]
puzzle2 :: IO [String]
puzzle2 = solveCrossword rs cs
where rs = [ R.KPlus (R.oneOf "AWE")
, R.KPlus (R.oneOf "ALP") * "K"
, "PR" + "ER" + "EP"
]
cs = [ R.oneOf "BQW" * ("PR" + "LE")
, R.KPlus (R.oneOf "RANK")
]
puzzle3 :: IO [String]
puzzle3 = solveCrossword rs cs
where rs = [ R.KStar (R.oneOf "TRASH")
, ("FA" + "AB") * R.KStar (R.oneOf "TUP")
, R.KStar ("BA" + "TH" + "TU")
, R.KStar R.All * "A" * R.KStar R.All
]
cs = [ R.KStar ("TS" + "RA" + "QA")
, R.KStar ("AB" + "UT" + "AR")
, ("K" + "T") * "U" * R.KStar R.All * ("A" + "R")
, R.KPlus ("AR" + "FS" + "ST")
]