{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Haskell.Homplexity.Cyclomatic(
Cyclomatic
, cyclomaticT
, Depth
, depthT) where
import Data.Data
import Data.Generics.Uniplate.Data
import Language.Haskell.Exts.SrcLoc
import Language.Haskell.Exts.Syntax
import Language.Haskell.Homplexity.CodeFragment
import Language.Haskell.Homplexity.Metric
import Language.Haskell.Homplexity.Utilities
type MatchSet = [Match SrcLoc]
newtype Cyclomatic = Cyclomatic { unCyclo :: Int }
deriving (Eq, Ord, Enum, Num, Real, Integral)
cyclomaticT :: Proxy Cyclomatic
cyclomaticT = Proxy
instance Show Cyclomatic where
showsPrec _ (Cyclomatic cc) = ("cyclomatic complexity of " ++)
. shows cc
instance Metric Cyclomatic Function where
measure x = Cyclomatic . cyclomatic $ x
cyclomatic :: Data from => from -> Int
cyclomatic x = cyclomaticOfMatches x
+ cyclomaticOfExprs x
+ 1
cyclomaticOfMatches :: Data from => from -> Int
cyclomaticOfMatches = sumOf recurse . childrenBi
where
recurse :: MatchSet -> Int
recurse x = length x - 1 + sumOf cyclomaticOfMatches x
cyclomaticOfExprs :: forall from.
Data from => from -> Int
cyclomaticOfExprs = sumOf armCount . (universeBi :: from -> [Exp SrcLoc])
where
armCount (If {} ) = 2 - 1
armCount (MultiIf _ alts) = length alts - 1
armCount (LCase _ alts) = length alts - 1
armCount (Case _ _ alts) = length alts - 1
armCount _ = 0
newtype Depth = Depth Int
deriving (Eq, Ord, Enum, Num, Real, Integral)
depthT :: Proxy Depth
depthT = Proxy
instance Metric Depth Function where
measure (Function {..}) = Depth $ depthOfMatches functionRhs `max` depthOfMatches functionBinds
instance Show Depth where
showsPrec _ (Depth d) = ("branching depth of "++)
. shows d
depthOfExpr :: Exp SrcLoc -> Int
depthOfExpr x = fromEnum (isDecision x)+maxOf depthOfExpr (children x)
depthOfMatches :: Data from => [from] -> Int
depthOfMatches [] = 0
depthOfMatches [m ] = maxOf depthOfExpr (childrenBi m )
depthOfMatches ms = 1+maxOf depthOfExpr (concatMap childrenBi ms)
isDecision :: Exp SrcLoc -> Bool
isDecision If {} = True
isDecision MultiIf {} = True
isDecision LCase {} = True
isDecision Case {} = True
isDecision _ = False