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
41 commits
Select commit Hold shift + click to select a range
fcf6540
Rename the name parameter to address.
robrix Jul 29, 2019
56984fa
Define Cache as a newtype.
robrix Jul 29, 2019
7b6b6a4
Generalize convergeTerm over the address type.
robrix Jul 29, 2019
05fa90e
Generalize the Cache type over the term type.
robrix Jul 29, 2019
fdc20a4
Generalize convergeTerm over the term type.
robrix Jul 29, 2019
c82623d
Generalize cacheTerm over the term type.
robrix Jul 29, 2019
104bdac
Generalize Analysis over the term type.
robrix Jul 29, 2019
465319b
Simplify deref for Typecheck & ImportGraph.
robrix Jul 26, 2019
9acaaae
:fire: the parentAddr in ImportGraph.
robrix Jul 29, 2019
65e2184
Import graphs don’t need to collect the set of addresses in scope whe…
robrix Jul 29, 2019
54430ac
Abstract Semi over the term type.
robrix Jul 29, 2019
3387eac
Abstract Value over the term type.
robrix Jul 29, 2019
e022b47
Reformat the signature for importGraph.
robrix Jul 29, 2019
7e7f33c
Generalize importGraphAnalysis over the term type.
robrix Jul 29, 2019
99d9a8d
Parameterize runFile by the evaluator.
robrix Jul 29, 2019
2666f6c
Generalize runFile over the term type.
robrix Jul 29, 2019
5c67ea0
Reformat the signature for typecheckingFlowInsensitive.
robrix Jul 29, 2019
6652520
Reformat the signature for runFile.
robrix Jul 29, 2019
97ae6e9
Use a type synonym for types.
robrix Jul 29, 2019
813cde3
Reformat the signature for runFile to accommodate the evaluator.
robrix Jul 29, 2019
e287557
Generalize typecheckingFlowInsensitive over the term type.
robrix Jul 29, 2019
8b8a330
Generalize runFile over the term type.
robrix Jul 29, 2019
b926114
Change the kind of the term field to *.
robrix Jul 29, 2019
4553d59
Generalize importGraph over the term type.
robrix Jul 29, 2019
fde2a44
Abstract Concrete over the term type.
robrix Jul 29, 2019
2559f58
Generalize Heap over the term type.
robrix Jul 29, 2019
2dde200
Generalize lookupConcrete over the term type.
robrix Jul 29, 2019
1192971
Generalize concreteAnalysis over the term type.
robrix Jul 29, 2019
c3cf286
Generalize EdgeType over the term type.
robrix Jul 29, 2019
ea174b2
Generalize runHeap over the term type.
robrix Jul 29, 2019
021350b
Generalize heapGraph over the term type.
robrix Jul 29, 2019
a549039
Generalize heapValueGraph over the term type.
robrix Jul 29, 2019
bd8f0ca
Generalize heapAddressGraph over the term type.
robrix Jul 29, 2019
d817530
Generalize addressStyle over the term type.
robrix Jul 29, 2019
da0d780
Generalize runFile over the term type.
robrix Jul 29, 2019
15e5731
Generalize concrete over the term types.
robrix Jul 29, 2019
2c28e53
:fire: the FrameId reader effect.
robrix Jul 29, 2019
e9853c1
Avoid allocating a useless cell.
robrix Jul 29, 2019
0b86f91
Clean up some language extensions.
robrix Jul 29, 2019
bd5aea6
Fix the doctests of the concrete analysis.
robrix Jul 29, 2019
8ad510d
Merge branch 'master' into generalize-analyses-over-the-term-type
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
79 changes: 49 additions & 30 deletions semantic-core/src/Analysis/Concrete.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DerivingVia, FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DerivingVia, FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RankNTypes, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
module Analysis.Concrete
( Concrete(..)
, concrete
Expand All @@ -20,7 +20,6 @@ import Control.Effect.NonDet
import Control.Effect.Reader hiding (Local)
import Control.Effect.State
import Control.Monad ((<=<), guard)
import qualified Data.Core as Core
Copy link
Contributor Author

Choose a reason for hiding this comment

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

We no longer rely directly on imports of Data.Core or any other syntax. We do still rely on Analysis.Eval for the Analysis record, but it could easily be moved elsewhere (and will eventually be factored into effects anyway).

This means that we could in principle split the analyses off into a new package, which is a good sign that we’ve got the right separation of concerns going.

import Data.File
import Data.Function (fix)
import qualified Data.IntMap as IntMap
Expand All @@ -30,7 +29,6 @@ import qualified Data.Map as Map
import Data.Name
import Data.Semigroup (Last (..))
import qualified Data.Set as Set
import Data.Term
import Data.Text (Text, pack)
import Data.Traversable (for)
import Prelude hiding (fail)
Expand All @@ -41,17 +39,17 @@ type Env = Map.Map User Precise
newtype FrameId = FrameId { unFrameId :: Precise }
deriving (Eq, Ord, Show)

data Concrete
= Closure Loc User (Term (Core.Ann :+: Core.Core) User) Env
data Concrete term
= Closure Loc User term Env
| Unit
| Bool Bool
| String Text
| Record Env
deriving (Eq, Ord, Show)
-- NB: We derive the 'Semigroup' instance for 'Concrete' to take the second argument. This is equivalent to stating that the return value of an imperative sequence of statements is the value of its final statement.
deriving Semigroup via Last Concrete
deriving Semigroup via Last (Concrete term)

recordFrame :: Concrete -> Maybe Env
recordFrame :: Concrete term -> Maybe Env
recordFrame (Record frame) = Just frame
recordFrame _ = Nothing

Expand All @@ -60,44 +58,64 @@ newtype Frame = Frame
}
deriving (Eq, Ord, Show)

