{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Tools.STree (STree, readSTree, writeSTree, mkSTree) where
import Data.SBV.Core.Data
import Data.SBV.Core.Model
import Data.Proxy
type STree i e = STreeInternal (SBV i) (SBV e)
data STreeInternal i e = SLeaf e
| SBin (STreeInternal i e) (STreeInternal i e)
deriving Int -> STreeInternal i e -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall i e. Show e => Int -> STreeInternal i e -> ShowS
forall i e. Show e => [STreeInternal i e] -> ShowS
forall i e. Show e => STreeInternal i e -> String
showList :: [STreeInternal i e] -> ShowS
$cshowList :: forall i e. Show e => [STreeInternal i e] -> ShowS
show :: STreeInternal i e -> String
$cshow :: forall i e. Show e => STreeInternal i e -> String
showsPrec :: Int -> STreeInternal i e -> ShowS
$cshowsPrec :: forall i e. Show e => Int -> STreeInternal i e -> ShowS
Show
instance SymVal e => Mergeable (STree i e) where
symbolicMerge :: Bool -> SBool -> STree i e -> STree i e -> STree i e
symbolicMerge Bool
f SBool
b (SLeaf SBV e
i) (SLeaf SBV e
j) = forall i e. e -> STreeInternal i e
SLeaf (forall a. Mergeable a => Bool -> SBool -> a -> a -> a
symbolicMerge Bool
f SBool
b SBV e
i SBV e
j)
symbolicMerge Bool
f SBool
b (SBin STree i e
l STree i e
r) (SBin STree i e
l' STree i e
r') = forall i e.
STreeInternal i e -> STreeInternal i e -> STreeInternal i e
SBin (forall a. Mergeable a => Bool -> SBool -> a -> a -> a
symbolicMerge Bool
f SBool
b STree i e
l STree i e
l') (forall a. Mergeable a => Bool -> SBool -> a -> a -> a
symbolicMerge Bool
f SBool
b STree i e
r STree i e
r')
symbolicMerge Bool
_ SBool
_ STree i e
_ STree i e
_ = forall a. HasCallStack => String -> a
error String
"SBV.STree.symbolicMerge: Impossible happened while merging states"
readSTree :: (SFiniteBits i, SymVal e) => STree i e -> SBV i -> SBV e
readSTree :: forall i e.
(SFiniteBits i, SymVal e) =>
STree i e -> SBV i -> SBV e
readSTree STree i e
s SBV i
i = forall {e} {i}. Mergeable e => [SBool] -> STreeInternal i e -> e
walk (forall a. SFiniteBits a => SBV a -> [SBool]
blastBE SBV i
i) STree i e
s
where walk :: [SBool] -> STreeInternal i e -> e
walk [] (SLeaf e
v) = e
v
walk (SBool
b:[SBool]
bs) (SBin STreeInternal i e
l STreeInternal i e
r) = forall a. Mergeable a => SBool -> a -> a -> a
ite SBool
b ([SBool] -> STreeInternal i e -> e
walk [SBool]
bs STreeInternal i e
r) ([SBool] -> STreeInternal i e -> e
walk [SBool]
bs STreeInternal i e
l)
walk [SBool]
_ STreeInternal i e
_ = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"SBV.STree.readSTree: Impossible happened while reading: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show SBV i
i
writeSTree :: (SFiniteBits i, SymVal e) => STree i e -> SBV i -> SBV e -> STree i e
writeSTree :: forall i e.
(SFiniteBits i, SymVal e) =>
STree i e -> SBV i -> SBV e -> STree i e
writeSTree STreeInternal (SBV i) (SBV e)
s SBV i
i SBV e
j = forall {i}.
Mergeable (STreeInternal i (SBV e)) =>
[SBool] -> STreeInternal i (SBV e) -> STreeInternal i (SBV e)
walk (forall a. SFiniteBits a => SBV a -> [SBool]
blastBE SBV i
i) STreeInternal (SBV i) (SBV e)
s
where walk :: [SBool] -> STreeInternal i (SBV e) -> STreeInternal i (SBV e)
walk [] STreeInternal i (SBV e)
_ = forall i e. e -> STreeInternal i e
SLeaf SBV e
j
walk (SBool
b:[SBool]
bs) (SBin STreeInternal i (SBV e)
l STreeInternal i (SBV e)
r) = forall i e.
STreeInternal i e -> STreeInternal i e -> STreeInternal i e
SBin (forall a. Mergeable a => SBool -> a -> a -> a
ite SBool
b STreeInternal i (SBV e)
l ([SBool] -> STreeInternal i (SBV e) -> STreeInternal i (SBV e)
walk [SBool]
bs STreeInternal i (SBV e)
l)) (forall a. Mergeable a => SBool -> a -> a -> a
ite SBool
b ([SBool] -> STreeInternal i (SBV e) -> STreeInternal i (SBV e)
walk [SBool]
bs STreeInternal i (SBV e)
r) STreeInternal i (SBV e)
r)
walk [SBool]
_ STreeInternal i (SBV e)
_ = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"SBV.STree.writeSTree: Impossible happened while reading: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show SBV i
i
mkSTree :: forall i e. HasKind i => [SBV e] -> STree i e
mkSTree :: forall i e. HasKind i => [SBV e] -> STree i e
mkSTree [SBV e]
ivals
| forall a. HasKind a => a -> Bool
isReal (forall {k} (t :: k). Proxy t
Proxy @i)
= forall a. HasCallStack => String -> a
error String
"SBV.STree.mkSTree: Cannot build a real-valued sized tree"
| Bool -> Bool
not (forall a. HasKind a => a -> Bool
isBounded (forall {k} (t :: k). Proxy t
Proxy @i))
= forall a. HasCallStack => String -> a
error String
"SBV.STree.mkSTree: Cannot build an infinitely large tree"
| Int
reqd forall a. Eq a => a -> a -> Bool
/= Int
given
= forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"SBV.STree.mkSTree: Required " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
reqd forall a. [a] -> [a] -> [a]
++ String
" elements, received: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
given
| Bool
True
= forall {e} {i}. [e] -> STreeInternal i e
go [SBV e]
ivals
where reqd :: Int
reqd = Int
2 forall a b. (Num a, Integral b) => a -> b -> a
^ forall a. HasKind a => a -> Int
intSizeOf (forall {k} (t :: k). Proxy t
Proxy @i)
given :: Int
given = forall (t :: * -> *) a. Foldable t => t a -> Int
length [SBV e]
ivals
go :: [e] -> STreeInternal i e
go [] = forall a. HasCallStack => String -> a
error String
"SBV.STree.mkSTree: Impossible happened, ran out of elements"
go [e
l] = forall i e. e -> STreeInternal i e
SLeaf e
l
go [e]
ns = let ([e]
l, [e]
r) = forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [e]
ns forall a. Integral a => a -> a -> a
`div` Int
2) [e]
ns in forall i e.
STreeInternal i e -> STreeInternal i e -> STreeInternal i e
SBin ([e] -> STreeInternal i e
go [e]
l) ([e] -> STreeInternal i e
go [e]
r)