Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Binding = String
- type Code = String
- type Inspection = Binding -> Code -> Bool
- hasComposition :: Inspection
- hasGuards :: Inspection
- hasIf :: Inspection
- hasConditional :: Inspection
- hasLambda :: Inspection
- hasDirectRecursion :: Inspection
- hasUsage :: String -> Inspection
- hasComprehension :: Inspection
- hasBinding :: Inspection
- hasTypeDeclaration :: Inspection
- hasTypeSignature :: Inspection
- isParseable :: Code -> Bool
- negateInspection :: Inspection -> Inspection
- isName :: String -> HsName -> Bool
- nameOf :: HsName -> String
- bindingInMatch :: HsMatch -> String
- isBindingEO :: (EO -> Bool) -> Binding -> Code -> Bool
- isBindingRhs :: (HsRhs -> Bool) -> Binding -> Code -> Bool
- testWithBindingRhs :: ([HsRhs] -> Bool) -> Binding -> Code -> Bool
- withBindingRhs :: ([HsRhs] -> a) -> Binding -> Code -> Maybe a
- findBindingRhs :: String -> Code -> Maybe [HsRhs]
- rhsForBinding :: HsDecl -> [HsRhs]
- concatRhs :: HsRhs -> [HsDecl] -> [HsRhs]
- testWithCode :: ([HsDecl] -> Bool) -> Code -> Bool
- withCode :: ([HsDecl] -> a) -> Code -> Maybe a
- orFalse :: Maybe Bool -> Bool
- orNil :: Maybe [t] -> [t]
Documentation
type Inspection = Binding -> Code -> Bool Source
hasComposition :: Inspection Source
Inspection that tells whether a binding uses the composition operator .
in its definition
hasGuards :: Inspection Source
Inspection that tells whether a binding uses guards in its definition
Inspection that tells whether a binding uses ifs in its definition
hasConditional :: Inspection Source
Inspection that tells whether a binding uses ifs or guards in its definition
hasLambda :: Inspection Source
Inspection that tells whether a binding uses a lambda expression in its definition
hasDirectRecursion :: Inspection Source
Inspection that tells whether a binding is direct recursive
hasUsage :: String -> Inspection Source
Inspection that tells whether a binding uses the the given target binding in its definition
hasComprehension :: Inspection Source
Inspection that tells whether a binding uses lists comprehensions in its definition
hasBinding :: Inspection Source
Inspection that tells whether a top level binding exists
isParseable :: Code -> Bool Source
bindingInMatch :: HsMatch -> String Source
rhsForBinding :: HsDecl -> [HsRhs] Source