Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.

Commit 1a98406

Browse files
authored
Merge pull request #80 from github/remove-redundant-hasspan
Remove redundant HasSpan class.
2 parents 5d86878 + 3e1f3bc commit 1a98406

File tree

12 files changed

+83
-67
lines changed

12 files changed

+83
-67
lines changed

semantic.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,6 @@ library
120120
, Data.Abstract.FreeVariables
121121
, Data.Abstract.AccessControls.Class
122122
, Data.Abstract.AccessControls.Instances
123-
, Data.Abstract.HasSpan
124123
, Data.Abstract.Heap
125124
, Data.Abstract.Live
126125
, Data.Abstract.Module

src/Data/Abstract/Evaluatable.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,6 @@ module Data.Abstract.Evaluatable
55
, traceResolve
66
-- * Preludes
77
, HasPrelude(..)
8-
-- * Spans
9-
, HasSpan(..)
108
-- * Effects
119
, EvalError(..)
1210
, throwEvalError
@@ -37,11 +35,10 @@ import Data.Language
3735
import Data.Scientific (Scientific)
3836
import Data.Semigroup.App
3937
import Data.Semigroup.Foldable
40-
import Data.Span (emptySpan)
38+
import Data.Span (HasSpan(..), emptySpan)
4139
import Data.Sum hiding (project)
4240
import Data.Term
4341
import Prologue
44-
import Data.Abstract.HasSpan
4542

4643
-- | The 'Evaluatable' class defines the necessary interface for a term to be evaluated. While a default definition of 'eval' is given, instances with computational content must implement 'eval' to perform their small-step operational semantics.
4744
class (Show1 constr, Foldable constr) => Evaluatable constr where

src/Data/Abstract/HasSpan.hs

Lines changed: 0 additions & 19 deletions
This file was deleted.

src/Data/Location.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Data.Location
88

99
import Prologue
1010

11+
import Control.Lens.Lens
1112
import Data.JSON.Fields
1213
import Data.Range
1314
import Data.Span
@@ -20,5 +21,9 @@ data Location
2021
deriving (Eq, Ord, Show, Generic, NFData)
2122
deriving Semigroup via GenericSemigroup Location
2223

