homplexity-0.4.4.1: Haskell code quality tool

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Homplexity.CodeFragment

Description

This module generalizes over types of code fragments that may need to be iterated upon and measured separately.

Synopsis

Documentation

class (Show c, Data (AST c), Data c) => CodeFragment c where Source

Class CodeFragment allows for: * both selecting direct or all descendants of the given type of object within another structure (with occurs and allOccurs) * naming the object to allow user to distinguish it.

In order to compute selection, we just need to know which AST nodes contain the given object, and how to extract this given object from AST, if it is there (matchAST).:w

Minimal complete definition

matchAST, fragmentName

occurs :: (CodeFragment c, Data from) => from -> [c] Source

Direct occurences of given CodeFragment fragment within another structure.

occursOf :: (Data from, CodeFragment c) => Proxy c -> from -> [c] Source

Explicitly typed variant of occurs.

allOccurs :: (CodeFragment c, Data from) => from -> [c] Source

allOccursOf :: (Data from, CodeFragment c) => Proxy c -> from -> [c] Source

Explicitly typed variant of allOccurs.

newtype Program Source

Program

Constructors

Program 

Fields

allModules :: [Module SrcLoc]
 

programT :: Proxy Program Source

Proxy for passing Program type as an argument.

program :: [Module SrcLoc] -> Program Source

Smart constructor for adding cross-references in the future.

data Module l :: * -> *

Constructors

Module l (Maybe (ModuleHead l)) [ModulePragma l] [ImportDecl l] [Decl l] 
XmlPage l (ModuleName l) [ModulePragma l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l] 
XmlHybrid l (Maybe (ModuleHead l)) [ModulePragma l] [ImportDecl l] [Decl l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l] 

Instances

Functor Module 
Foldable Module 
Traversable Module 
Annotated Module 
AppFixity Module 
Eq l => Eq (Module l) 
Data l => Data (Module l) 
Ord l => Ord (Module l) 
Show l => Show (Module l) 
Generic (Module l) 
CodeFragment (Module SrcLoc) Source 
type Rep (Module l) = D1 D1Module ((:+:) (C1 C1_0Module ((:*:) ((:*:) (S1 NoSelector (Rec0 l)) (S1 NoSelector (Rec0 (Maybe (ModuleHead l))))) ((:*:) (S1 NoSelector (Rec0 [ModulePragma l])) ((:*:) (S1 NoSelector (Rec0 [ImportDecl l])) (S1 NoSelector (Rec0 [Decl l])))))) ((:+:) (C1 C1_1Module ((:*:) ((:*:) (S1 NoSelector (Rec0 l)) ((:*:) (S1 NoSelector (Rec0 (ModuleName l))) (S1 NoSelector (Rec0 [ModulePragma l])))) ((:*:) ((:*:) (S1 NoSelector (Rec0 (XName l))) (S1 NoSelector (Rec0 [XAttr l]))) ((:*:) (S1 NoSelector (Rec0 (Maybe (Exp l)))) (S1 NoSelector (Rec0 [Exp l])))))) (C1 C1_2Module ((:*:) ((:*:) ((:*:) (S1 NoSelector (Rec0 l)) (S1 NoSelector (Rec0 (Maybe (ModuleHead l))))) ((:*:) (S1 NoSelector (Rec0 [ModulePragma l])) (S1 NoSelector (Rec0 [ImportDecl l])))) ((:*:) ((:*:) (S1 NoSelector (Rec0 [Decl l])) (S1 NoSelector (Rec0 (XName l)))) ((:*:) (S1 NoSelector (Rec0 [XAttr l])) ((:*:) (S1 NoSelector (Rec0 (Maybe (Exp l)))) (S1 NoSelector (Rec0 [Exp l]))))))))) 

moduleT :: Proxy (Module SrcLoc) Source

Proxy for passing Module type as an argument.

data Function Source

Alias for a function declaration

Constructors

Function 

Fields

functionNames :: [String]
 
functionLocations :: [SrcLoc]
 
functionRhs :: [Rhs SrcLoc]
 
functionBinds :: [Binds SrcLoc]
 

functionT :: Proxy Function Source

Proxy for passing Function type as an argument.

data TypeSignature Source

Type alias for a type signature of a function as a CodeFragment

Constructors

TypeSignature 

Fields

loc :: SrcLoc
 
identifiers :: [Name SrcLoc]
 
theType :: Type SrcLoc
 

typeSignatureT :: Proxy TypeSignature Source

Proxy for passing Program type as an argument.

fragmentLoc :: CodeFragment c => c -> SrcLoc Source

First location for each CodeFragment - for convenient reporting.