mirror of
https://github.com/github/semantic.git
synced 2024-12-27 00:44:57 +03:00
Move Located & Cell into Control.Abstract.Heap.
This commit is contained in:
parent
d058bb5fd4
commit
0cd3ac31b6
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
module Control.Abstract.Heap
|
||||
( Heap
|
||||
, Cell
|
||||
@ -38,3 +39,17 @@ assign :: ( Member (State (Heap location (Cell location) value)) effects
|
||||
-> value
|
||||
-> Evaluator location value effects ()
|
||||
assign address = modifyHeap . heapInsert address
|
||||
|
||||
|
||||
class Location location where
|
||||
-- | The type into which stored values will be written for a given location type.
|
||||
type family Cell location :: * -> *
|
||||
|
||||
instance Location Precise where
|
||||
type Cell Precise = Latest
|
||||
|
||||
instance Location Monovariant where
|
||||
type Cell Monovariant = All
|
||||
|
||||
instance Location (Located location) where
|
||||
type Cell (Located location) = Cell location
|
||||
|
@ -13,7 +13,7 @@ module Control.Abstract.Value
|
||||
import Control.Abstract.Environment
|
||||
import Control.Abstract.Evaluator
|
||||
import Control.Abstract.Heap
|
||||
import Data.Abstract.Address (Address, Cell)
|
||||
import Data.Abstract.Address (Address)
|
||||
import Data.Abstract.Environment as Env
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Abstract.Live (Live)
|
||||
|
@ -22,18 +22,10 @@ instance Show location => Show (Address location value) where
|
||||
showsPrec d = showsPrec d . unAddress
|
||||
|
||||
|
||||
class Location location where
|
||||
-- | The type into which stored values will be written for a given location type.
|
||||
type family Cell location :: * -> *
|
||||
|
||||
|
||||
-- | 'Precise' models precise store semantics where only the 'Latest' value is taken. Everything gets it's own address (always makes a new allocation) which makes for a larger store.
|
||||
newtype Precise = Precise { unPrecise :: Int }
|
||||
deriving (Eq, Ord)
|
||||
|
||||
instance Location Precise where
|
||||
type Cell Precise = Latest
|
||||
|
||||
instance Show Precise where
|
||||
showsPrec d = showsUnaryWith showsPrec "Precise" d . unPrecise
|
||||
|
||||
@ -42,9 +34,6 @@ instance Show Precise where
|
||||
newtype Monovariant = Monovariant { unMonovariant :: Name }
|
||||
deriving (Eq, Ord)
|
||||
|
||||
instance Location Monovariant where
|
||||
type Cell Monovariant = All
|
||||
|
||||
instance Show Monovariant where
|
||||
showsPrec d = showsUnaryWith showsPrec "Monovariant" d . unName . unMonovariant
|
||||
|
||||
@ -56,9 +45,6 @@ data Located location = Located
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Location (Located location) where
|
||||
type Cell (Located location) = Cell location
|
||||
|
||||
|
||||
-- | A cell holding a single value. Writes will replace any prior value.
|
||||
--
|
||||
|
Loading…
Reference in New Issue
Block a user