haskell-names: Name resolution library for Haskell

[ bsd3, language, library ] [ Propose Tags ]

This package takes modules parsed with `haskell-src-exts`, resolves used names and annotates the parsed module with scoping information.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1, 0.1.1, 0.1.2, 0.2, 0.2.1, 0.3, 0.3.1, 0.3.2, 0.3.2.1, 0.3.2.2, 0.3.2.3, 0.3.2.4, 0.3.2.5, 0.3.2.6, 0.3.2.7, 0.3.2.8, 0.3.3, 0.3.3.1, 0.3.3.2, 0.4, 0.4.1, 0.5.0, 0.5.1, 0.5.2, 0.5.3, 0.6.0, 0.7.0, 0.8.0, 0.9.0, 0.9.1, 0.9.2, 0.9.3, 0.9.4, 0.9.5, 0.9.6, 0.9.7, 0.9.8, 0.9.9
Change log CHANGELOG.md
Dependencies aeson (>=0.8.0.2 && <0.12), base (>=4.7 && <5), bytestring (>=0.10.4.0 && <0.11), containers (>=0.2 && <0.6), data-lens-light (>=0.1.2.1 && <0.2), filepath (>=1.1 && <1.5), haskell-src-exts (>=1.17 && <1.18), mtl (>=2.2.1 && <2.3), tagged (>=0.8.4 && <0.9), transformers (>=0.4.2.0 && <0.6), traverse-with-class (>=0.2.0.3 && <0.3), uniplate (>=1.5.1 && <1.7) [details]
License BSD-3-Clause
Author Philipp Schuster, Roman Cheplyaka, Lennart Augustsson
Maintainer Philipp Schuster
Revised Revision 1 made by HerbertValerioRiedel at 2018-10-10T20:31:29Z
Category Language
Home page http://documentup.com/haskell-suite/haskell-names
Source repo head: git clone git://github.com/haskell-suite/haskell-names.git
Uploaded by PhilippSchuster at 2016-07-18T20:39:18Z
Distributions
Reverse Dependencies 5 direct, 20 indirect [details]
Downloads 37394 total (63 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-07-18 [all 1 reports]

Readme for haskell-names-0.7.0

[back to package description]

haskell-names Build Status

haskell-names does name and module resolution for haskell-src-exts AST.

Namely, it can do the following:

  • For a list of modules, compute the list of symbols each module exports. This is called resolve.
  • For each name in a module, figure out what it refers to — whether it's bound locally (say, by a where clause) or globally (and then give its origin). This is called annotate.

Installation

If you're building a development version, then you might also need to install a development version of haskell-src-exts.

Environments

An environment is a map from module name to list of symbols the module exports. Symbols are for example types, classes, functions etc. We persist these lists in a JSON format. For example, here are a couple of entries from Prelude.names:

[
  {
    "name": "map",
    "entity": "value",
    "module": "GHC.Base"
  },
  {
    "name": "IO",
    "entity": "newtype",
    "module": "GHC.Types"
  },
  ...
]

As you see, each entity is annotated with the module where it was originally defined. Additionally, class methods, field selectors, and data constructors are annotated with the class or type they belong to.

haskell-names provides functions readSymbols and writeSymbols to read and write interface files.

Name resolution

The annotate function annotates the given module with scoping information.

Its essence is described in the article Open your name resolution.

Example

Let's say you have a module and you want to find out whether it uses Prelude.head.

module Main where

import Language.Haskell.Exts.Annotated (
  fromParseResult, parseModuleWithMode, defaultParseMode,
  parseFilename, prettyPrint, srcInfoSpan)
import Language.Haskell.Exts (
  Name(Ident), ModuleName(ModuleName))
import Language.Haskell.Names (
  loadBase, annotate, symbolName,
  Scoped(Scoped), NameInfo(GlobalSymbol))

import qualified Data.Map as Map (
  lookup)

import Data.Maybe (
  fromMaybe, listToMaybe)
import Data.List (
  nub)
import qualified Data.Foldable as Foldable (
  toList)
import Control.Monad (
  forM_, guard)

main :: IO ()
main = do

  -- read the program's source from stdin
  source <- getContents

  -- parse the program (using haskell-src-exts)
  let ast = fromParseResult (
        parseModuleWithMode defaultParseMode {parseFilename="stdin"} source)

  -- get base environment
  baseEnvironment <- loadBase

  -- get symbols defined in prelude
  let preludeSymbols = fromMaybe (error "Prelude not found") (
        Map.lookup (ModuleName "Prelude") baseEnvironment)

  -- find a Prelude symbol with name 'head' using the List monad
  let headSymbol = fromMaybe (error "Prelude.head not found") (
        listToMaybe (do
          preludeSymbol <- preludeSymbols
          guard (symbolName preludeSymbol == Ident "head")
          return preludeSymbol))

  -- annotate the AST
  let annotatedAST = annotate baseEnvironment ast

  -- get all annotations
  let annotations = Foldable.toList annotatedAST

  -- filter head Usages in List monad and remove duplicates
  let headUsages = nub (do
        Scoped (GlobalSymbol globalSymbol _) location <- annotations
        guard (globalSymbol == headSymbol)
        return location)

  case headUsages of
    [] ->
      putStrLn "Congratulations! Your code doesn't use Prelude.head"
    _ -> forM_ headUsages (\location ->
      putStrLn ("Prelude.head is used at " ++ (prettyPrint (srcInfoSpan location))))

Example invocation

% ./find-heads 
one = head [1]
^D
Prelude.head is used at stdin: (1:7) - (1:11)

% ./find-heads
import Prelude hiding (head)
import Data.Text

f = head (pack "foo")
^D
Congratulations! Your code doesn't use Prelude.head

API documentation

The core module you need is Language.Haskell.Names

Other modules are more experimental, less documented, and you probably don't need them anyway.

Known issues

See the list of all issues.

  • haskell-names doesn't perform validation yet. If a module is not valid Haskell, then the behaviour is undefined. See the issues marked as validation.
  • Symbol fixities are not recorded (#1)
  • Type variables are not resolved (#2)
  • Arrows are not fully supported (#8)

Maintainers

Philipp Schuster is the primary maintainer.

Adam Bergmark is the backup maintainer. Please get in touch with him if the primary maintainer cannot be reached.