module Ersatz.Bit
( Bit(..)
, assert
, Boolean(..)
) where
import Prelude hiding ((&&),(||),not,and,or,all,any)
import qualified Prelude
import Control.Applicative
import Control.Monad.State
import Data.Foldable (Foldable, toList)
import qualified Data.Foldable as Foldable
import Data.Sequence (Seq, (<|), (|>), (><))
import qualified Data.Sequence as Seq
import Data.Typeable
import Ersatz.Decoding
import Ersatz.Encoding
import Ersatz.Internal.Formula
import Ersatz.Internal.Literal
import Ersatz.Internal.StableName
import Ersatz.Problem
import Ersatz.Solution
import Ersatz.Variable
import GHC.Generics
import System.IO.Unsafe
infixr 3 &&, &&#
infixr 2 ||, ||#
infixr 0 ==>
data Bit
= And (Seq Bit)
| Or (Seq Bit)
| Xor Bit Bit
| Mux Bit Bit Bit
| Not Bit
| Var !Literal
deriving (Show, Typeable)
instance Boolean Bit where
bool True = true
bool False = false
true = Var literalTrue
false = Var literalFalse
a@(Var (Literal (1))) && _ = a
_ && b@(Var (Literal (1))) = b
a && Var (Literal 1) = a
Var (Literal 1) && b = b
And as && And bs = And (as >< bs)
And as && b = And (as |> b)
a && And bs = And (a <| bs)
a && b = And (a <| b <| Seq.empty)
a || Var (Literal (1)) = a
Var (Literal (1)) || b = b
a@(Var (Literal 1)) || _ = a
_ || b@(Var (Literal 1)) = b
Or as || Or bs = Or (as >< bs)
Or as || b = Or (as |> b)
a || Or bs = Or (a <| bs)
a || b = Or (a <| b <| Seq.empty)
not (Not c) = c
not (Var l) = Var (negateLiteral l)
not c = Not c
a `xor` Var (Literal (1)) = a
Var (Literal (1)) `xor` b = b
a `xor` Var (Literal 1) = not a
Var (Literal 1) `xor` b = not b
a `xor` b = Xor a b
and = Foldable.foldl' (&&) true
or = Foldable.foldl' (||) false
all p = Foldable.foldl' (\res b -> res && p b) true
any p = Foldable.foldl' (\res b -> res || p b) false
choose f _ (Var (Literal (1))) = f
choose _ t (Var (Literal 1)) = t
choose f t s = Mux f t s
instance Variable Bit where
exists = liftM Var exists
#ifndef HLINT
forall = liftM Var forall
#endif
instance Decoding Bit where
type Decoded Bit = Bool
decode sol b
= solutionStableName sol (unsafePerformIO (makeStableName' b))
<|> case b of
And cs -> andMaybeBools . toList $ decode sol <$> cs
Or cs -> orMaybeBools . toList $ decode sol <$> cs
Xor x y -> xor <$> decode sol x <*> decode sol y
Mux cf ct cp -> do
p <- decode sol cp
decode sol $ if p then ct else cf
Not c' -> not <$> decode sol c'
Var l -> decode sol l
where
andMaybeBools :: [Maybe Bool] -> Maybe Bool
andMaybeBools mbs
| any not knowns = Just False
| null unknowns = Just True
| otherwise = Nothing
where
(unknowns, knowns) = partitionMaybes mbs
orMaybeBools :: [Maybe Bool] -> Maybe Bool
orMaybeBools mbs
| or knowns = Just True
| null unknowns = Just False
| otherwise = Nothing
where
(unknowns, knowns) = partitionMaybes mbs
partitionMaybes :: [Maybe a] -> ([()], [a])
partitionMaybes = foldr go ([],[])
where
go Nothing ~(ns, js) = (():ns, js)
go (Just a) ~(ns, js) = (ns, a:js)
instance Encoding Bit where
type Encoded Bit = Bool
encode = bool
assert :: (MonadState s m, HasSAT s) => Bit -> m ()
assert b = do
l <- runBit b
assertFormula (formulaLiteral l)
runBit :: (MonadState s m, HasSAT s) => Bit -> m Literal
runBit (Not c) = negateLiteral `liftM` runBit c
runBit (Var l) = return l
runBit b = generateLiteral b $ \out ->
assertFormula =<< case b of
And bs -> formulaAnd out `liftM` mapM runBit (toList bs)
Or bs -> formulaOr out `liftM` mapM runBit (toList bs)
Xor x y -> liftM2 (formulaXor out) (runBit x) (runBit y)
Mux x y p -> liftM3 (formulaMux out) (runBit x) (runBit y) (runBit p)
Not _ -> error "Unreachable"
Var _ -> error "Unreachable"
class GBoolean f where
gbool :: Bool -> f a
(&&#) :: f a -> f a -> f a
(||#) :: f a -> f a -> f a
gnot :: f a -> f a
gall :: Foldable t => (a -> f b) -> t a -> f b
gany :: Foldable t => (a -> f b) -> t a -> f b
gxor :: f a -> f a -> f a
instance GBoolean U1 where
gbool _ = U1
U1 &&# U1 = U1
U1 ||# U1 = U1
gnot U1 = U1
gall _ _ = U1
gany _ _ = U1
gxor _ _ = U1
instance (GBoolean f, GBoolean g) => GBoolean (f :*: g) where
gbool x = gbool x :*: gbool x
(a :*: b) &&# (c :*: d) = (a &&# c) :*: (b &&# d)
(a :*: b) ||# (c :*: d) = (a ||# c) :*: (b ||# d)
gnot (a :*: b) = gnot a :*: gnot b
gall p xs = gall id ls :*: gall id rs
where (ls, rs) = gunzip . map p . toList $ xs
gany p xs = gany id ls :*: gany id rs
where (ls, rs) = gunzip . map p . toList $ xs
gxor (a :*: b) (c :*: d) = gxor a c :*: gxor b d
instance Boolean a => GBoolean (K1 i a) where
gbool = K1 . bool
K1 a &&# K1 b = K1 (a && b)
K1 a ||# K1 b = K1 (a || b)
gnot (K1 a) = K1 (not a)
gall p as = K1 (all (unK1 . p) as)
gany p as = K1 (any (unK1 . p) as)
gxor (K1 a) (K1 b) = K1 (xor a b)
instance GBoolean a => GBoolean (M1 i c a) where
gbool = M1 . gbool
M1 a &&# M1 b = M1 (a &&# b)
M1 a ||# M1 b = M1 (a ||# b)
gnot (M1 a) = M1 (gnot a)
gall p as = M1 (gall (unM1 . p) as)
gany p as = M1 (gany (unM1 . p) as)
gxor (M1 a) (M1 b) = M1 (gxor a b)
class Boolean b where
bool :: Bool -> b
true :: b
true = bool True
false :: b
false = bool False
(&&) :: b -> b -> b
(||) :: b -> b -> b
(==>) :: b -> b -> b
x ==> y = not x || y
not :: b -> b
and :: Foldable t => t b -> b
and = Ersatz.Bit.all id
or :: Foldable t => t b -> b
or = Ersatz.Bit.any id
nand :: Foldable t => t b -> b
nand = not . and
nor :: Foldable t => t b -> b
nor = not . or
all :: (Foldable t, Boolean b) => (a -> b) -> t a -> b
any :: (Foldable t, Boolean b) => (a -> b) -> t a -> b
xor :: b -> b -> b
choose :: b
-> b
-> b
-> b
choose f t s = (f && not s) || (t && s)
#ifndef HLINT
default bool :: (Generic b, GBoolean (Rep b)) => Bool -> b
bool = to . gbool
default (&&) :: (Generic b, GBoolean (Rep b)) => b -> b -> b
x && y = to (from x &&# from y)
default (||) :: (Generic b, GBoolean (Rep b)) => b -> b -> b
x || y = to (from x ||# from y)
default not :: (Generic b, GBoolean (Rep b)) => b -> b
not = to . gnot . from
default all :: (Foldable t, Generic b, GBoolean (Rep b)) => (a -> b) -> t a -> b
all p = to . gall (from . p)
default any :: (Foldable t, Generic b, GBoolean (Rep b)) => (a -> b) -> t a -> b
any p = to . gany (from . p)
default xor :: (Generic b, GBoolean (Rep b)) => b -> b -> b
xor x y = to (from x `gxor` from y)
#endif
instance Boolean Bool where
bool = id
true = True
false = False
(&&) = (Prelude.&&)
(||) = (Prelude.||)
not = Prelude.not
and = Foldable.and
or = Foldable.or
all = Foldable.all
any = Foldable.any
xor = (/=)
choose f _ False = f
choose _ t True = t
gunzip :: [(f :*: g) a] -> ([f a], [g a])
gunzip = foldr go ([],[])
where go (a :*: b) ~(as, bs) = (a:as, b:bs)