mirror of
https://github.com/github/semantic.git
synced 2024-12-26 16:33:03 +03:00
Revert "Move Precise & Latest into their own module."
This reverts commit 318ed8510aeb31ae892652685771bdba810d2df4.
This commit is contained in:
parent
b9678fcc57
commit
e8aa1a4da7
@ -6,7 +6,6 @@ module Control.Abstract.Addressable
|
|||||||
import Control.Abstract.Context
|
import Control.Abstract.Context
|
||||||
import Control.Abstract.Evaluator
|
import Control.Abstract.Evaluator
|
||||||
import Data.Abstract.Address
|
import Data.Abstract.Address
|
||||||
import Data.Abstract.Address.Precise
|
|
||||||
import Data.Abstract.FreeVariables
|
import Data.Abstract.FreeVariables
|
||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
|
@ -4,6 +4,7 @@ module Data.Abstract.Address where
|
|||||||
import Data.Abstract.FreeVariables
|
import Data.Abstract.FreeVariables
|
||||||
import Data.Abstract.Module (ModuleInfo)
|
import Data.Abstract.Module (ModuleInfo)
|
||||||
import Data.Abstract.Package (PackageInfo)
|
import Data.Abstract.Package (PackageInfo)
|
||||||
|
import Data.Monoid (Last(..))
|
||||||
import Data.Semigroup.Reducer
|
import Data.Semigroup.Reducer
|
||||||
import Data.Semilattice.Lower
|
import Data.Semilattice.Lower
|
||||||
import Data.Set as Set
|
import Data.Set as Set
|
||||||
@ -21,6 +22,14 @@ instance Show location => Show (Address location value) where
|
|||||||
showsPrec d = showsPrec d . unAddress
|
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.
|
-- | '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 }
|
newtype Monovariant = Monovariant { unMonovariant :: Name }
|
||||||
deriving (Eq, Ord)
|
deriving (Eq, Ord)
|
||||||
@ -37,6 +46,19 @@ data Located location = Located
|
|||||||
deriving (Eq, Ord, Show)
|
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.
|
-- | 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.
|
-- This is equivalent to 'Set', but with a 'Show' instance designed to minimize the amount of text we have to scroll past in ghci.
|
||||||
|
@ -1,27 +1 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
|
||||||
module Data.Abstract.Address.Precise where
|
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
|
|
||||||
|
@ -23,7 +23,6 @@ import Control.Abstract
|
|||||||
import qualified Control.Exception as Exc
|
import qualified Control.Exception as Exc
|
||||||
import Control.Monad.Effect (reinterpret)
|
import Control.Monad.Effect (reinterpret)
|
||||||
import Data.Abstract.Address
|
import Data.Abstract.Address
|
||||||
import Data.Abstract.Address.Precise
|
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Abstract.Module
|
import Data.Abstract.Module
|
||||||
import Data.Abstract.Package as Package
|
import Data.Abstract.Package as Package
|
||||||
|
@ -9,7 +9,6 @@ import Control.Abstract.Evaluator
|
|||||||
import Control.Abstract.TermEvaluator
|
import Control.Abstract.TermEvaluator
|
||||||
import Control.Monad.Effect.Trace (runPrintingTrace)
|
import Control.Monad.Effect.Trace (runPrintingTrace)
|
||||||
import Data.Abstract.Address
|
import Data.Abstract.Address
|
||||||
import Data.Abstract.Address.Precise
|
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Abstract.Value
|
import Data.Abstract.Value
|
||||||
import Data.Abstract.Type
|
import Data.Abstract.Type
|
||||||
|
@ -18,7 +18,6 @@ import Control.Arrow ((&&&))
|
|||||||
import Control.Monad.Effect.Trace as X (runIgnoringTrace, runReturningTrace)
|
import Control.Monad.Effect.Trace as X (runIgnoringTrace, runReturningTrace)
|
||||||
import Control.Monad ((>=>))
|
import Control.Monad ((>=>))
|
||||||
import Data.Abstract.Address as X
|
import Data.Abstract.Address as X
|
||||||
import Data.Abstract.Address.Precise as X
|
|
||||||
import Data.Abstract.Environment as Env
|
import Data.Abstract.Environment as Env
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Abstract.FreeVariables as X hiding (dropExtension)
|
import Data.Abstract.FreeVariables as X hiding (dropExtension)
|
||||||
|
Loading…
Reference in New Issue
Block a user