Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
152 commits
Select commit Hold shift + click to select a range
0115512
Simplify how we instantiate in unlam.
robrix Jul 19, 2019
ebafd64
Move encloseIf back into Data.Core.Pretty.
robrix Jul 19, 2019
de51991
Generalize encloseIf to any Semigroup.
robrix Jul 19, 2019
83cd925
Use Named to represent the binder.
robrix Jul 19, 2019
218c8f3
Define records of simultaneously-bound fields.
robrix Jul 19, 2019
00beb2d
Define a smart constructor for records.
robrix Jul 19, 2019
e259bc0
Define a recursive binder.
robrix Jul 19, 2019
f373ca4
Define a smart constructor for recursive bindings.
robrix Jul 19, 2019
1398c99
Redefine records as a flat list of bindings.
robrix Jul 19, 2019
2606e1e
:fire: a redundant where clause.
robrix Jul 19, 2019
3459b3b
Parse recursive bindings.
robrix Jul 19, 2019
972a52d
Prefix records during pretty-printing.
robrix Jul 19, 2019
79f5737
Parse records.
robrix Jul 19, 2019
cbf9f43
Define a smart-constructor for :>>.
robrix Jul 19, 2019
8c06d7b
Reintroduce assignment syntax.
robrix Jul 19, 2019
a10cdc9
Use >>> to define Block’s Semigroup instance.
robrix Jul 19, 2019
15a125b
Give fixity & precedence for >>>.
robrix Jul 19, 2019
6f5e578
Define a smart constructor for local bindings.
robrix Jul 19, 2019
e809a29
:memo: :>>=.
robrix Jul 19, 2019
38efb33
Move unseq & unseqs up under >>>.
robrix Jul 19, 2019
ef24642
Give fixity & precedence for :<-.
robrix Jul 19, 2019
bff499e
:memo: :..
robrix Jul 19, 2019
f24ef8b
Correct the docs for Record.
robrix Jul 19, 2019
b5a0624
:fire: redundant parens.
robrix Jul 22, 2019
db448e6
:fire: Let & Frame.
robrix Jul 22, 2019
1d50aec
Define prog5 using lams.
robrix Jul 22, 2019
2a5c181
:fire: lam'/lams'.
robrix Jul 22, 2019
c175bc3
Bind the global scope recursively.
robrix Jul 22, 2019
c9b328e
:fire: a bunch of redundant prefixes.
robrix Jul 22, 2019
94546f7
Define a helper for binding multiple local variables in a sequence.
robrix Jul 22, 2019
c495b4b
:fire: Edge.
robrix Jul 22, 2019
85c1815
Look up globals in the global scope.
robrix Jul 22, 2019
5e8a2c2
Note that :>>= is sequential let.
robrix Jul 22, 2019
b851621
:memo: Rec.
robrix Jul 22, 2019
8373e3a
:fire: a redundant qualifier.
robrix Jul 22, 2019
d5afd84
Rename bind* to abstract*.
robrix Jul 22, 2019
2c13ed8
Don’t build a lambda for method calls.
robrix Jul 22, 2019
fb318fa
Tidier frame-pushing.
robrix Jul 22, 2019
4cc6520
Define :. as strictly projection.
robrix Jul 22, 2019
cd3f73a
bind acts locally.
robrix Jul 22, 2019
c613b0c
:fire: the edge instruction.
robrix Jul 22, 2019
b0bc2cf
Note a FIXME.
robrix Jul 22, 2019
5f21602
:fire: some redundant FIXMEs.
robrix Jul 22, 2019
8bc79bd
Define and implement a record operation.
robrix Jul 22, 2019
fea81ee
:fire: the frame operation.
robrix Jul 22, 2019
6c5240b
Bind and look names up in an Env.
robrix Jul 22, 2019
d41d775
Don’t stratify frames through the heap.
robrix Jul 22, 2019
384c221
:fire: frameEdges.
robrix Jul 22, 2019
9b6f7dd
Obj holds an Env, not a Frame.
robrix Jul 22, 2019
958d32f
Follow edges through the graph.
robrix Jul 22, 2019
1abddf4
Annotate each binding.
robrix Jul 22, 2019
9ffd3f8
Annotate the entire prelude, not just the composition with ann.
robrix Jul 22, 2019
77cb532
Annotate prog5 deeply.
robrix Jul 22, 2019
2a60039
Closures close over their lexical environment once more.
robrix Jul 22, 2019
d299288
Only close over the free variables.
robrix Jul 22, 2019
a1f41e1
Rename Obj to Record.
robrix Jul 22, 2019
900bdbe
Rename objectFrame to recordFrame.
robrix Jul 22, 2019
acfcee1
Bind the Ruby prelude sequentially.
robrix Jul 22, 2019
3f7ac5e
Compute the fields of the record.
robrix Jul 22, 2019
37caa4d
Annotate the Ruby prelude deeply.
robrix Jul 22, 2019
0c80fd2
Set the super field.
robrix Jul 22, 2019
69b2151
Implement typechecking for records.
robrix Jul 22, 2019
325dc9d
:fire: some redundant FIXMEs.
robrix Jul 22, 2019
45a3d6f
Fix the generators.
robrix Jul 22, 2019
9522662
:fire: redundant specs.
robrix Jul 22, 2019
ed94f7e
Fix the expectation for projections.
robrix Jul 22, 2019
a25d971
Better pretty-printing of parse errors.
robrix Jul 22, 2019
724ae17
Allow binds to process non-binding statements.
robrix Jul 22, 2019
0797316
Rename binds to do'.
robrix Jul 22, 2019
1ce4153
do' doesn’t take an explicit body.
robrix Jul 22, 2019
b8bcad0
Use do' instead of block.
robrix Jul 22, 2019
a39e773
Follow the do' model for the Ruby prelude.
robrix Jul 22, 2019
a77ecdb
Parse binding statements.
robrix Jul 22, 2019
f9eea38
Print braces around nested binds.
robrix Jul 22, 2019
52da8b7
Qualify the import of Data.Core.
robrix Jul 22, 2019
043d308
Generate records.
robrix Jul 22, 2019
b43bdbb
Use named' to define the name generator.
robrix Jul 22, 2019
539f8db
Test roundtripping of general expressions.
robrix Jul 22, 2019
45723e7
Simplify the pretty-printing of sequences with a helper.
robrix Jul 22, 2019
344b5bd
Projection binds tighter than application.
robrix Jul 22, 2019
a5ac6f3
Correct the condition on parenthesization.
robrix Jul 23, 2019
0cb3f18
Indentation.
robrix Jul 23, 2019
f851b2b
Correct a bunch of precedences.
robrix Jul 23, 2019
09fdb30
Alignment.
robrix Jul 23, 2019
024d2d4
Don’t qualify the Pretty import.
robrix Jul 23, 2019
200bf17
Print spaces after semicolons.
robrix Jul 23, 2019
5c033ab
:fire: encloseIf.
robrix Jul 23, 2019
77acb91
Add spaces inside braces.
robrix Jul 23, 2019
f1c4d8a
Add spaces inside records’ braces.
robrix Jul 23, 2019
390b25a
Wrap & indent records.
robrix Jul 23, 2019
50f9b82
Nest sequences.
robrix Jul 23, 2019
9b3164a
:fire: block.
robrix Jul 23, 2019
ed0231c
Add an unbind eliminator for >>>=.
robrix Jul 23, 2019
4e98c04
Move the unseq/unseqs exports up.
robrix Jul 23, 2019
b0ee9ee
Derive Foldable, Functor, & Traversable instances for :<-.
robrix Jul 23, 2019
aa7f1fc
Define a Bifunctor instance for :<-.
robrix Jul 23, 2019
1caf99b
Align.
robrix Jul 23, 2019
a63e7c3
Clean up the language extensions in Data.Name.
robrix Jul 23, 2019
16413e1
Define a couple of functions for taking apart sequences of syntax.
robrix Jul 23, 2019
6050b95
Define an eliminator for statements.
robrix Jul 23, 2019
fa9c991
Define an eliminator for blocks of statements.
robrix Jul 23, 2019
6aa85af
Simplify un/unEither to not assume a Monad.
robrix Jul 23, 2019
1e43157
Pass the index to un/unEither’s argument.
robrix Jul 23, 2019
0045283
Define unstatements using un.
robrix Jul 23, 2019
7b29063
:fire: bind.
robrix Jul 23, 2019
6b250c7
Pretty-print variables early.
robrix Jul 23, 2019
b119712
Avoid redundant nesting of statements.
robrix Jul 23, 2019
a96eadb
Nest & align recursive bindings.
robrix Jul 23, 2019
47b43cf
Don’t pad empty records.
robrix Jul 23, 2019
453b898
Use colons to separate keys & values.
robrix Jul 23, 2019
3da182d
Comma-separate records.
robrix Jul 23, 2019
9612762
Define Prec as a newtype.
robrix Jul 23, 2019
56d40da
Rename with to withPrec.
robrix Jul 23, 2019
edbea69
Indentation.
robrix Jul 23, 2019
99668a3
Don’t set the precedence recursively.
robrix Jul 23, 2019
5b68260
inParens wraps a Doc, not an action.
robrix Jul 23, 2019
76eb3e2
Pretty-print with mandatory precedence handling.
robrix Jul 23, 2019
b58ddb4
Projections are lvalues.
robrix Jul 23, 2019
b700740
Split out a rule for application.
robrix Jul 23, 2019
d1671a6
Rename prj to projection.
robrix Jul 23, 2019
59af553
Recur via expr.
robrix Jul 23, 2019
08878f1
assign binds looser than application.
robrix Jul 23, 2019
9ccd11e
ifthenelse and lambda bind looser than assignment.
robrix Jul 23, 2019
068941e
Correct the precedence of if/then/else and lambda.
robrix Jul 23, 2019
e03236d
Generate assignments.
robrix Jul 23, 2019
308066f
Generate recursive bindings.
robrix Jul 23, 2019
8e5c216
Correct the precedence of recursive bindings.
robrix Jul 23, 2019
4bd2129
Lower the precedence in lambda bodies.
robrix Jul 23, 2019
0d530dc
Sort the recursive generators.
robrix Jul 23, 2019
e4470bc
Generate load instructions.
robrix Jul 23, 2019
3b67414
Rename edge to load.
robrix Jul 23, 2019
ac3f487
Correct the precedence of load.
robrix Jul 23, 2019
3d65ae9
Sort the atoms.
robrix Jul 23, 2019
f10cbb2
Generate string literals.
robrix Jul 23, 2019
0254bc9
Parse more escape sequences.
robrix Jul 23, 2019
15430ba
Alignment.
robrix Jul 23, 2019
41a31d1
Simplify the projection rule.
robrix Jul 23, 2019
7c24672
Parse whitespace following string literals.
robrix Jul 23, 2019
a0bf65f
Move Edge into Concrete.
robrix Jul 23, 2019
339585f
Merge branch 'master' into records
robrix Aug 6, 2019
93eba20
Rename un/unEither to unprefix/unprefixEither.
robrix Aug 6, 2019
7b0a415
:memo: unprefix.
robrix Aug 6, 2019
ab07e5a
:memo: unprefix’s purpose.
robrix Aug 6, 2019
e2ec37e
:memo: unprefix’s parameters.
robrix Aug 6, 2019
eb2ede6
Subterm.
robrix Aug 6, 2019
7c686d1
:memo: unprefixEither.
robrix Aug 6, 2019
0d2f05a
:memo: the parameters to unprefixEither.
robrix Aug 6, 2019
dd6d9a0
Type application.
robrix Aug 6, 2019
28404ae
foldrWithKey.
robrix Aug 6, 2019
b80dd53
Pull the rhs into a where clause.
robrix Aug 6, 2019
78bd32e
Don’t prefix :<-.
robrix Aug 6, 2019
372ed98
Avoid rolling our own string literal parser.
robrix Aug 6, 2019
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
103 changes: 45 additions & 58 deletions semantic-core/src/Analysis/Concrete.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RecordWildCards, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
module Analysis.Concrete
( Concrete(..)
, concrete
Expand Down Expand Up @@ -27,10 +27,11 @@ import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import Data.Loc
import qualified Data.Map as Map
Copy link
Contributor

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.

Copy link
Contributor Author

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.

import Data.Monoid (Alt(..))
import Data.Name
import qualified Data.Set as Set
import Data.Term
import Data.Text (Text, pack)
import Data.Traversable (for)
import Prelude hiding (fail)

type Precise = Int
Expand All @@ -40,25 +41,27 @@ newtype FrameId = FrameId { unFrameId :: Precise }
deriving (Eq, Ord, Show)

data Concrete
= Closure Loc User (Term Core.Core User) Precise
= Closure Loc User (Term Core.Core User) Env
| Unit
| Bool Bool
| String Text
| Obj Frame
| Record Env
deriving (Eq, Ord, Show)

objectFrame :: Concrete -> Maybe Frame
objectFrame (Obj frame) = Just frame
objectFrame _ = Nothing
recordFrame :: Concrete -> Maybe Env
recordFrame (Record frame) = Just frame
recordFrame _ = Nothing

data Frame = Frame
{ frameEdges :: [(Core.Edge, Precise)]
, frameSlots :: Env
newtype Frame = Frame
{ frameSlots :: Env
}
deriving (Eq, Ord, Show)

type Heap = IntMap.IntMap Concrete

data Edge = Lexical | Import
deriving (Eq, Ord, Show)


-- | Concrete evaluation of a term to a value.
--
Expand All @@ -74,46 +77,39 @@ concrete
runFile :: ( Carrier sig m
, Effect sig
, Member Fresh sig
, Member (Reader FrameId) sig
, Member (State Heap) sig
)
=> File (Term Core.Core User)
-> m (File (Either (Loc, String) Concrete))
runFile file = traverse run file
where run = runReader (fileLoc file)
. runFailWithLoc
. runReader @Env mempty
. fix (eval concreteAnalysis)

concreteAnalysis :: ( Carrier sig m
, Member Fresh sig
, Member (Reader Env) sig
Copy link
Contributor Author

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.

, Member (Reader Loc) sig
, Member (Reader FrameId) sig
, Member (State Heap) sig
, MonadFail m
)
=> Analysis Precise Concrete m
concreteAnalysis = Analysis{..}
where alloc _ = fresh
bind name addr = modifyCurrentFrame (updateFrameSlots (Map.insert name addr))
lookupEnv n = do
FrameId frameAddr <- ask
val <- deref frameAddr
heap <- get
pure (val >>= lookupConcrete heap n)
bind name addr m = local (Map.insert name addr) m
lookupEnv n = asks (Map.lookup n)
Copy link
Contributor

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.

deref = gets . IntMap.lookup
assign addr value = modify (IntMap.insert addr value)
abstract _ name body = do
loc <- ask
FrameId parentAddr <- ask
pure (Closure loc name body parentAddr)
apply eval (Closure loc name body parentAddr) a = do
frameAddr <- fresh
assign frameAddr (Obj (Frame [(Core.Lexical, parentAddr)] mempty))
local (const loc) . (frameAddr ...) $ do
env <- asks (flip Map.restrictKeys (Set.delete name (foldMap Set.singleton body)))
pure (Closure loc name body env)
apply eval (Closure loc name body env) a = do
local (const loc) $ do
addr <- alloc name
assign addr a
bind name addr
eval body
local (const (Map.insert name addr env)) (eval body)
apply _ f _ = fail $ "Cannot coerce " <> show f <> " to function"
unit = pure Unit
bool b = pure (Bool b)
Expand All @@ -122,30 +118,24 @@ concreteAnalysis = Analysis{..}
string s = pure (String s)
asString (String s) = pure s
asString v = fail $ "Cannot coerce " <> show v <> " to String"
-- FIXME: differential inheritance (reference fields instead of copying)
-- FIXME: copy non-lexical parents deeply?
frame = do
lexical <- asks unFrameId
pure (Obj (Frame [(Core.Lexical, lexical)] mempty))
-- FIXME: throw an error
-- FIXME: support dynamic imports
edge e addr = modifyCurrentFrame (\ (Frame ps fs) -> Frame ((e, addr) : ps) fs)
addr ... m = local (const (FrameId addr)) m

updateFrameSlots f frame = frame { frameSlots = f (frameSlots frame) }

modifyCurrentFrame f = do
addr <- asks unFrameId
Just (Obj frame) <- deref addr
assign addr (Obj (f frame))
record fields = do
fields' <- for fields $ \ (name, value) -> do
addr <- alloc name
assign addr value
pure (name, addr)
pure (Record (Map.fromList fields'))
addr ... n = do
val <- deref addr
heap <- get
pure (val >>= lookupConcrete heap n)


lookupConcrete :: Heap -> User -> Concrete -> Maybe Precise
lookupConcrete heap name = run . evalState IntSet.empty . runNonDet . inConcrete
where -- look up the name in a concrete value
inConcrete = inFrame <=< maybeA . objectFrame
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)
Copy link
Contributor

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?

Copy link
Contributor Author

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.

-- look up the name in the value an address points to, if we haven’t already visited it
inAddress addr = do
visited <- get
Expand All @@ -157,27 +147,24 @@ lookupConcrete heap name = run . evalState IntSet.empty . runNonDet . inConcrete
maybeA = maybe empty pure


runHeap :: (Carrier sig m, Member Fresh sig) => ReaderC FrameId (StateC Heap m) a -> m (Heap, a)
runHeap m = do
addr <- fresh
runState (IntMap.singleton addr (Obj (Frame [] mempty))) (runReader (FrameId addr) m)
runHeap :: StateC Heap m a -> m (Heap, a)
runHeap = runState mempty


-- | 'heapGraph', 'heapValueGraph', and 'heapAddressGraph' allow us to conveniently export SVGs of the heap:
--
-- > λ let (heap, res) = concrete [ruby]
-- > λ writeFile "/Users/rob/Desktop/heap.dot" (export (addressStyle heap) (heapAddressGraph heap))
-- > λ :!dot -Tsvg < ~/Desktop/heap.dot > ~/Desktop/heap.svg
heapGraph :: (Precise -> Concrete -> a) -> (Either Core.Edge User -> Precise -> G.Graph a) -> Heap -> G.Graph a
heapGraph :: (Precise -> Concrete -> a) -> (Either Edge User -> Precise -> G.Graph a) -> Heap -> G.Graph a
heapGraph vertex edge h = foldr (uncurry graph) G.empty (IntMap.toList h)
where graph k v rest = (G.vertex (vertex k v) `G.connect` outgoing v) `G.overlay` rest
outgoing = \case
Unit -> G.empty
Bool _ -> G.empty
String _ -> G.empty
Closure _ _ _ parentAddr -> edge (Left Core.Lexical) parentAddr
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 -> Map.foldrWithKey (\ k -> G.overlay . edge (Right k)) G.empty frame

heapValueGraph :: Heap -> G.Graph Concrete
heapValueGraph h = heapGraph (const id) (const fromAddr) h
Expand All @@ -189,20 +176,20 @@ heapAddressGraph = heapGraph (\ addr v -> (Value v, addr)) (fmap G.vertex . (,)
addressStyle :: Heap -> G.Style (EdgeType, Precise) Text
addressStyle heap = (G.defaultStyle vertex) { G.edgeAttributes }
where vertex (_, addr) = pack (show addr) <> " = " <> maybe "?" fromConcrete (IntMap.lookup addr heap)
edgeAttributes _ (Slot name, _) = ["label" G.:= name]
edgeAttributes _ (Edge Core.Import, _) = ["color" G.:= "blue"]
edgeAttributes _ (Edge Core.Lexical, _) = ["color" G.:= "green"]
edgeAttributes _ _ = []
edgeAttributes _ (Slot name, _) = ["label" G.:= name]
edgeAttributes _ (Edge Import, _) = ["color" G.:= "blue"]
edgeAttributes _ (Edge Lexical, _) = ["color" G.:= "green"]
edgeAttributes _ _ = []
fromConcrete = \case
Unit -> "()"
Bool b -> pack $ show b
String s -> pack $ show s
Closure (Loc p (Span s e)) n _ _ -> "\\\\ " <> n <> " [" <> p <> ":" <> showPos s <> "-" <> showPos e <> "]"
Obj _ -> "{}"
Record _ -> "{}"
showPos (Pos l c) = pack (show l) <> ":" <> pack (show c)

data EdgeType
= Edge Core.Edge
= Edge Edge
| Slot User
| Value Concrete
deriving (Eq, Ord, Show)
Expand Down
Loading