-
Notifications
You must be signed in to change notification settings - Fork 459
Sequence values in the abstract domain #204
Changes from all commits
fde3424
7d9100f
cd950fd
0f34dce
dbf8941
559a7aa
82cb7e4
d600246
8d08b1a
c2e620a
File filter
Filter by extension
Conversations
Jump to
Diff view
Diff view
There are no files selected for viewing
| Original file line number | Diff line number | Diff line change |
|---|---|---|
|
|
@@ -30,6 +30,7 @@ import Prelude hiding (fail) | |
| eval :: ( Carrier sig m | ||
| , Member (Reader Loc) sig | ||
| , MonadFail m | ||
| , Semigroup value | ||
| ) | ||
| => Analysis address value m | ||
| -> (Term Core User -> m value) | ||
|
|
@@ -41,12 +42,15 @@ eval Analysis{..} eval = \case | |
| addr <- alloc n | ||
| v <- bind n addr (eval (instantiate1 (pure n) b)) | ||
| v <$ assign addr v | ||
| a :>> b -> eval a >> eval b | ||
| -- NB: Combining the results of the evaluations allows us to model effects in abstract domains. This in turn means that we can define an abstract domain modelling the types-and-effects of computations by means of a 'Semigroup' instance which takes the type of its second operand and the union of both operands’ effects. | ||
| -- | ||
| -- It’s also worth noting that we use a semigroup instead of a semilattice because the lattice structure of our abstract domains is instead modelled by nondeterminism effects used by some of them. | ||
| a :>> b -> (<>) <$> eval a <*> eval b | ||
|
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Combining the results of evaluations together with def f
a
b
endThen a domain modelling the type-and-effect of
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. It’s also worth asking: why a semigroup, when so much of the abstract interpretation literature focuses on (semi)lattices? In short, our lattice structure is provided by the sets of computations performed under the nondeterminism effect; paraphrasing Darais et al, concretization maps values in the abstract domain to finite sets of observations in the concrete domain. So in short, the lattice’s least upper bound operation is a) provided by
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Finally, we could eventually consider strengthening the
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. This all makes total sense to me, and is a huge win for clarity. Can we move the relevant sections of the above comments (which are wonderful!) to comments on the |
||
| Named (Ignored n) a :>>= b -> do | ||
| a' <- eval a | ||
| addr <- alloc n | ||
| assign addr a' | ||
| bind n addr (eval (instantiate1 (pure n) b)) | ||
| bind n addr ((a' <>) <$> eval (instantiate1 (pure n) b)) | ||
| Lam (Named (Ignored n) b) -> abstract eval n (instantiate1 (pure n) b) | ||
| f :$ a -> do | ||
| f' <- eval f | ||
|
|
@@ -210,18 +214,18 @@ ruby = fromBody $ annWith callStack (rec (named' __semantic_global) (do' stateme | |
|
|
||
|
|
||
| data Analysis 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 Core User -> m value) -> User -> Term Core User -> m value | ||
| , apply :: (Term Core User -> m value) -> value -> value -> m value | ||
| , unit :: m value | ||
| , bool :: Bool -> m value | ||
| , asBool :: value -> m Bool | ||
| , string :: Text -> m value | ||
| , asString :: value -> m Text | ||
| , record :: [(User, value)] -> m value | ||
| , (...) :: address -> User -> m (Maybe address) | ||
| { 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 Core User -> m value) -> User -> Term Core User -> m value | ||
| , apply :: (Term Core User -> m value) -> value -> value -> m value | ||
| , unit :: m value | ||
| , bool :: Bool -> m value | ||
| , asBool :: value -> m Bool | ||
| , string :: Text -> m value | ||
| , asString :: value -> m Text | ||
| , record :: [(User, value)] -> m value | ||
| , (...) :: address -> User -> m (Maybe address) | ||
|
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Whitespace-only changes to this block. |
||
| } | ||
| Original file line number | Diff line number | Diff line change |
|---|---|---|
| @@ -1,4 +1,4 @@ | ||
| {-# LANGUAGE DeriveGeneric, DeriveTraversable, FlexibleContexts, FlexibleInstances, LambdaCase, OverloadedStrings, QuantifiedConstraints, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeOperators #-} | ||
| {-# LANGUAGE DeriveGeneric, DeriveTraversable, DerivingVia, FlexibleContexts, FlexibleInstances, LambdaCase, OverloadedStrings, QuantifiedConstraints, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeOperators #-} | ||
| module Analysis.Typecheck | ||
| ( Monotype (..) | ||
| , Meta | ||
|
|
@@ -30,6 +30,7 @@ import qualified Data.Map as Map | |
| import Data.Maybe (fromJust, fromMaybe) | ||
| import Data.Name as Name | ||
| import Data.Scope | ||
| import Data.Semigroup (Last (..)) | ||
| import qualified Data.Set as Set | ||
| import Data.Term | ||
| import Data.Void | ||
|
|
@@ -44,6 +45,11 @@ data Monotype f a | |
| | Record (Map.Map User (f a)) | ||
| deriving (Foldable, Functor, Generic1, Traversable) | ||
|
|
||
| -- FIXME: Union the effects/annotations on the operands. | ||
|
|
||
| -- | We derive the 'Semigroup' instance for types to take the second argument. This is equivalent to stating that the type of an imperative sequence of statements is the type of its final statement. | ||
| deriving via (Last (Term Monotype a)) instance Semigroup (Term Monotype a) | ||
|
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. I was legit surprised that this instance isn’t orphaned, but it’s due to |
||
|
|
||
| deriving instance (Eq a, forall a . Eq a => Eq (f a), Monad f) => Eq (Monotype f a) | ||
| deriving instance (Ord a, forall a . Eq a => Eq (f a) | ||
| , forall a . Ord a => Ord (f a), Monad f) => Ord (Monotype f 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.
This instance makes me so happy!