Skip to content

Conversation

@sauclovian-g
Copy link
Contributor

This is not done yet; I just want a full CI run as a precaution...

(note for when it is done: there's a lot here and you'll almost certainly want to review one commit at a time)

@sauclovian-g sauclovian-g force-pushed the rationalize-repl branch 2 times, most recently from 108e6b2 to c249a64 Compare October 31, 2025 07:14
@sauclovian-g
Copy link
Contributor Author

Provided it doesn't break, I think it's about time to merge this one.

@sauclovian-g sauclovian-g marked this pull request as ready for review October 31, 2025 08:05
Comment on lines 9 to 16
module SAWScript.REPL.Trie (
Trie,
empty,
insert,
lookup,
lookupWithExact,
leaves
) where
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It might be worth adding some module Haddocks where saying that SAWScript.REPL.Trie is intended to be imported qualified, given that it exports some commonly-used function names like empty, insert, and lookup.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Fixed.

searchCmd :: Text -> REPL ()
searchCmd str
| null str = do io $ putStrLn $ "[error] :search requires at least one argument"
| Text.null str = io $ putStrLn $ "[error] :search requires at least one argument"
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Redundant $:

-  | Text.null str = io $ putStrLn $ "[error] :search requires at least one argument"
+  | Text.null str = io $ putStrLn "[error] :search requires at least one argument"

Similarly for cdCmd.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Fixed. The one disappeared, but apparently not the other.

