{-# LANGUAGE RankNTypes #-}
module HsDev.Symbols.Parsed (
Ann, Parsed,
qnames, names, binders, locals, globals, references, unresolveds,
usages, named, imports, declarations, moduleNames,
annL, symbolL, file, pos, defPos, resolvedName,
isBinder, isLocal, isGlobal, isReference, isUnresolved, resolveError,
refsTo, refsToName,
nameInfoL, positionL, regionL, fileL,
symbolNameL,
prettyPrint
) where
import Control.Lens
import Data.Data
import Data.Data.Lens
import Data.Maybe (isJust)
import Data.Text (Text)
import Language.Haskell.Exts hiding (Name(..))
import qualified Language.Haskell.Exts as E (Name(..))
import Language.Haskell.Names
import HsDev.Symbols.Name
import HsDev.Symbols.Location (Position(..), positionLine, positionColumn, Region(..), region)
type Ann = Scoped SrcSpanInfo
type Parsed = Module Ann
qnames :: Data (ast Ann) => Traversal' (ast Ann) (QName Ann)
qnames = biplate
names :: Data (ast Ann) => Traversal' (ast Ann) (E.Name Ann)
names = biplate
binders :: Annotated ast => Traversal' (ast Ann) (ast Ann)
binders = filtered isBinder
locals :: Annotated ast => Traversal' (ast Ann) (ast Ann)
locals = filtered isLocal
globals :: Annotated ast => Traversal' (ast Ann) (ast Ann)
globals = filtered isGlobal
references :: Annotated ast => Traversal' (ast Ann) (ast Ann)
references = filtered isReference
unresolveds :: Annotated ast => Traversal' (ast Ann) (ast Ann)
unresolveds = filtered isUnresolved
usages :: Annotated ast => Name -> Traversal' (ast Ann) (ast Ann)
usages = filtered . refsTo
named :: Annotated ast => Text -> Traversal' (ast Ann) (ast Ann)
named = filtered . refsToName
imports :: Data (ast Ann) => Traversal' (ast Ann) (ImportDecl Ann)
imports = biplate
declarations :: Data (ast Ann) => Traversal' (ast Ann) (Decl Ann)
declarations = biplate
moduleNames :: Data (ast Ann) => Traversal' (ast Ann) (ModuleName Ann)
moduleNames = biplate
annL :: Annotated ast => Lens' (ast a) a
annL = lens ann (\v a' -> amap (const a') v)
symbolL :: Data a => Traversal' a Symbol
symbolL = biplate
file :: Annotated ast => Lens' (ast Ann) FilePath
file = annL . fileL
pos :: (Annotated ast, SrcInfo isrc, Data isrc) => Lens' (ast isrc) Position
pos = annL . positionL
defPos :: Annotated ast => Traversal' (ast Ann) Position
defPos = annL . defLoc' where
defLoc' :: Traversal' Ann Position
defLoc' f (Scoped (LocalValue s) i) = Scoped <$> (LocalValue <$> positionL f s) <*> pure i
defLoc' f (Scoped (TypeVar s) i) = Scoped <$> (TypeVar <$> positionL f s) <*> pure i
defLoc' f (Scoped ValueBinder i) = Scoped ValueBinder <$> positionL f i
defLoc' f (Scoped TypeBinder i) = Scoped TypeBinder <$> positionL f i
defLoc' _ s = pure s
resolvedName :: Annotated ast => Traversal' (ast Ann) Name
resolvedName = annL . nameInfoL . symbolL . symbolNameL
isBinder :: Annotated ast => ast Ann -> Bool
isBinder e = (e ^. annL . nameInfoL) `elem` [TypeBinder, ValueBinder]
isLocal :: Annotated ast => ast Ann -> Bool
isLocal e = case e ^. annL . nameInfoL of
LocalValue _ -> True
TypeVar _ -> True
_ -> False
isGlobal :: Annotated ast => ast Ann -> Bool
isGlobal e = case e ^. annL . nameInfoL of
GlobalSymbol _ _ -> True
_ -> False
isReference :: Annotated ast => ast Ann -> Bool
isReference e = isLocal e || isGlobal e
isUnresolved :: Annotated ast => ast Ann -> Bool
isUnresolved = isJust . resolveError
resolveError :: Annotated ast => ast Ann -> Maybe String
resolveError e = case e ^. annL . nameInfoL of
ScopeError err -> Just $ ppError err
_ -> Nothing
refsTo :: Annotated ast => Name -> ast Ann -> Bool
refsTo n a = Just n == a ^? resolvedName
refsToName :: Annotated ast => Text -> ast Ann -> Bool
refsToName n a = Just n == fmap nameIdent (a ^? resolvedName)
nameInfoL :: Lens' (Scoped a) (NameInfo a)
nameInfoL = lens g' s' where
g' (Scoped i _) = i
s' (Scoped _ s) i' = Scoped i' s
positionL :: (SrcInfo isrc, Data isrc) => Lens' isrc Position
positionL = lens g' s' where
g' i = Position l c where
SrcLoc _ l c = getPointLoc i
s' i (Position l c) = over biplate upd i where
Position sl sc = g' i
upd :: SrcLoc -> SrcLoc
upd (SrcLoc f' l' c')
| l' == sl = SrcLoc f' l (c' - sc + c)
| otherwise = SrcLoc f' (l' - sl + l) c'
regionL :: Annotated ast => Lens' (ast Ann) Region
regionL = lens g' s' where
g' i = case ann i of
Scoped _ sinfo -> toPos (srcSpanStart span') `region` toPos (srcSpanEnd span') where
span' = srcInfoSpan sinfo
toPos = uncurry Position
s' i (Region s e) = amap (fmap upd) i where
upd :: SrcSpanInfo -> SrcSpanInfo
upd sinfo = sinfo {
srcInfoSpan = (srcInfoSpan sinfo) {
srcSpanStartLine = s ^. positionLine,
srcSpanStartColumn = s ^. positionColumn,
srcSpanEndLine = e ^. positionLine,
srcSpanEndColumn = e ^. positionColumn },
srcInfoPoints = [] }
fileL :: (SrcInfo isrc, Data isrc) => Lens' isrc FilePath
fileL = lens g' s' where
g' = fileName
s' i f = set biplate f i
symbolNameL :: Lens' Symbol Name
symbolNameL = lens g' s' where
g' sym' = Qual () (symbolModule sym') (symbolName sym')
s' sym' (Qual _ m n) = sym' { symbolModule = m, symbolName = n }
s' sym' (UnQual _ n) = sym' { symbolName = n }
s' sym' _ = sym'