type Heap = IntMap.IntMap Concrete
type Heap term = IntMap.IntMap (Concrete term)

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


-- | Concrete evaluation of a term to a value.
--
-- >>> map fileBody (snd (concrete [File (Loc "bool" emptySpan) (Core.bool True)]))
-- >>> map fileBody (snd (concrete eval [File (Loc "bool" emptySpan) (Core.bool True)]))
-- [Right (Bool True)]
concrete :: [File (Term (Core.Ann :+: Core.Core) User)] -> (Heap, [File (Either (Loc, String) Concrete)])
concrete
:: (Foldable term, Show (term User))
=> (forall sig m
. (Carrier sig m, Member (Reader Loc) sig, MonadFail m)
Copy link
Contributor Author

Choose a reason for hiding this comment

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

Abstracting this evaluator over any m satisfying these effects (these being the effects required by eval) enables us to avoid coupling the evaluator(s) to implementation details of the analyses, too.

This list of constraints will eventually grow as we factor bits of Analysis out into effects.

=> Analysis (term User) Precise (Concrete (term User)) m
-> (term User -> m (Concrete (term User)))
-> (term User -> m (Concrete (term User)))
)
-> [File (term User)]
-> (Heap (term User), [File (Either (Loc, String) (Concrete (term User)))])
concrete eval
= run
. runFresh
. runHeap
. traverse runFile

runFile :: ( Carrier sig m
, Effect sig
, Member Fresh sig
, Member (State Heap) sig
)
=> File (Term (Core.Ann :+: Core.Core) User)
-> m (File (Either (Loc, String) Concrete))
runFile file = traverse run file
. traverse (runFile eval)

runFile
:: ( Carrier sig m
, Effect sig
, Foldable term
, Member Fresh sig
, Member (State (Heap (term User))) sig
, Show (term User)
)
=> (forall sig m
. (Carrier sig m, Member (Reader Loc) sig, MonadFail m)
=> Analysis (term User) Precise (Concrete (term User)) m
-> (term User -> m (Concrete (term User)))
-> (term User -> m (Concrete (term User)))
)
-> File (term User)
-> m (File (Either (Loc, String) (Concrete (term User))))
runFile eval file = traverse run file
where run = runReader (fileLoc file)
. runFailWithLoc
. runReader @Env mempty
. fix (eval concreteAnalysis)

concreteAnalysis :: ( Carrier sig m
, Foldable term
Copy link
Contributor Author

Choose a reason for hiding this comment

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

We need Foldable to collect the free variables in the term to filter the env that closures close over.

, Member Fresh sig
, Member (Reader Env) sig
, Member (Reader Loc) sig
, Member (State Heap) sig
, Member (State (Heap (term User))) sig
, MonadFail m
, Show (term User)
)
=> Analysis Precise Concrete m
=> Analysis (term User) Precise (Concrete (term User)) m
concreteAnalysis = Analysis{..}
where alloc _ = fresh
bind name addr m = local (Map.insert name addr) m
Expand Down Expand Up @@ -133,7 +151,7 @@ concreteAnalysis = Analysis{..}
pure (val >>= lookupConcrete heap n)


