weeder-2.8.0: Detect dead code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Weeder

Synopsis

Analysis

data Analysis Source #

All information maintained by analyseHieFile.

Constructors

Analysis 

Fields

  • dependencyGraph :: Graph Declaration

    A graph between declarations, capturing dependencies.

  • declarationSites :: Map Declaration (Set Int)

    A partial mapping between declarations and their line numbers. This Map is partial as we don't always know where a Declaration was defined (e.g., it may come from a package without source code). We capture a set of sites, because a declaration may be defined in multiple locations, e.g., a type signature for a function separate from its definition.

  • implicitRoots :: Set Root

    Stores information on Declarations that may be automatically marked as always reachable. This is used, for example, to capture knowledge not yet modelled in weeder, or to mark all instances of a class as roots.

  • exports :: Map Module (Set Declaration)

    All exports for a given module.

  • modulePaths :: Map Module FilePath

    A map from modules to the file path to the .hs file defining them.

  • prettyPrintedType :: Map Declaration String

    Used to match against the types of instances and to replace the appearance of declarations in the output

  • requestedEvidence :: Map Declaration (Set Name)

    Map from declarations to the names containing evidence uses that should be followed and treated as dependencies of the declaration. We use this to be able to delay analysing evidence uses until later, allowing us to begin the rest of the analysis before we have read all hie files.

Instances

Instances details
Monoid Analysis Source # 
Instance details

Defined in Weeder

Semigroup Analysis Source # 
Instance details

Defined in Weeder

Generic Analysis Source # 
Instance details

Defined in Weeder

Associated Types

type Rep Analysis :: Type -> Type #

Methods

from :: Analysis -> Rep Analysis x #

to :: Rep Analysis x -> Analysis #

NFData Analysis Source # 
Instance details

Defined in Weeder

Methods

rnf :: Analysis -> () #

type Rep Analysis Source # 
Instance details

Defined in Weeder

analyseEvidenceUses :: RefMap TypeIndex -> Analysis -> Analysis Source #

Follow evidence uses listed under requestedEvidence back to their instance bindings, and connect their corresponding declaration to those bindings.

analyseHieFile :: MonadState Analysis m => Config -> HieFile -> m () Source #

Incrementally update Analysis with information in a HieFile.

emptyAnalysis :: Analysis Source #

The empty analysis - the result of analysing zero .hie files.

outputableDeclarations :: Analysis -> Set Declaration Source #

The set of all declarations that could possibly appear in the output.

Reachability

data Root Source #

A root for reachability analysis.

Constructors

DeclarationRoot Declaration

A given declaration is a root.

InstanceRoot

We store extra information for instances in order to be able to specify e.g. all instances of a class as roots.

Fields

ModuleRoot Module

All exported declarations in a module are roots.

Instances

Instances details
Generic Root Source # 
Instance details

Defined in Weeder

Associated Types

type Rep Root :: Type -> Type #

Methods

from :: Root -> Rep Root x #

to :: Rep Root x -> Root #

NFData Root Source # 
Instance details

Defined in Weeder

Methods

rnf :: Root -> () #

Eq Root Source # 
Instance details

Defined in Weeder

Methods

(==) :: Root -> Root -> Bool #

(/=) :: Root -> Root -> Bool #

Ord Root Source # 
Instance details

Defined in Weeder

Methods

compare :: Root -> Root -> Ordering #

(<) :: Root -> Root -> Bool #

(<=) :: Root -> Root -> Bool #

(>) :: Root -> Root -> Bool #

(>=) :: Root -> Root -> Bool #

max :: Root -> Root -> Root #

min :: Root -> Root -> Root #

type Rep Root Source # 
Instance details

Defined in Weeder

reachable :: Analysis -> Set Root -> Set Declaration Source #

Determine the set of all declaration reachable from a set of roots.

Declarations

data Declaration Source #

Constructors

Declaration 

Fields

Instances

Instances details
Generic Declaration Source # 
Instance details

Defined in Weeder

Associated Types

type Rep Declaration :: Type -> Type #

Show Declaration Source # 
Instance details

Defined in Weeder

NFData Declaration Source # 
Instance details

Defined in Weeder

Methods

rnf :: Declaration -> () #

Eq Declaration Source # 
Instance details

Defined in Weeder

Ord Declaration Source # 
Instance details

Defined in Weeder

type Rep Declaration Source # 
Instance details

Defined in Weeder

type Rep Declaration = D1 ('MetaData "Declaration" "Weeder" "weeder-2.8.0-LLWyvDLkfMUFuW7r7YiEQF" 'False) (C1 ('MetaCons "Declaration" 'PrefixI 'True) (S1 ('MetaSel ('Just "declModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Module) :*: S1 ('MetaSel ('Just "declOccName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OccName)))