Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Haskell.Homplexity.CodeFragment
Description
This module generalizes over types of code fragments that may need to be iterated upon and measured separately.
- class (Show c, Data (AST c), Data c) => CodeFragment c where
- fragmentName :: c -> String
- fragmentSlice :: c -> SrcSlice
- occurs :: (CodeFragment c, Data from) => from -> [c]
- occursOf :: (Data from, CodeFragment c) => Proxy c -> from -> [c]
- allOccurs :: (CodeFragment c, Data from) => from -> [c]
- allOccursOf :: (Data from, CodeFragment c) => Proxy c -> from -> [c]
- newtype Program = Program {
- allModules :: [Module SrcLoc]
- programT :: Proxy Program
- program :: [Module SrcLoc] -> Program
- data Module l :: * -> *
- moduleT :: Proxy (Module SrcLoc)
- data Function = Function {
- functionNames :: [String]
- functionLocations :: [SrcLoc]
- functionRhs :: [Rhs SrcLoc]
- functionBinds :: [Binds SrcLoc]
- functionT :: Proxy Function
- data TypeSignature = TypeSignature {
- loc :: SrcLoc
- identifiers :: [Name SrcLoc]
- theType :: Type SrcLoc
- typeSignatureT :: Proxy TypeSignature
- fragmentLoc :: CodeFragment c => c -> SrcLoc
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
Instances
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
.
Program
Constructors
Program | |
Fields
|
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
Alias for a function declaration
Constructors
Function | |
Fields
|
data TypeSignature Source
Type alias for a type signature of a function as a CodeFragment
Constructors
TypeSignature | |
Fields
|
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.