24+
instance HasSpan Location where
25+
span = lens locationSpan (\l s -> l { locationSpan = s })
26+
{-# INLINE span #-}
27+
2328
instance ToJSONFields Location where
2429
toJSONFields Location{..} = toJSONFields locationByteRange <> toJSONFields locationSpan

src/Data/Quieterm.hs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,18 @@
1-
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
1+
{-# LANGUAGE GeneralizedNewtypeDeriving, RankNTypes, TypeFamilies #-}
22
module Data.Quieterm
33
( Quieterm(..)
44
, quieterm
55
) where
66

7+
import Prelude hiding (span)
8+
9+
import Control.Lens
710
import Control.DeepSeq
811
import Data.Abstract.Declarations (Declarations)
912
import Data.Abstract.FreeVariables (FreeVariables)
1013
import Data.Functor.Classes
1114
import Data.Functor.Foldable
15+
import Data.Span
1216
import Data.Term
1317
import Text.Show (showListWith)
1418

@@ -43,5 +47,9 @@ instance NFData1 f => NFData1 (Quieterm f) where
4347
instance (NFData1 f, NFData a) => NFData (Quieterm f a) where
4448
rnf = liftRnf rnf
4549

50+
instance HasSpan ann => HasSpan (Quieterm syntax ann) where
51+
span = lens (view span . unQuieterm) (\(Quieterm i) s -> Quieterm (set span s i))
52+
{-# INLINE span #-}
53+
4654
quieterm :: (Recursive term, Base term ~ TermF syntax ann) => term -> Quieterm syntax ann
4755
quieterm = cata Quieterm

src/Data/Span.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,11 @@ class HasSpan a where
4545

4646
start :: Lens' a Pos
4747
start = span.start
48+
{-# INLINE start #-}
4849

4950
end :: Lens' a Pos
5051
end = span.end
52+
{-# INLINE end #-}
5153

5254
instance HasSpan Span where
5355
span = id

src/Data/Syntax/Declaration.hs

Lines changed: 15 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,20 @@
22
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
33
module Data.Syntax.Declaration where
44

5-
import Prologue
5+
import Prelude hiding (span)
6+
import Prologue
7+
8+
import Control.Lens.Getter
9+
import qualified Data.Map.Strict as Map
10+
import qualified Data.Set as Set
611

712
import Control.Abstract hiding (AccessControl (..), Function)
813
import Data.Abstract.Evaluatable
914
import Data.Abstract.Name (__self)
10-
import qualified Data.Abstract.ScopeGraph as ScopeGraph
15+
import qualified Data.Abstract.ScopeGraph as ScopeGraph
1116
import Data.JSON.Fields
12-
import qualified Data.Map.Strict as Map
1317
import qualified Data.Reprinting.Scope as Scope
14-
import qualified Data.Set as Set
15-
import Data.Span (emptySpan)
18+
import Data.Span
1619
import Diffing.Algorithm
1720
import Reprinting.Tokenize hiding (Superclass)
1821

@@ -28,10 +31,10 @@ instance Diffable Function where
2831

2932
instance Evaluatable Function where
3033
eval _ _ Function{..} = do
31-
span <- ask @Span
32-
(name, associatedScope) <- declareFunction (declaredName functionName) ScopeGraph.Public span ScopeGraph.Function
34+
current <- ask @Span
35+
(name, associatedScope) <- declareFunction (declaredName functionName) ScopeGraph.Public current ScopeGraph.Function
3336

34-
params <- withScope associatedScope . for functionParameters $ \paramNode -> declareMaybeName (declaredName paramNode) Default ScopeGraph.Public (getSpan paramNode) ScopeGraph.Parameter Nothing
37+
params <- withScope associatedScope . for functionParameters $ \paramNode -> declareMaybeName (declaredName paramNode) Default ScopeGraph.Public (paramNode^.span) ScopeGraph.Parameter Nothing
3538

3639
addr <- lookupSlot (Declaration name)
3740
v <- function name params functionBody associatedScope
@@ -87,13 +90,13 @@ instance Diffable Method where
8790
-- local environment.
8891
instance Evaluatable Method where
8992
eval _ _ Method{..} = do
90-
span <- ask @Span
91-
(name, associatedScope) <- declareFunction (declaredName methodName) methodAccessControl span ScopeGraph.Method
93+
current <- ask @Span
94+
(name, associatedScope) <- declareFunction (declaredName methodName) methodAccessControl current ScopeGraph.Method
9295

9396
params <- withScope associatedScope $ do
9497
-- TODO: Should we give `self` a special Relation?
9598
declare (Declaration __self) ScopeGraph.Prelude ScopeGraph.Public emptySpan ScopeGraph.Unknown Nothing
96-
for methodParameters $ \paramNode -> declareMaybeName (declaredName paramNode) Default ScopeGraph.Public (getSpan paramNode) ScopeGraph.Parameter Nothing
99+
for methodParameters $ \paramNode -> declareMaybeName (declaredName paramNode) Default ScopeGraph.Public (paramNode^.span) ScopeGraph.Parameter Nothing
97100

98101
addr <- lookupSlot (Declaration name)
99102
v <- function name params methodBody associatedScope
@@ -161,8 +164,7 @@ instance Evaluatable VariableDeclaration where
161164
eval _ _ (VariableDeclaration []) = unit
162165
eval eval _ (VariableDeclaration decs) = do
163166
for_ decs $ \declaration -> do
164-
let span = getSpan declaration
165-
_ <- declareMaybeName (declaredName declaration) Default ScopeGraph.Public span ScopeGraph.VariableDeclaration Nothing
167+
_ <- declareMaybeName (declaredName declaration) Default ScopeGraph.Public (declaration^.span) ScopeGraph.VariableDeclaration Nothing
166168
eval declaration
167169
unit
168170

src/Data/Term.hs

Lines changed: 20 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE RankNTypes, TypeFamilies, TypeOperators, ScopedTypeVariables, FunctionalDependencies #-}
1+
{-# LANGUAGE FunctionalDependencies, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
22
module Data.Term
33
( Term(..)
44
, termIn
@@ -14,11 +14,15 @@ module Data.Term
1414
, Annotated (..)
1515
) where
1616

17+
import Prelude hiding (span)
1718
import Prologue
18-
import Data.Aeson
19-
import Data.JSON.Fields
20-
import Text.Show
19+
20+
import Control.Lens.Lens
21+
import Data.Aeson
22+
import Data.JSON.Fields
23+
import Data.Span
2124
import qualified Data.Sum as Sum
25+
import Text.Show
2226

2327
-- | A Term with an abstract syntax tree and an annotation.
2428
newtype Term syntax ann = Term { unTerm :: TermF syntax ann (Term syntax ann) }
@@ -40,6 +44,18 @@ guardTerm = Sum.projectGuard . termOut
4044
data TermF syntax ann recur = In { termFAnnotation :: ann, termFOut :: syntax recur }
4145
deriving (Eq, Ord, Foldable, Functor, Show, Traversable, Generic1)
4246

47+
annotationLens :: Lens' (TermF syntax ann recur) ann
48+
annotationLens = lens termFAnnotation (\t a -> t { termFAnnotation = a })
49+
{-# INLINE annotationLens #-}
50+
51+
instance HasSpan ann => HasSpan (TermF syntax ann recur) where
52+
span = annotationLens.span
53+
{-# INLINE span #-}
54+
55+
instance HasSpan ann => HasSpan (Term syntax ann) where
56+
span = inner.span where inner = lens unTerm (\t i -> t { unTerm = i })
57+
{-# INLINE span #-}
58+
4359
-- | A convenience typeclass to get the annotation out of a 'Term' or 'TermF'.
4460
-- Useful in term-rewriting algebras.
4561
class Annotated t ann | t -> ann where

src/Language/PHP/Syntax.hs

Lines changed: 10 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,13 @@
22
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
33
module Language.PHP.Syntax where
44

5+
import Prelude hiding (span)
6+
import Prologue hiding (Text)
7+
8+
import Control.Lens.Getter
9+
import qualified Data.Map.Strict as Map
10+
import qualified Data.Text as T
11+
512
import Control.Abstract as Abstract
613
import Data.Abstract.BaseError
714
import Data.Abstract.Evaluatable as Abstract
@@ -10,10 +17,8 @@ import Data.Abstract.Path
1017
import qualified Data.Abstract.ScopeGraph as ScopeGraph
1118
import Data.JSON.Fields
1219
import qualified Data.Language as Language
13-
import qualified Data.Map.Strict as Map
14-
import qualified Data.Text as T
20+
import Data.Span
1521
import Diffing.Algorithm
16-
import Prologue hiding (Text)
1722

1823
newtype Text a = Text { value :: T.Text }
1924
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
@@ -174,8 +179,7 @@ instance Evaluatable QualifiedName where
174179
eval _ _ (QualifiedName obj iden) = do
175180
-- TODO: Consider gensym'ed names used for References.
176181
name <- maybeM (throwNoNameError obj) (declaredName obj)
177-
let objSpan = getSpan obj
178-
reference (Reference name) objSpan ScopeGraph.Identifier (Declaration name)
182+
reference (Reference name) (obj^.span) ScopeGraph.Identifier (Declaration name)
179183
childScope <- associatedScope (Declaration name)
180184

181185
propName <- maybeM (throwNoNameError iden) (declaredName iden)
@@ -185,8 +189,7 @@ instance Evaluatable QualifiedName where
185189
currentFrameAddress <- currentFrame
186190
frameAddress <- newFrame childScope (Map.singleton Lexical (Map.singleton currentScopeAddress currentFrameAddress))
187191
withScopeAndFrame frameAddress $ do
188-
let propSpan = getSpan iden
189-
reference (Reference propName) propSpan ScopeGraph.Identifier (Declaration propName)
192+
reference (Reference propName) (iden^.span) ScopeGraph.Identifier (Declaration propName)
190193
slot <- lookupSlot (Declaration propName)
191194
deref slot
192195
Nothing ->

src/Language/Python/Syntax.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -3,24 +3,27 @@
33
{-# OPTIONS_GHC -fno-warn-orphans #-} -- FIXME
44
module Language.Python.Syntax where
55

6+
import Prelude hiding (span)
7+
import Prologue
8+
9+
import Control.Lens.Getter
10+
import Data.Aeson hiding (object)
11+
import qualified Data.List as List
12+
import qualified Data.List.NonEmpty as NonEmpty
13+
import qualified Data.Map.Strict as Map
14+
import qualified Data.Text as T
15+
import System.FilePath.Posix
16+
617
import Control.Abstract.Heap
718
import Control.Abstract.ScopeGraph hiding (Import)
819
import Data.Abstract.BaseError
920
import Data.Abstract.Evaluatable
1021
import Data.Abstract.Module
1122
import qualified Data.Abstract.ScopeGraph as ScopeGraph
12-
import Data.Aeson hiding (object)
13-
import Data.Functor.Classes.Generic
1423
import Data.JSON.Fields
1524
import qualified Data.Language as Language
16-
import qualified Data.List as List
17-
import qualified Data.List.NonEmpty as NonEmpty
18-
import qualified Data.Map.Strict as Map
19-
import qualified Data.Text as T
25+
import Data.Span
2026
import Diffing.Algorithm
21-
import GHC.Generics
22-
import Prologue
23-
import System.FilePath.Posix
2427

2528
data QualifiedName
2629
= QualifiedName { paths :: NonEmpty FilePath }
@@ -132,8 +135,7 @@ instance Evaluatable Import where
132135

133136
-- Add declaration of the alias name to the current scope (within our current module).
134137
aliasName <- maybeM (throwNoNameError aliasTerm) (declaredAlias aliasTerm)
135-
let aliasSpan = getSpan aliasTerm
136-
declare (Declaration aliasName) Default Public aliasSpan ScopeGraph.UnqualifiedImport (Just importScope)
138+
declare (Declaration aliasName) Default Public (aliasTerm^.span) ScopeGraph.UnqualifiedImport (Just importScope)
137139
-- Retrieve the frame slot for the new declaration.
138140
aliasSlot <- lookupSlot (Declaration aliasName)
139141
assign aliasSlot =<< object aliasFrame
@@ -171,8 +173,7 @@ instance Evaluatable Import where
171173
aliasName <- maybeM (throwNoNameError aliasTerm) (declaredAlias aliasTerm)
172174
aliasValue <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
173175
if aliasValue /= aliasName then do
174-
let aliasSpan = getSpan aliasTerm
175-
insertImportReference (Reference aliasName) aliasSpan ScopeGraph.Identifier (Declaration aliasValue) scopeAddress
176+
insertImportReference (Reference aliasName) (aliasTerm^.span) ScopeGraph.Identifier (Declaration aliasValue) scopeAddress
176177
else
177178
pure ()
178179

@@ -198,8 +199,7 @@ instance Evaluatable QualifiedImport where
198199
go [] = pure ()
199200
go (((nameTerm, name), modulePath) : namesAndPaths) = do
200201
scopeAddress <- newScope mempty
201-
let nameSpan = getSpan nameTerm
202-
declare (Declaration name) Default Public nameSpan ScopeGraph.QualifiedImport (Just scopeAddress)
202+
declare (Declaration name) Default Public (nameTerm^.span) ScopeGraph.QualifiedImport (Just scopeAddress)
203203
aliasSlot <- lookupSlot (Declaration name)
204204
-- a.b.c
205205
withScope scopeAddress $

0 commit comments

Comments
 (0)