{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Documentation.SBV.Examples.Misc.Tuple where
import Data.SBV
import Data.SBV.Tuple
import Data.SBV.Control
import Prelude hiding ((!!))
import Data.SBV.List ((!!))
import Data.SBV.RegExp
import qualified Data.SBV.String as S
import qualified Data.SBV.List as L
type Dict a b = SBV [(a, b)]
example :: IO [(String, Integer)]
example :: IO [(String, Integer)]
example = Symbolic [(String, Integer)] -> IO [(String, Integer)]
forall a. Symbolic a -> IO a
runSMT (Symbolic [(String, Integer)] -> IO [(String, Integer)])
-> Symbolic [(String, Integer)] -> IO [(String, Integer)]
forall a b. (a -> b) -> a -> b
$ do dict :: Dict String Integer <- String -> Symbolic (Dict String Integer)
forall a. SymVal a => String -> Symbolic (SBV a)
free String
"dict"
let len = Int
5 :: Int
range = [Int
0 .. Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
constrain $ L.length dict .== fromIntegral len
let goodKey a
i SBV String
s = let l :: SInteger
l = SBV String -> SInteger
S.length SBV String
s
r :: RegExp
r = RegExp
asciiLower RegExp -> RegExp -> RegExp
forall a. Num a => a -> a -> a
* RegExp -> RegExp
KStar (RegExp
asciiLetter RegExp -> RegExp -> RegExp
forall a. Num a => a -> a -> a
+ RegExp
digit RegExp -> RegExp -> RegExp
forall a. Num a => a -> a -> a
+ RegExp
"_" RegExp -> RegExp -> RegExp
forall a. Num a => a -> a -> a
+ RegExp
"'")
in SInteger
l SInteger -> SInteger -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== a -> SInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
iSInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
+SInteger
3 SBool -> SBool -> SBool
.&& SBV String
s SBV String -> RegExp -> SBool
forall a. RegExpMatchable a => a -> RegExp -> SBool
`match` RegExp
r
restrict a
i = case SBV (String, Integer) -> (SBV String, SInteger)
forall tup a. Tuple tup a => SBV tup -> a
untuple (Dict String Integer
dict Dict String Integer -> SInteger -> SBV (String, Integer)
forall a. SymVal a => SList a -> SInteger -> SBV a
!! a -> SInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i) of
(SBV String
k, SInteger
v) -> SBool -> m ()
forall a. QuantifiedBool a => a -> m ()
forall (m :: * -> *) a.
(SolverContext m, QuantifiedBool a) =>
a -> m ()
constrain (SBool -> m ()) -> SBool -> m ()
forall a b. (a -> b) -> a -> b
$ a -> SBV String -> SBool
forall {a}. Integral a => a -> SBV String -> SBool
goodKey a
i SBV String
k SBool -> SBool -> SBool
.&& SInteger
v SInteger -> SInteger -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== SBV String -> SInteger
S.length SBV String
k
mapM_ restrict range
let keys = [(Dict String Integer
dict Dict String Integer -> SInteger -> SBV (String, Integer)
forall a. SymVal a => SList a -> SInteger -> SBV a
!! Int -> SInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)SBV (String, Integer)
-> (SBV (String, Integer) -> SBV String) -> SBV String
forall a b. a -> (a -> b) -> b
^.SBV (String, Integer) -> SBV String
forall b a. HasField "_1" b a => SBV a -> SBV b
_1 | Int
i <- [Int]
range]
constrain $ distinct keys
query $ do ensureSat
getValue dict