lookupConcrete :: Heap -> User -> Concrete -> Maybe Precise
lookupConcrete :: Heap term -> User -> Concrete term -> Maybe Precise
lookupConcrete heap name = run . evalState IntSet.empty . runNonDet . inConcrete
where -- look up the name in a concrete value
inConcrete = inFrame <=< maybeA . recordFrame
Expand All @@ -150,7 +168,7 @@ lookupConcrete heap name = run . evalState IntSet.empty . runNonDet . inConcrete
maybeA = maybe empty pure


runHeap :: StateC Heap m a -> m (Heap, a)
runHeap :: StateC (Heap term) m a -> m (Heap term, a)
runHeap = runState mempty


Expand All @@ -159,7 +177,7 @@ runHeap = runState mempty
-- > λ 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 Edge User -> Precise -> G.Graph a) -> Heap -> G.Graph a
heapGraph :: (Precise -> Concrete term -> a) -> (Either Edge User -> Precise -> G.Graph a) -> Heap term -> 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
Expand All @@ -169,14 +187,14 @@ heapGraph vertex edge h = foldr (uncurry graph) G.empty (IntMap.toList h)
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 :: Heap term -> G.Graph (Concrete term)
heapValueGraph h = heapGraph (const id) (const fromAddr) h
where fromAddr addr = maybe G.empty G.vertex (IntMap.lookup addr h)

heapAddressGraph :: Heap -> G.Graph (EdgeType, Precise)
heapAddressGraph :: Heap term -> G.Graph (EdgeType term, Precise)
heapAddressGraph = heapGraph (\ addr v -> (Value v, addr)) (fmap G.vertex . (,) . either Edge Slot)

addressStyle :: Heap -> G.Style (EdgeType, Precise) Text
addressStyle :: Heap term -> G.Style (EdgeType term, 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]
Expand All @@ -191,12 +209,13 @@ addressStyle heap = (G.defaultStyle vertex) { G.edgeAttributes }
Record _ -> "{}"
showPos (Pos l c) = pack (show l) <> ":" <> pack (show c)

data EdgeType
data EdgeType term
= Edge Edge
| Slot User
| Value Concrete
| Value (Concrete term)
deriving (Eq, Ord, Show)


-- $setup
-- >>> :seti -XOverloadedStrings
-- >>> import qualified Data.Core as Core
8 changes: 4 additions & 4 deletions semantic-core/src/Analysis/Eval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ eval :: ( Carrier sig m
, MonadFail m
, Semigroup value
)
=> Analysis address value m
=> Analysis (Term (Ann :+: Core) User) address value m
Copy link
Contributor Author

Choose a reason for hiding this comment

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

eval is still specialized to Term (Ann :+: Core) User; intuitively, it is the canonical abstract interpreter for Core, and thus has to be specialized to it.