Comment on lines 60 to 69
let subnode = case Map.lookup c tbl of
Nothing -> empty
Just n -> n
subnode' = insert' key' subnode
in
Node (Map.insert c subnode' tbl) mbValue
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This uses Map.lookup/Map.insert to replace Map.alter, the latter of which is a single, fused O(log n) operation that will likely be more efficient than the former, which use two separate O(log n) operations. I would prefer using Map.alter unless you have a compelling reason not to.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

To me it's clearer this way, or at least not as messy, and since there are about half a dozen REPL commands that's all the thing is used for, it can't possibly matter...

import qualified Lang.Crucible.FunctionHandle as Crucible


deriving instance Typeable AIG.Proxy
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

FYI: Typeable instances are automatically derived for all data types since GHC 7.10, since there's no need to keep this explicit Typeable instance around. (In fact, recent versions of GHC will warn if you try to do this.)

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Removed, along with a few others that are floating about.

Stability : provisional
-}
{-# LANGUAGE OverloadedStrings #-}
-- TODO RGS: Do better (or at least comment why we do this)
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thank you for fixing this! I'm embarrassed that I accidentally checked this comment in :)

, rTopLevelRW :: IORef TopLevelRW
, rProofState :: Maybe (IORef ProofState)
, rTopLevelRW :: TopLevelRW
, rProofState :: Maybe ProofState
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It might be worth documenting under what conditions one can expect this field to be Just. Some of the panics introduced elsewhere in this comment talk about a "ProofScript mode", which seems relevant here.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Good thought. Done

Comment on lines 59 to 68
-- found, load it. If not, raise an error.
findAndLoadFile :: Options -> FilePath -> IO [Stmt]
findAndLoadFile :: Options -> FilePath -> IO (Either [Text] [Stmt])
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

A minor thing, but after these changes, this function no longer raises an error (as claimed in the Haddocks), but instead returns an error (via Left).

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Fixed


-- | Load the 'Stmt's in a @.saw@ file.
loadFile :: Options -> FilePath -> IO (Either [Text] [Stmt])
loadFile :: Options.Options -> FilePath -> IO (Either [Text] [Stmt])
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It might be worth having a separate import SAWCentral.Options (Options) statement so that we don't have to repeat ourselves in writing Options.Options.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Fixed

It looks like if GH thinks a file is deleted (even if it was actually renamed and the rename matching can't figure it out across the whole patch set) that it doesn't display the comments on it in the diff view. Sigh

-- A few more misc commands

, prim "sharpSAT" "Term -> TopLevel Integer"
, prim "sharpSAT" "Term -> TopLevel Int"
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

FYI, some of the test cases' expected output needs to be updated as a result of this change.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Fixed

@sauclovian-g
Copy link
Contributor Author

force-push: fix routine test failures and rebase on master.

The test2314 failure is a real bug and needs further analysis.

@sauclovian-g
Copy link
Contributor Author

force-push: fix the problem with test2314 (misplaced catch) and also apply one of the cosmetic review comments.

@sauclovian-g
Copy link
Contributor Author

Also, the last three of the changes listed before the force-push aren't actually part of it. (Thanks, GH...)

They address the rest of the review comments so far.

@sauclovian-g
Copy link
Contributor Author

ok, that's strange, a message got an extra space in it? and broke test_search... ah I see why, mistake in the 80-columns patch, I'll fix it Monday

Should have been part of #2752. (Oops.)
Also add an export list. There should always be an export list.

NFCI.
No functional change intended, except:
   - I fixed a typo in a string constant
   - use the correct panic module in Trie.hs
For git safety this commit contains only the rename; build changes are
next.
The only AIGProxy ever passed to this is compactProxy, so don't waste
brain cycles on threading that through the REPL logic.

Also, nothing uses the returned BuiltinContext so don't bother
returning it.

NFCI
It's not obvious if they're the same (they are) or which one should be
used when. Just use "liftIO" as it's standard, even though it costs a
bit more to type.

NFCI
It contains some IORefs, but it's not at all clear why it does when
it's already a state monad of its own, and I think I'm going to remove
them.

NFCI
It's already a state monad; the refs are pointless.
Boot the rest out, mostly into a new file SAWScript.REPL.Data, so
named because it provides code that inspects the data in the REPL
state.

NFCI
No actual changes, just move text around.
Split the data extraction part (move to Data.hs) from the printing
part.
For now, shift the throws to the callers. This might get rearranged
later, but for the moment I'm about to add more stuff to this module
that has different caller requirements and I'd like it to all be
uniform.

The state of the chewing gum currently serving as SAW's exception
handling is such that this changes the way parse errors print. (The
whitespace is different and there's now a vacuous stack trace like
type errors generate.) Accept this for now and update all the affected
test reference outputs.
Now it's the only place that calls directly into the lexer and parser.

There wasn't any code that was doing anything inappropriate with the
lexer output, or anything besides feeding it directly to the parser;
but on the other hand there's no reason to have five copies of that
logic across three modules.

NFCI
Rename readSchema to readSchemaPure because unlike all the other
entry points it doesn't need IO. (It panics on any errors because
it's used to handle types in the builtins table.)
Move that check out of the caller.

This is somewhat ugly on the Import side for various reasons.
Condensing it will happen later.
Move that check out of the caller.

This is also somewhat ugly on the Import side for various reasons.
Condensing it will happen later.
It was "Term -> TopLevel Integer" rather than "Term -> TopLevel Int".

There is no type "Integer"; we weren't checking that the types of
builtins are well formed. That's about to change.

Update the affected test reference outputs.
There was no check in the caller; we were assuming all of the types of
builtins were valid, and as noted in the previous commit one of them
wasn't. "Oops"

Beware: the check is only evaluated if something actually looks at the
type. Running :search or :env is sufficient (and we have tests that do
that) but just starting SAW with a bad type in the builtins table will
not panic.

(I tried adding some strictness notations and that didn't help; but I
think detecting problems on any :search or :env run is probably
acceptable so didn't try that hard.)
Instead of calling out the functions that call the typechecker as
"checked", call out the ones that don't as "unchecked". NFCI.

Currently the only uses that do not call the typechecker are the ones
that lead into the interpreter's statement-at-a-time execution, and
that's going to require other more involved cleanup before it can be
made to go away.
"import" is the wrong terminology, as in SAWScript "import" means
importing Cryptol. "Loader" seems like a good alternative.

For git safety this commit is just the rename. Accompanying build
changes are next.
The execution changes just move some of the bits to Command.hs;
the completion rework is pretty much total.

It should be at least marginally better than it was before, e.g.  if
you type "let x : <tab>" it'll offer names of types rather than values.

If you spot any regressions please file issues.
Source files should have
   - directives
   - the Haddock header
   - the module name and export list
   - imports in a rational order

It looks nicer to have the Haddock header first and then the
directives list, but it turns out that any whole-file documentation or
description has to go in the Haddock header or Haddock throws it away,
and putting the directives after then makes them too far down in
modules with lots of things to say.
@sauclovian-g
Copy link
Contributor Author

That force-push was the fix, the one I'm about to push rebases over #2766.

@sauclovian-g sauclovian-g merged commit 1c52684 into master Nov 3, 2025
37 checks passed
@sauclovian-g sauclovian-g deleted the rationalize-repl branch November 3, 2025 21:43
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Labels

None yet

Projects

None yet

Development

Successfully merging this pull request may close these issues.

3 participants