-
Notifications
You must be signed in to change notification settings - Fork 459
Conversation
robrix
left a comment
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Ready for review.
|
|
||
| concreteAnalysis :: ( Carrier sig m | ||
| , Member Fresh sig | ||
| , Member (Reader Env) sig |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Rather than modelling the local environment explicitly in the heap, we resume using an Env for it, and modelling non-local scopes explicitly with records. Computation of scope graphs is still possible by instrumenting binds (among other things), but we get to enjoy a much simpler implementation of name binding and lookup.
| Rec (Named (Ignored n) b) -> do | ||
| addr <- alloc n | ||
| v <- bind n addr (eval (instantiate1 (pure n) b)) | ||
| v <$ assign addr v |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Rec implements recursive bindings of the form rec x = y s.t. occurrences of x within y are bound to the result of y. It’s not strictly requisite given mutable variables, but it’s hella convenient, and easier to analyze than the equivalent mutation-based knot-tying.
| a' <- eval a | ||
| addr <- alloc n | ||
| assign addr a' | ||
| bind n addr (eval (instantiate1 (pure n) b)) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
We once more support local variables using :>>=.
| a :. b -> do | ||
| a' <- ref a | ||
| a' ... eval b | ||
| a' ... b >>= maybe (freeVariable (show b)) (deref' b) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Projection simply selects (the address of) a field out of a record, rather than pushing into a frame.
| , Just "NilClass" :<- record | ||
| [ (__semantic_super, var "(NilClass)") | ||
| , (__semantic_super, var "Object") | ||
| , ("nil?", lam "_" (var __semantic_global ... "true")) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
We look true up in __semantic_global (which is bound recursively) because it hasn’t been defined yet.
| , bindEither | ||
| , abstract1 | ||
| , abstract | ||
| , abstractEither |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
I renamed these to match bound.
| , Gen.subterm expr Core.load | ||
| , record expr | ||
| , Gen.subtermM expr (\ x -> (x Core....) . namedValue <$> name) | ||
| , Gen.subterm2 expr expr (Core..=) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
This should be exhaustive.
| assert_let_dot_precedence = "let a = f.g.h" `parsesInto` (let' "a" .= (f ... g ... h)) | ||
|
|
||
| assert_let_in_push_precedence :: Assertion | ||
| assert_let_in_push_precedence = "f.let g = h" `parsesInto` (f ... (let' "g" .= h)) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
These don’t make sense any more.
| assert_roundtrips (File _ core) = parseEither Parse.core (showCore core) @?= Right (stripAnnotations core) | ||
| assert_roundtrips (File _ core) = case parseEither Parse.core (showCore core) of | ||
| Right v -> v @?= stripAnnotations core | ||
| Left e -> assertFailure e |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
This gives us better error messages, tho sadly I can’t seem to find a way to do the same in tripping.
| runFile file = traverse run file | ||
| where run = runReader (fileLoc file) | ||
| . runFailWithLoc | ||
| . runReader (mempty :: Env) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Slight nitpick: I prefer runReader @Env mempty, since I love a good visible type annotation.
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Fixed in dd6d9a0.
| heap <- get | ||
| pure (val >>= lookupConcrete heap n) | ||
| bind name addr m = local (Map.insert name addr) m | ||
| lookupEnv n = asks (Map.lookup n) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Wow, way way way way better.
| import qualified Data.IntMap as IntMap | ||
| import qualified Data.IntSet as IntSet | ||
| import Data.Loc | ||
| import qualified Data.Map as Map |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
I wonder whether strict maps are preferable? Probably something we should file an issue about.
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
I’m not particularly interested in the performance of the concrete analysis at the moment given that we’re only intending to use it for validation, but we can revisit that later, for sure.
| inConcrete = inFrame <=< maybeA . recordFrame | ||
| -- look up the name in a specific 'Frame', with slots taking precedence over parents | ||
| inFrame (Frame ps fs) = maybeA (Map.lookup name fs) <|> getAlt (foldMap (Alt . inAddress . snd) ps) | ||
| inFrame fs = maybeA (Map.lookup name fs) <|> (maybeA (Map.lookup "__semantic_super" fs) >>= inAddress) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
We have a top-level define for __semantic_super somewhere, can we use it here?
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
It’s not top-level, and I’m actually pretty sure that I don’t want this to live in here long-term; it should be encoded in the compilers, so that different languages can specify their own lookup strategies. This will be important for e.g. method_missing’s semantics.
| Obj frame -> fromFrame frame | ||
| fromFrame (Frame es ss) = foldr (G.overlay . uncurry (edge . Left)) (foldr (G.overlay . uncurry (edge . Right)) G.empty (Map.toList ss)) es | ||
| Closure _ _ _ env -> foldr (G.overlay . edge (Left Lexical)) G.empty env | ||
| Record frame -> foldr (G.overlay . uncurry (edge . Right)) G.empty (Map.toList frame) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
| Record frame -> foldr (G.overlay . uncurry (edge . Right)) G.empty (Map.toList frame) | |
| Record frame -> Map.foldrWithKey (\k v -> G.overlay (edge v (Right k)) G.empty frame |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Great suggestion! Fixed in 28404ae.
| application = projection `chainl1` (pure (Core.$$)) | ||
|
|
||
| projection :: (TokenParsing m, Monad m) => m (Term Core User) | ||
| projection = foldl' (Core....) <$> atom <*> many (namedValue <$ dot <*> name) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Beautiful.
|
|
||
| statement :: (TokenParsing m, Monad m) => m (Maybe (Named User) Core.:<- Term Core User) | ||
| statement | ||
| = try ((Core.:<-) . Just <$> name <* symbol "<-" <*> expr) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Nitpick: I would give (Core.:<-) its own prefix name here, as that particular punctuation cluster is tough to read when prefixed with Core (or just import it unqualified)
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Fixed in 78bd32e.
| , between (string "\"") (string "\"") (Core.string . fromString <$> many ('"' <$ string "\\\"" <|> noneOf "\"")) | ||
| , lambda | ||
| , record | ||
| , token (between (string "\"") (string "\"") (Core.string . fromString <$> many (escape <|> (noneOf "\"" <?> "non-escaped character")))) |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Two questions: how does this differ from stringLiteral from the parsers package? Can we make its differences explicit in a comment?
Secondly, and nitpickingly, I prefer char for single-character parsers.
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
That exists?? I was looking for it but didn’t find it. TIL, thank you! 🙇
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Fixed in 372ed98.
| withPrec :: Int -> Prec AnsiDoc -> AnsiDoc | ||
| withPrec d (Prec d' a) | ||
| | maybe False (d >) d' = parens a | ||
| | otherwise = a |
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Loving this. Definitely an improvement on my first stabs at it.
This PR replaces much of the frame machinery with a more principled approach based on first-class records (labelled products).