Skip to content

Commit 0c3e702

Browse files
committed
copilot-language: Preserve proposition quantifiers. Refs #254.
Currently, `copilot-language` remembers whether a proposition (i.e., a stream of booleans) is quantified universally (i.e., using `forAll`) or existentially (i.e., using `exists`). When translating from `copilot-language` to `copilot-core`, however, the quantifier is discarded. This means that a `copilot-core` `Property` does not record any quantifier information at all, making it impossible for downstream libraries that use `copilot-core` to handle universal quantification differently from existential quantification. Now that `copilot-core` preserves quantifier information in its API, this commit updates `copilot-language` to respect quantifiers when translating into `copilot-core`.
1 parent 5b08e81 commit 0c3e702

File tree

3 files changed

+35
-8
lines changed

3 files changed

+35
-8
lines changed

copilot-language/src/Copilot/Language/Analyze.hs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,11 @@ analyzeObserver refStreams (Observer _ e) = analyzeExpr refStreams e
110110
--
111111
-- This function can fail with one of the exceptions in 'AnalyzeException'.
112112
analyzeProperty :: IORef Env -> Property -> IO ()
113-
analyzeProperty refStreams (Property _ e) = analyzeExpr refStreams e
113+
analyzeProperty refStreams (Property _ p) =
114+
-- Soundness note: it is OK to call `extractProp` here to drop the quantifier
115+
-- from the proposition `p`, as the analysis does not depend on what the
116+
-- quantifier is.
117+
analyzeExpr refStreams (extractProp p)
114118

115119
data SeenExtern = NoExtern
116120
| SeenFun
@@ -291,7 +295,12 @@ specExts refStreams spec = do
291295
env' args
292296

293297
propertyExts :: ExternEnv -> Property -> IO ExternEnv
294-
propertyExts env (Property _ stream) = collectExts refStreams stream env
298+
propertyExts env (Property _ p) =
299+
-- Soundness note: it is OK to call `extractProp` here to drop the
300+
-- quantifier from the proposition `p`. This is because we are simply
301+
-- gathering externs from `p`, and the presence of externs does not depend
302+
-- on what the quantifier is.
303+
collectExts refStreams (extractProp p) env
295304

296305
theoremExts :: ExternEnv -> (Property, UProof) -> IO ExternEnv
297306
theoremExts env (p, _) = propertyExts env p

copilot-language/src/Copilot/Language/Reify.hs

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
-- specification.
55

66
{-# LANGUAGE ExistentialQuantification #-}
7+
{-# LANGUAGE GADTs #-}
78
{-# LANGUAGE Rank2Types #-}
89
{-# LANGUAGE Safe #-}
910

@@ -105,11 +106,22 @@ mkProperty
105106
-> IORef [Core.Stream]
106107
-> Property
107108
-> IO Core.Property
108-
mkProperty refMkId refStreams refMap (Property name guard) = do
109-
w1 <- mkExpr refMkId refStreams refMap guard
109+
mkProperty refMkId refStreams refMap (Property name p) = do
110+
p' <- mkProp refMkId refStreams refMap p
110111
return Core.Property
111112
{ Core.propertyName = name
112-
, Core.propertyExpr = w1 }
113+
, Core.propertyProp = p' }
114+
115+
-- | Transform a Copilot proposition into a Copilot Core proposition.
116+
mkProp :: IORef Int
117+
-> IORef (Map Core.Id)
118+
-> IORef [Core.Stream]
119+
-> Prop a
120+
-> IO Core.Prop
121+
mkProp refMkId refStreams refMap prop =
122+
case prop of
123+
Forall e -> Core.Forall <$> mkExpr refMkId refStreams refMap e
124+
Exists e -> Core.Exists <$> mkExpr refMkId refStreams refMap e
113125

114126
-- | Transform a Copilot stream expression into a Copilot Core expression.
115127
{-# INLINE mkExpr #-}

copilot-language/src/Copilot/Language/Spec.hs

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -153,7 +153,7 @@ trigger name e args = tell [TriggerItem $ Trigger name e args]
153153
-- | A property, representing a boolean stream that is existentially or
154154
-- universally quantified over time.
155155
data Property where
156-
Property :: String -> Stream Bool -> Property
156+
Property :: String -> Prop a -> Property
157157

158158
-- | A proposition, representing the quantification of a boolean streams over
159159
-- time.
@@ -170,6 +170,12 @@ exists :: Stream Bool -> Prop Existential
170170
exists = Exists
171171

172172
-- | Extract the underlying stream from a quantified proposition.
173+
--
174+
-- Think carefully before using this function, as this function will remove the
175+
-- quantifier from a proposition. Universally quantified streams usually require
176+
-- separate treatment from existentially quantified ones, so carelessly using
177+
-- this function to remove quantifiers can result in hard-to-spot soundness
178+
-- bugs.
173179
extractProp :: Prop a -> Stream Bool
174180
extractProp (Forall p) = p
175181
extractProp (Exists p) = p
@@ -180,15 +186,15 @@ extractProp (Exists p) = p
180186
-- This function returns, in the monadic context, a reference to the
181187
-- proposition.
182188
prop :: String -> Prop a -> Writer [SpecItem] (PropRef a)
183-
prop name e = tell [PropertyItem $ Property name (extractProp e)]
189+
prop name e = tell [PropertyItem $ Property name e]
184190
>> return (PropRef name)
185191

186192
-- | A theorem, or proposition together with a proof.
187193
--
188194
-- This function returns, in the monadic context, a reference to the
189195
-- proposition.
190196
theorem :: String -> Prop a -> Proof a -> Writer [SpecItem] (PropRef a)
191-
theorem name e (Proof p) = tell [TheoremItem (Property name (extractProp e), p)]
197+
theorem name e (Proof p) = tell [TheoremItem (Property name e, p)]
192198
>> return (PropRef name)
193199

194200
-- | Construct a function argument from a stream.

0 commit comments

Comments
 (0)