1
1
mirror of https://github.com/github/semantic.git synced 2024-12-24 23:42:31 +03:00

Move Precise & Latest into their own module.

This commit is contained in:
Rob Rix 2018-05-16 11:53:24 -04:00
parent 0467b0c8fe
commit 680336057d
6 changed files with 30 additions and 22 deletions

View File

@ -6,6 +6,7 @@ module Control.Abstract.Addressable
import Control.Abstract.Context
import Control.Abstract.Evaluator
import Data.Abstract.Address
import Data.Abstract.Address.Precise
import Data.Abstract.FreeVariables
import Prologue

View File

@ -4,7 +4,6 @@ module Data.Abstract.Address where
import Data.Abstract.FreeVariables
import Data.Abstract.Module (ModuleInfo)
import Data.Abstract.Package (PackageInfo)
import Data.Monoid (Last(..))
import Data.Semigroup.Reducer
import Data.Semilattice.Lower
import Data.Set as Set
@ -22,14 +21,6 @@ instance Show location => Show (Address location value) where
showsPrec d = showsPrec d . unAddress
-- | '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 Show Precise where
showsPrec d = showsUnaryWith showsPrec "Precise" d . unPrecise
-- | 'Monovariant' models using one address for a particular name. It trackes the set of values that a particular address takes and uses it's name to lookup in the store and only allocation if new.
newtype Monovariant = Monovariant { unMonovariant :: Name }
deriving (Eq, Ord)
@ -46,19 +37,6 @@ data Located location = Located
deriving (Eq, Ord, Show)
-- | A cell holding a single value. Writes will replace any prior value.
--
-- This is equivalent to 'Data.Monoid.Last', but with a 'Show' instance designed to minimize the amount of text we have to scroll past in ghci.
newtype Latest value = Latest { unLatest :: Last value }
deriving (Eq, Foldable, Functor, Lower, Monoid, Semigroup, Ord, Traversable)
instance Reducer value (Latest value) where
unit = Latest . unit . Just
instance Show value => Show (Latest value) where
showsPrec d = showsPrec d . getLast . unLatest
-- | A cell holding all values written to its address.
--
-- This is equivalent to 'Set', but with a 'Show' instance designed to minimize the amount of text we have to scroll past in ghci.

View File

@ -1 +1,27 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Abstract.Address.Precise where
import Data.Monoid (Last(..))
import Data.Semigroup.Reducer
import Data.Semilattice.Lower
import Prologue
-- | '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 Show Precise where
showsPrec d = showsUnaryWith showsPrec "Precise" d . unPrecise
-- | A cell holding a single value. Writes will replace any prior value.
--
-- This is equivalent to 'Data.Monoid.Last', but with a 'Show' instance designed to minimize the amount of text we have to scroll past in ghci.
newtype Latest value = Latest { unLatest :: Last value }
deriving (Eq, Foldable, Functor, Lower, Monoid, Semigroup, Ord, Traversable)
instance Reducer value (Latest value) where
unit = Latest . unit . Just
instance Show value => Show (Latest value) where
showsPrec d = showsPrec d . getLast . unLatest

View File

@ -23,6 +23,7 @@ import Control.Abstract
import qualified Control.Exception as Exc
import Control.Monad.Effect (reinterpret)
import Data.Abstract.Address
import Data.Abstract.Address.Precise
import Data.Abstract.Evaluatable
import Data.Abstract.Module
import Data.Abstract.Package as Package

View File

@ -9,6 +9,7 @@ import Control.Abstract.Evaluator
import Control.Abstract.TermEvaluator
import Control.Monad.Effect.Trace (runPrintingTrace)
import Data.Abstract.Address
import Data.Abstract.Address.Precise
import Data.Abstract.Evaluatable
import Data.Abstract.Value
import Data.Abstract.Type

View File

@ -18,6 +18,7 @@ import Control.Arrow ((&&&))
import Control.Monad.Effect.Trace as X (runIgnoringTrace, runReturningTrace)
import Control.Monad ((>=>))
import Data.Abstract.Address as X
import Data.Abstract.Address.Precise as X
import Data.Abstract.Environment as Env
import Data.Abstract.Evaluatable
import Data.Abstract.FreeVariables as X hiding (dropExtension)