-> (Term (Ann :+: Core) User -> m value)
-> (Term (Ann :+: Core) User -> m value)
eval Analysis{..} eval = \case
Expand Down Expand Up @@ -214,14 +214,14 @@ ruby = fromBody $ annWith callStack (rec (named' __semantic_global) (do' stateme
__semantic_truthy = "__semantic_truthy"


data Analysis address value m = Analysis
data Analysis term address value m = Analysis
{ alloc :: User -> m address
, bind :: forall a . User -> address -> m a -> m a
, lookupEnv :: User -> m (Maybe address)
, deref :: address -> m (Maybe value)
, assign :: address -> value -> m ()
, abstract :: (Term (Ann :+: Core) User -> m value) -> User -> Term (Ann :+: Core) User -> m value
, apply :: (Term (Ann :+: Core) User -> m value) -> value -> value -> m value
, abstract :: (term -> m value) -> User -> term -> m value
, apply :: (term -> m value) -> value -> value -> m value
, unit :: m value
, bool :: Bool -> m value
, asBool :: value -> m Bool
Expand Down
50 changes: 26 additions & 24 deletions semantic-core/src/Analysis/FlowInsensitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,60 +13,62 @@ import Control.Effect.Fresh
import Control.Effect.NonDet
import Control.Effect.Reader
import Control.Effect.State
import qualified Data.Core as Core
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.Monoid (Alt(..))
import qualified Data.Set as Set
import Data.Term (Term)

type Cache name a = Map.Map (Term (Core.Ann :+: Core.Core) name) (Set.Set a)
type Heap name a = Map.Map name (Set.Set a)
newtype Cache term a = Cache { unCache :: Map.Map term (Set.Set a) }
Copy link
Contributor Author

Choose a reason for hiding this comment

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

Without the newtype, abstracting the cache over the term type made it impossible to distinguish from Heap.

deriving (Eq, Ord, Show)

type Heap address a = Map.Map address (Set.Set a)

newtype FrameId name = FrameId { unFrameId :: name }
deriving (Eq, Ord, Show)


convergeTerm :: forall m sig a name
convergeTerm :: forall m sig a term address proxy
. ( Carrier sig m
, Effect sig
, Eq address
, Member Fresh sig
, Member (State (Heap name a)) sig
, Member (State (Heap address a)) sig
, Ord a
, Ord name
, Ord term
)
=> (Term (Core.Ann :+: Core.Core) name -> NonDetC (ReaderC (Cache name a) (StateC (Cache name a) m)) a)
-> Term (Core.Ann :+: Core.Core) name
=> proxy address
Copy link
Contributor Author

Choose a reason for hiding this comment

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

We didn’t mention the address type anywhere else, so we needed a dummy parameter to keep it unambiguous. (We could also have used AllowAmbiguousTypes & TypeApplications, but I try to avoid the former since it makes calling the thing significantly more challenging.)

Copy link
Contributor

Choose a reason for hiding this comment

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

+1 on avoiding AllowAmbiguousTypes, since Proxy has nice behavior with TypeApplications anyway.

-> (term -> NonDetC (ReaderC (Cache term a) (StateC (Cache term a) m)) a)
-> term
-> m (Set.Set a)
convergeTerm eval body = do
convergeTerm _ eval body = do
heap <- get
(cache, _) <- converge (Map.empty :: Cache name a, heap :: Heap name a) $ \ (prevCache, _) -> runState Map.empty . runReader prevCache $ do
(cache, _) <- converge (Cache Map.empty :: Cache term a, heap :: Heap address a) $ \ (prevCache, _) -> runState (Cache Map.empty) . runReader prevCache $ do
_ <- resetFresh . runNonDetM Set.singleton $ eval body
get
pure (fromMaybe mempty (Map.lookup body cache))
pure (fromMaybe mempty (Map.lookup body (unCache cache)))

cacheTerm :: forall m sig a name
cacheTerm :: forall m sig a term
. ( Alternative m
, Carrier sig m
, Member (Reader (Cache name a)) sig
, Member (State (Cache name a)) sig
, Member (Reader (Cache term a)) sig
, Member (State (Cache term a)) sig
, Ord a
, Ord name
, Ord term
)
=> (Term (Core.Ann :+: Core.Core) name -> m a)
-> (Term (Core.Ann :+: Core.Core) name -> m a)
=> (term -> m a)
-> (term -> m a)
cacheTerm eval term = do
cached <- gets (Map.lookup term)
cached <- gets (Map.lookup term . unCache)
case cached :: Maybe (Set.Set a) of
Just results -> foldMapA pure results
Nothing -> do
results <- asks (fromMaybe mempty . Map.lookup term)
modify (Map.insert term (results :: Set.Set a))
results <- asks (fromMaybe mempty . Map.lookup term . unCache)
modify (Cache . Map.insert term (results :: Set.Set a) . unCache)
result <- eval term
result <$ modify (Map.insertWith (<>) term (Set.singleton (result :: a)))
result <$ modify (Cache . Map.insertWith (<>) term (Set.singleton (result :: a)) . unCache)

runHeap :: name -> ReaderC (FrameId name) (StateC (Heap name a) m) b -> m (Heap name a, b)
runHeap addr m = runState (Map.singleton addr Set.empty) (runReader (FrameId addr) m)
runHeap :: StateC (Heap address a) m b -> m (Heap address a, b)
runHeap m = runState (Map.empty) m

-- | Fold a collection by mapping each element onto an 'Alternative' action.
foldMapA :: (Alternative m, Foldable t) => (b -> m a) -> t b -> m a
Expand Down
Loading