Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module generalizes over types of code fragments that may need to be iterated upon and measured separately.
Synopsis
- 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 DataDef = DataDef {
- dataDefName :: String
- dataDefCtors :: Either [QualConDecl SrcLoc] [GadtDecl SrcLoc]
- dataDefT :: Proxy DataDef
- data TypeSignature = TypeSignature {
- loc :: SrcLoc
- identifiers :: [Name SrcLoc]
- theType :: Type SrcLoc
- typeSignatureT :: Proxy TypeSignature
- data TypeClass = TypeClass {}
- typeClassT :: Proxy TypeClass
- 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
matchAST, fragmentName
fragmentName :: c -> String Source #
fragmentSlice :: c -> SrcSlice Source #
Instances
CodeFragment TypeClass Source # | |
CodeFragment TypeSignature Source # | |
Defined in Language.Haskell.Homplexity.CodeFragment type AST TypeSignature :: Type matchAST :: AST TypeSignature -> Maybe TypeSignature fragmentName :: TypeSignature -> String Source # | |
CodeFragment DataDef Source # | |
CodeFragment Function Source # | |
CodeFragment Program Source # | |
CodeFragment (Module SrcLoc) Source # | |
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
Program | |
|
Instances
Data Program Source # | |
Defined in Language.Haskell.Homplexity.CodeFragment gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Program -> c Program # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Program # toConstr :: Program -> Constr # dataTypeOf :: Program -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Program) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Program) # gmapT :: (forall b. Data b => b -> b) -> Program -> Program # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Program -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Program -> r # gmapQ :: (forall d. Data d => d -> u) -> Program -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Program -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Program -> m Program # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Program -> m Program # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Program -> m Program # | |
Show Program Source # | |
CodeFragment Program Source # | |
program :: [Module SrcLoc] -> Program Source #
Smart constructor for adding cross-references in the future.
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
Function | |
|
Instances
Data Function Source # | |
Defined in Language.Haskell.Homplexity.CodeFragment gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Function -> c Function # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Function # toConstr :: Function -> Constr # dataTypeOf :: Function -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Function) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Function) # gmapT :: (forall b. Data b => b -> b) -> Function -> Function # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Function -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Function -> r # gmapQ :: (forall d. Data d => d -> u) -> Function -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Function -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Function -> m Function # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Function -> m Function # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Function -> m Function # | |
Show Function Source # | |
CodeFragment Function Source # | |
Metric Depth Function Source # | |
Metric Cyclomatic Function Source # | |
Defined in Language.Haskell.Homplexity.Cyclomatic measure :: Function -> Cyclomatic Source # |
Alias for a data
declaration
DataDef | |
|
Instances
Data DataDef Source # | |
Defined in Language.Haskell.Homplexity.CodeFragment gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDef -> c DataDef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataDef # toConstr :: DataDef -> Constr # dataTypeOf :: DataDef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataDef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataDef) # gmapT :: (forall b. Data b => b -> b) -> DataDef -> DataDef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDef -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDef -> r # gmapQ :: (forall d. Data d => d -> u) -> DataDef -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDef -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDef -> m DataDef # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDef -> m DataDef # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDef -> m DataDef # | |
Show DataDef Source # | |
CodeFragment DataDef Source # | |
Metric RecordFieldsCount DataDef Source # | |
Defined in Language.Haskell.Homplexity.RecordFieldsCount measure :: DataDef -> RecordFieldsCount Source # |
data TypeSignature Source #
Type alias for a type signature of a function as a CodeFragment
TypeSignature | |
|
Instances
typeSignatureT :: Proxy TypeSignature Source #
Proxy for passing TypeSignature
type as an argument.
Alias for a class signature
Instances
typeClassT :: Proxy TypeClass Source #
Proxy for passing TypeClass
type as an argument.
fragmentLoc :: CodeFragment c => c -> SrcLoc Source #
First location for each CodeFragment
- for convenient reporting.