{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -fno-warn-unused-binds #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} -- UUAGC 0.9.55 (src/GLuaFixer/AG/ASTLint.ag) module GLuaFixer.AG.ASTLint where {-# LINE 9 "src/GLuaFixer/AG/../../GLua/AG/Token.ag" #-} import GHC.Generics import Text.ParserCombinators.UU.BasicInstances hiding (pos) {-# LINE 19 "src/GLuaFixer/AG/ASTLint.hs" #-} {-# LINE 10 "src/GLuaFixer/AG/../../GLua/AG/AST.ag" #-} import Data.Aeson import GHC.Generics import GLua.AG.Token import GLua.TokenTypes () {-# LINE 27 "src/GLuaFixer/AG/ASTLint.hs" #-} {-# LINE 10 "src/GLuaFixer/AG/ASTLint.ag" #-} import Data.Char (isLower, isUpper) import qualified Data.Map.Strict as M import Data.Maybe import qualified Data.Set as S import GLua.AG.AST import qualified GLua.AG.PrettyPrint as PP import qualified GLua.AG.Token as T import GLua.TokenTypes import GLuaFixer.LintMessage import GLuaFixer.LintSettings {-# LINE 41 "src/GLuaFixer/AG/ASTLint.hs" #-} {-# LINE 28 "src/GLuaFixer/AG/ASTLint.ag" #-} warn :: Region -> Issue -> FilePath -> LintMessage warn pos issue = LintMessage LintWarning pos issue -- Used in detecting "not (a == b)" kind of things oppositeBinOp :: BinOp -> Maybe String oppositeBinOp ALT = Just ">=" oppositeBinOp AGT = Just "<=" oppositeBinOp ALEQ = Just ">" oppositeBinOp AGEQ = Just "<" oppositeBinOp ANEq = Just "==" oppositeBinOp AEq = Just "~=" oppositeBinOp _ = Nothing -- Checks whether a variable shadows existing variables checkShadows :: [M.Map String (Bool, Region)] -> MToken -> Maybe (FilePath -> LintMessage) checkShadows [] _ = Nothing checkShadows _ (MToken _ (Identifier "_")) = Nothing -- Exception for vars named '_' checkShadows (scope : scs) mtok' = if M.member lbl scope then Just $ warn (mpos mtok') $ VariableShadows lbl location else checkShadows scs mtok' where lbl = tokenLabel mtok' location = snd $ fromMaybe (error "checkShadows fromMaybe") $ M.lookup lbl scope -- Determines whether a variable is local -- It is local if it does not exist in any but the topmost (global) scope -- it may or may not exist in the topmost scope. isVariableLocal :: [M.Map String (Bool, Region)] -> String -> Bool isVariableLocal [] _ = False isVariableLocal [_] _ = False isVariableLocal (scope : scs) var = case M.lookup var scope of Just _ -> True Nothing -> isVariableLocal scs var -- Registers a variable as global variable when it hasn't been -- introduced in any of the visible scopes registerVariable :: [M.Map String (Bool, Region)] -> Region -> String -> Bool -> [M.Map String (Bool, Region)] registerVariable [] _ _ _ = error "cannot register top level variable" registerVariable (scope : []) pos var used = [ case M.lookup var scope of Just (used', pos') -> M.insert var (used || used', pos') scope Nothing -> M.insert var (used, pos) scope ] -- global scope registerVariable (scope : scs) pos var used = case M.lookup var scope of Just (True, _) -> scope : scs Just (False, pos') -> M.insert var (used, pos') scope : scs Nothing -> scope : registerVariable scs pos var used findSelf :: [MToken] -> Bool findSelf ((MToken _ (Identifier "self")) : _) = True findSelf _ = False data VariableStyle = StartsLowerCase | StartsUpperCase | VariableStyleNeither deriving (Eq) data DeterminedVariableStyle = VarStyleNotDetermined | VarStyleDetermined !VariableStyle combineDeterminedVarStyle :: DeterminedVariableStyle -> VariableStyle -> DeterminedVariableStyle combineDeterminedVarStyle old new = case old of VarStyleNotDetermined -> VarStyleDetermined new VarStyleDetermined VariableStyleNeither -> VarStyleDetermined new _ -> old determineVariableStyle :: String -> VariableStyle determineVariableStyle = \case [] -> VariableStyleNeither (c : _) | isLower c -> StartsLowerCase | isUpper c -> StartsUpperCase | otherwise -> VariableStyleNeither variableStyleInconsistent :: DeterminedVariableStyle -> VariableStyle -> Bool variableStyleInconsistent determinedStyle varStyle = case determinedStyle of VarStyleNotDetermined -> False VarStyleDetermined VariableStyleNeither -> False VarStyleDetermined existing -> case varStyle of VariableStyleNeither -> False _ -> existing /= varStyle unknownIdentifier :: String unknownIdentifier = "Unknown identifier" {-# LINE 135 "src/GLuaFixer/AG/ASTLint.hs" #-} {-# LINE 647 "src/GLuaFixer/AG/ASTLint.ag" #-} inh_AST :: LintSettings -> Inh_AST inh_AST conf = Inh_AST { config_Inh_AST = conf , isMeta_Inh_AST = False , loopLevel_Inh_AST = 0 , globalDefinitions_Inh_AST = M.empty , mtokenPos_Inh_AST = emptyRg , scopeLevel_Inh_AST = 0 , scopes_Inh_AST = [M.empty] , funcName_Inh_AST = "" , isInModule_Inh_AST = False , variableStyle_Inh_AST = VarStyleNotDetermined } allAttributes :: LintSettings -> AST -> Syn_AST allAttributes conf p = wrap_AST (sem_AST p) (inh_AST conf) astWarnings :: LintSettings -> AST -> [String -> LintMessage] astWarnings conf p = warnings_Syn_AST $ allAttributes conf p globalDefinitions :: LintSettings -> AST -> M.Map String [Region] globalDefinitions conf p = globalDefinitions_Syn_AST $ allAttributes conf p {-# LINE 161 "src/GLuaFixer/AG/ASTLint.hs" #-} -- AReturn ----------------------------------------------------- -- cata sem_AReturn :: AReturn -> T_AReturn sem_AReturn (AReturn _pos _values) = (sem_AReturn_AReturn (sem_Region _pos) (sem_MExprList _values)) sem_AReturn (NoReturn) = (sem_AReturn_NoReturn) -- semantic domain type T_AReturn = (AReturn, T_AReturn_1) type T_AReturn_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), Int, DeterminedVariableStyle, ([String -> LintMessage])) data Inh_AReturn = Inh_AReturn {config_Inh_AReturn :: LintSettings, funcName_Inh_AReturn :: String, globalDefinitions_Inh_AReturn :: (M.Map String [Region]), isInModule_Inh_AReturn :: Bool, isMeta_Inh_AReturn :: Bool, loopLevel_Inh_AReturn :: Int, mtokenPos_Inh_AReturn :: Region, scopeLevel_Inh_AReturn :: Int, scopes_Inh_AReturn :: ([M.Map String (Bool, Region)]), variableStyle_Inh_AReturn :: DeterminedVariableStyle} data Syn_AReturn = Syn_AReturn {copy_Syn_AReturn :: AReturn, globalDefinitions_Syn_AReturn :: (M.Map String [Region]), identifier_Syn_AReturn :: String, isInModule_Syn_AReturn :: Bool, mtokenPos_Syn_AReturn :: Region, scopes_Syn_AReturn :: ([M.Map String (Bool, Region)]), statementCount_Syn_AReturn :: Int, variableStyle_Syn_AReturn :: DeterminedVariableStyle, warnings_Syn_AReturn :: ([String -> LintMessage])} wrap_AReturn :: T_AReturn -> Inh_AReturn -> Syn_AReturn wrap_AReturn sem (Inh_AReturn _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_AReturn _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOstatementCount _lhsOvariableStyle _lhsOwarnings) ) sem_AReturn_AReturn :: T_Region -> T_MExprList -> T_AReturn sem_AReturn_AReturn pos_ values_ = ( case (values_) of (_valuesIcopy, values_1) -> ( case (pos_) of (_posIcopy, _posIidentifier, _posIwarnings) -> ( case ( ( AReturn _posIcopy _valuesIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_AReturn_AReturn_1 :: T_AReturn_1 sem_AReturn_AReturn_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _valuesOscopes -> ( case ( ( _lhsIisMeta ) ) of _valuesOisMeta -> ( case ( ( _lhsIisInModule ) ) of _valuesOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _valuesOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _valuesOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _valuesOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _valuesOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _valuesOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valuesOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _valuesOfuncName -> ( case ( ( True ) ) of _valuesOtopLevel -> ( case ( ( True ) ) of _valuesOinParentheses -> ( case (values_1 _valuesOconfig _valuesOfuncName _valuesOglobalDefinitions _valuesOinParentheses _valuesOisInModule _valuesOisMeta _valuesOloopLevel _valuesOmtokenPos _valuesOscopeLevel _valuesOscopes _valuesOtopLevel _valuesOvariableStyle) of (_valuesIglobalDefinitions, _valuesIidentifier, _valuesIisInModule, _valuesImtokenPos, _valuesIscopes, _valuesIvariableStyle, _valuesIwarnings) -> ( case ( ( _valuesIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _posIidentifier _valuesIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _valuesIisInModule ) ) of _lhsOisInModule -> ( case ( ( _posIcopy ) ) of _lhsOmtokenPos -> ( case ( ( _valuesIscopes ) ) of _lhsOscopes -> ( case ( ( 1 ) ) of _lhsOstatementCount -> ( case ( ( _valuesIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _posIwarnings ++ _valuesIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_AReturn_AReturn_1 ) ) of (sem_AReturn_1) -> (_lhsOcopy, sem_AReturn_1) ) ) ) ) ) sem_AReturn_NoReturn :: T_AReturn sem_AReturn_NoReturn = ( case ( ( NoReturn ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_AReturn_NoReturn_1 :: T_AReturn_1 sem_AReturn_NoReturn_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( 0 ) ) of _lhsOstatementCount -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_AReturn_NoReturn_1 ) ) of (sem_AReturn_1) -> (_lhsOcopy, sem_AReturn_1) ) ) ) -- AST --------------------------------------------------------- -- cata sem_AST :: AST -> T_AST sem_AST (AST _comments _chunk) = (sem_AST_AST _comments (sem_Block _chunk)) -- semantic domain type T_AST = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> (AST, (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_AST = Inh_AST {config_Inh_AST :: LintSettings, funcName_Inh_AST :: String, globalDefinitions_Inh_AST :: (M.Map String [Region]), isInModule_Inh_AST :: Bool, isMeta_Inh_AST :: Bool, loopLevel_Inh_AST :: Int, mtokenPos_Inh_AST :: Region, scopeLevel_Inh_AST :: Int, scopes_Inh_AST :: ([M.Map String (Bool, Region)]), variableStyle_Inh_AST :: DeterminedVariableStyle} data Syn_AST = Syn_AST {copy_Syn_AST :: AST, globalDefinitions_Syn_AST :: (M.Map String [Region]), identifier_Syn_AST :: String, isInModule_Syn_AST :: Bool, mtokenPos_Syn_AST :: Region, scopes_Syn_AST :: ([M.Map String (Bool, Region)]), variableStyle_Syn_AST :: DeterminedVariableStyle, warnings_Syn_AST :: ([String -> LintMessage])} wrap_AST :: T_AST -> Inh_AST -> Syn_AST wrap_AST sem (Inh_AST _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_AST _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_AST_AST :: ([MToken]) -> T_Block -> T_AST sem_AST_AST comments_ chunk_ = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case (chunk_) of (_chunkIcopy, chunk_1) -> ( case ( ( AST comments_ _chunkIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _lhsIisMeta ) ) of _chunkOisMeta -> ( case ( ( _lhsIisInModule ) ) of _chunkOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _chunkOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _chunkOconfig -> ( case ( ( M.empty : _lhsIscopes ) ) of _chunkOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _chunkOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _chunkOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _chunkOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _chunkOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _chunkOfuncName -> ( case ( ( False ) ) of _chunkOisRepeat -> ( case (chunk_1 _chunkOconfig _chunkOfuncName _chunkOglobalDefinitions _chunkOisInModule _chunkOisMeta _chunkOisRepeat _chunkOloopLevel _chunkOmtokenPos _chunkOscopeLevel _chunkOscopes _chunkOvariableStyle) of (_chunkIglobalDefinitions, _chunkIidentifier, _chunkIisIfStatement, _chunkIisInModule, _chunkImtokenPos, _chunkIscopes, _chunkIstatementCount, _chunkIvariableStyle, _chunkIwarnings) -> ( case ( ( _chunkIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _chunkIidentifier ) ) of _lhsOidentifier -> ( case ( ( _chunkIisInModule ) ) of _lhsOisInModule -> ( case ( ( _chunkImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _chunkIscopes ) ) of _lhsOscopes -> ( case ( ( _chunkIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _chunkIwarnings ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) -- Args -------------------------------------------------------- -- cata sem_Args :: Args -> T_Args sem_Args (ListArgs _args) = (sem_Args_ListArgs (sem_MExprList _args)) sem_Args (TableArg _arg) = (sem_Args_TableArg (sem_FieldList _arg)) sem_Args (StringArg _arg) = (sem_Args_StringArg (sem_MToken _arg)) -- semantic domain type T_Args = (Args, T_Args_1) type T_Args_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Args = Inh_Args {config_Inh_Args :: LintSettings, funcName_Inh_Args :: String, globalDefinitions_Inh_Args :: (M.Map String [Region]), isInModule_Inh_Args :: Bool, isMeta_Inh_Args :: Bool, loopLevel_Inh_Args :: Int, mtokenPos_Inh_Args :: Region, scopeLevel_Inh_Args :: Int, scopes_Inh_Args :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Args :: DeterminedVariableStyle} data Syn_Args = Syn_Args {copy_Syn_Args :: Args, globalDefinitions_Syn_Args :: (M.Map String [Region]), identifier_Syn_Args :: String, isInModule_Syn_Args :: Bool, mtokenPos_Syn_Args :: Region, scopes_Syn_Args :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Args :: DeterminedVariableStyle, warnings_Syn_Args :: ([String -> LintMessage])} wrap_Args :: T_Args -> Inh_Args -> Syn_Args wrap_Args sem (Inh_Args _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Args _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Args_ListArgs :: T_MExprList -> T_Args sem_Args_ListArgs args_ = ( case (args_) of (_argsIcopy, args_1) -> ( case ( ( ListArgs _argsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Args_ListArgs_1 :: T_Args_1 sem_Args_ListArgs_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _argsOscopes -> ( case ( ( _lhsIisMeta ) ) of _argsOisMeta -> ( case ( ( _lhsIisInModule ) ) of _argsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _argsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _argsOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _argsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _argsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _argsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _argsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _argsOfuncName -> ( case ( ( True ) ) of _argsOtopLevel -> ( case ( ( True ) ) of _argsOinParentheses -> ( case (args_1 _argsOconfig _argsOfuncName _argsOglobalDefinitions _argsOinParentheses _argsOisInModule _argsOisMeta _argsOloopLevel _argsOmtokenPos _argsOscopeLevel _argsOscopes _argsOtopLevel _argsOvariableStyle) of (_argsIglobalDefinitions, _argsIidentifier, _argsIisInModule, _argsImtokenPos, _argsIscopes, _argsIvariableStyle, _argsIwarnings) -> ( case ( ( _argsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _argsIidentifier ) ) of _lhsOidentifier -> ( case ( ( _argsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _argsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _argsIscopes ) ) of _lhsOscopes -> ( case ( ( _argsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _argsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Args_ListArgs_1 ) ) of (sem_Args_1) -> (_lhsOcopy, sem_Args_1) ) ) ) ) sem_Args_TableArg :: T_FieldList -> T_Args sem_Args_TableArg arg_ = ( case (arg_) of (_argIcopy, arg_1) -> ( case ( ( TableArg _argIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Args_TableArg_1 :: T_Args_1 sem_Args_TableArg_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _argOscopes -> ( case ( ( _lhsIisMeta ) ) of _argOisMeta -> ( case ( ( _lhsIisInModule ) ) of _argOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _argOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _argOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _argOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _argOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _argOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _argOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _argOfuncName -> ( case ( ( S.empty ) ) of _argOfieldNames -> ( case (arg_1 _argOconfig _argOfieldNames _argOfuncName _argOglobalDefinitions _argOisInModule _argOisMeta _argOloopLevel _argOmtokenPos _argOscopeLevel _argOscopes _argOvariableStyle) of (_argIfieldNames, _argIglobalDefinitions, _argIidentifier, _argIisInModule, _argImtokenPos, _argIscopes, _argIvariableStyle, _argIwarnings) -> ( case ( ( _argIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _argIidentifier ) ) of _lhsOidentifier -> ( case ( ( _argIisInModule ) ) of _lhsOisInModule -> ( case ( ( _argImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _argIscopes ) ) of _lhsOscopes -> ( case ( ( _argIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _argIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Args_TableArg_1 ) ) of (sem_Args_1) -> (_lhsOcopy, sem_Args_1) ) ) ) ) sem_Args_StringArg :: T_MToken -> T_Args sem_Args_StringArg arg_ = ( case (arg_) of (_argIcopy, _argImtok, _argImtokenPos, arg_1) -> ( case ( ( StringArg _argIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Args_StringArg_1 :: T_Args_1 sem_Args_StringArg_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _argOglobalDefinitions -> ( case ( ( _lhsIscopes ) ) of _argOscopes -> ( case ( ( _lhsImtokenPos ) ) of _argOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _argOisMeta -> ( case ( ( _lhsIisInModule ) ) of _argOisInModule -> ( case ( ( _lhsIfuncName ) ) of _argOfuncName -> ( case ( ( _lhsIconfig ) ) of _argOconfig -> ( case (arg_1 _argOconfig _argOfuncName _argOglobalDefinitions _argOisInModule _argOisMeta _argOmtokenPos _argOscopes) of (_argIglobalDefinitions, _argIidentifier, _argIisInModule, _argIscopes, _argIwarnings) -> ( case ( ( _argIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _argIidentifier ) ) of _lhsOidentifier -> ( case ( ( _argIisInModule ) ) of _lhsOisInModule -> ( case ( ( _argImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _argIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _argIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Args_StringArg_1 ) ) of (sem_Args_1) -> (_lhsOcopy, sem_Args_1) ) ) ) ) -- BinOp ------------------------------------------------------- -- cata sem_BinOp :: BinOp -> T_BinOp sem_BinOp (AOr) = (sem_BinOp_AOr) sem_BinOp (AAnd) = (sem_BinOp_AAnd) sem_BinOp (ALT) = (sem_BinOp_ALT) sem_BinOp (AGT) = (sem_BinOp_AGT) sem_BinOp (ALEQ) = (sem_BinOp_ALEQ) sem_BinOp (AGEQ) = (sem_BinOp_AGEQ) sem_BinOp (ANEq) = (sem_BinOp_ANEq) sem_BinOp (AEq) = (sem_BinOp_AEq) sem_BinOp (AConcatenate) = (sem_BinOp_AConcatenate) sem_BinOp (APlus) = (sem_BinOp_APlus) sem_BinOp (BinMinus) = (sem_BinOp_BinMinus) sem_BinOp (AMultiply) = (sem_BinOp_AMultiply) sem_BinOp (ADivide) = (sem_BinOp_ADivide) sem_BinOp (AModulus) = (sem_BinOp_AModulus) sem_BinOp (APower) = (sem_BinOp_APower) -- semantic domain type T_BinOp = (BinOp, T_BinOp_1) type T_BinOp_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_BinOp = Inh_BinOp {config_Inh_BinOp :: LintSettings, funcName_Inh_BinOp :: String, globalDefinitions_Inh_BinOp :: (M.Map String [Region]), isInModule_Inh_BinOp :: Bool, isMeta_Inh_BinOp :: Bool, loopLevel_Inh_BinOp :: Int, mtokenPos_Inh_BinOp :: Region, scopeLevel_Inh_BinOp :: Int, scopes_Inh_BinOp :: ([M.Map String (Bool, Region)]), variableStyle_Inh_BinOp :: DeterminedVariableStyle} data Syn_BinOp = Syn_BinOp {copy_Syn_BinOp :: BinOp, globalDefinitions_Syn_BinOp :: (M.Map String [Region]), identifier_Syn_BinOp :: String, isInModule_Syn_BinOp :: Bool, mtokenPos_Syn_BinOp :: Region, scopes_Syn_BinOp :: ([M.Map String (Bool, Region)]), variableStyle_Syn_BinOp :: DeterminedVariableStyle, warnings_Syn_BinOp :: ([String -> LintMessage])} wrap_BinOp :: T_BinOp -> Inh_BinOp -> Syn_BinOp wrap_BinOp sem (Inh_BinOp _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_BinOp _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_BinOp_AOr :: T_BinOp sem_BinOp_AOr = ( case ( ( AOr ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AOr_1 :: T_BinOp_1 sem_BinOp_AOr_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AOr_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AAnd :: T_BinOp sem_BinOp_AAnd = ( case ( ( AAnd ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AAnd_1 :: T_BinOp_1 sem_BinOp_AAnd_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AAnd_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_ALT :: T_BinOp sem_BinOp_ALT = ( case ( ( ALT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_ALT_1 :: T_BinOp_1 sem_BinOp_ALT_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_ALT_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AGT :: T_BinOp sem_BinOp_AGT = ( case ( ( AGT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AGT_1 :: T_BinOp_1 sem_BinOp_AGT_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AGT_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_ALEQ :: T_BinOp sem_BinOp_ALEQ = ( case ( ( ALEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_ALEQ_1 :: T_BinOp_1 sem_BinOp_ALEQ_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_ALEQ_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AGEQ :: T_BinOp sem_BinOp_AGEQ = ( case ( ( AGEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AGEQ_1 :: T_BinOp_1 sem_BinOp_AGEQ_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AGEQ_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_ANEq :: T_BinOp sem_BinOp_ANEq = ( case ( ( ANEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_ANEq_1 :: T_BinOp_1 sem_BinOp_ANEq_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_ANEq_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AEq :: T_BinOp sem_BinOp_AEq = ( case ( ( AEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AEq_1 :: T_BinOp_1 sem_BinOp_AEq_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AEq_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AConcatenate :: T_BinOp sem_BinOp_AConcatenate = ( case ( ( AConcatenate ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AConcatenate_1 :: T_BinOp_1 sem_BinOp_AConcatenate_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AConcatenate_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_APlus :: T_BinOp sem_BinOp_APlus = ( case ( ( APlus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_APlus_1 :: T_BinOp_1 sem_BinOp_APlus_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_APlus_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_BinMinus :: T_BinOp sem_BinOp_BinMinus = ( case ( ( BinMinus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_BinMinus_1 :: T_BinOp_1 sem_BinOp_BinMinus_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_BinMinus_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AMultiply :: T_BinOp sem_BinOp_AMultiply = ( case ( ( AMultiply ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AMultiply_1 :: T_BinOp_1 sem_BinOp_AMultiply_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AMultiply_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_ADivide :: T_BinOp sem_BinOp_ADivide = ( case ( ( ADivide ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_ADivide_1 :: T_BinOp_1 sem_BinOp_ADivide_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_ADivide_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_AModulus :: T_BinOp sem_BinOp_AModulus = ( case ( ( AModulus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_AModulus_1 :: T_BinOp_1 sem_BinOp_AModulus_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_AModulus_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) sem_BinOp_APower :: T_BinOp sem_BinOp_APower = ( case ( ( APower ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_BinOp_APower_1 :: T_BinOp_1 sem_BinOp_APower_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_BinOp_APower_1 ) ) of (sem_BinOp_1) -> (_lhsOcopy, sem_BinOp_1) ) ) ) -- Block ------------------------------------------------------- -- cata sem_Block :: Block -> T_Block sem_Block (Block _stats _ret) = (sem_Block_Block (sem_MStatList _stats) (sem_AReturn _ret)) -- semantic domain type T_Block = (Block, T_Block_1) type T_Block_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), Int, DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Block = Inh_Block {config_Inh_Block :: LintSettings, funcName_Inh_Block :: String, globalDefinitions_Inh_Block :: (M.Map String [Region]), isInModule_Inh_Block :: Bool, isMeta_Inh_Block :: Bool, isRepeat_Inh_Block :: Bool, loopLevel_Inh_Block :: Int, mtokenPos_Inh_Block :: Region, scopeLevel_Inh_Block :: Int, scopes_Inh_Block :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Block :: DeterminedVariableStyle} data Syn_Block = Syn_Block {copy_Syn_Block :: Block, globalDefinitions_Syn_Block :: (M.Map String [Region]), identifier_Syn_Block :: String, isIfStatement_Syn_Block :: Bool, isInModule_Syn_Block :: Bool, mtokenPos_Syn_Block :: Region, scopes_Syn_Block :: ([M.Map String (Bool, Region)]), statementCount_Syn_Block :: Int, variableStyle_Syn_Block :: DeterminedVariableStyle, warnings_Syn_Block :: ([String -> LintMessage])} wrap_Block :: T_Block -> Inh_Block -> Syn_Block wrap_Block sem (Inh_Block _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisRepeat _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisRepeat _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Block _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisIfStatement _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOstatementCount _lhsOvariableStyle _lhsOwarnings) ) sem_Block_Block :: T_MStatList -> T_AReturn -> T_Block sem_Block_Block stats_ ret_ = ( case (ret_) of (_retIcopy, ret_1) -> ( case (stats_) of (_statsIcopy, stats_1) -> ( case ( ( Block _statsIcopy _retIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Block_Block_1 :: T_Block_1 sem_Block_Block_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisRepeat _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _statsOscopes -> ( case ( ( _lhsIisMeta ) ) of _statsOisMeta -> ( case ( ( _lhsIconfig ) ) of _statsOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _statsOvariableStyle -> ( case ( ( _lhsImtokenPos ) ) of _statsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _statsOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _statsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _statsOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _statsOfuncName -> ( case ( ( _lhsIscopeLevel + 1 ) ) of _statsOscopeLevel -> ( case (stats_1 _statsOconfig _statsOfuncName _statsOglobalDefinitions _statsOisInModule _statsOisMeta _statsOloopLevel _statsOmtokenPos _statsOscopeLevel _statsOscopes _statsOvariableStyle) of (_statsIglobalDefinitions, _statsIidentifier, _statsIisIfStatement, _statsIisInModule, _statsImtokenPos, _statsIscopes, _statsIstatementCount, _statsIvariableStyle, _statsIwarnings) -> ( case ( ( _statsIscopes ) ) of _retOscopes -> ( case ( ( _lhsIisMeta ) ) of _retOisMeta -> ( case ( ( _statsIisInModule ) ) of _retOisInModule -> ( case ( ( _statsIglobalDefinitions ) ) of _retOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _retOconfig -> ( case ( ( _statsIvariableStyle ) ) of _retOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _retOscopeLevel -> ( case ( ( _statsImtokenPos ) ) of _retOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _retOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _retOfuncName -> ( case (ret_1 _retOconfig _retOfuncName _retOglobalDefinitions _retOisInModule _retOisMeta _retOloopLevel _retOmtokenPos _retOscopeLevel _retOscopes _retOvariableStyle) of (_retIglobalDefinitions, _retIidentifier, _retIisInModule, _retImtokenPos, _retIscopes, _retIstatementCount, _retIvariableStyle, _retIwarnings) -> ( case ( ( _retIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _statsIidentifier _retIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _statsIisIfStatement ) ) of _lhsOisIfStatement -> ( case ( ( _retIisInModule ) ) of _lhsOisInModule -> ( case ( ( _retImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( if _lhsIisRepeat then _retIscopes else tail _retIscopes ) ) of _lhsOscopes -> ( case ( ( _statsIstatementCount + _retIstatementCount ) ) of _lhsOstatementCount -> ( case ( ( _retIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _statsIwarnings ++ _retIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( M.filterWithKey (\k (b, _) -> not (null k) && head k /= '_' && not b) (head _retIscopes) ) ) of _deadVars -> ( case ( ( lint_maxScopeDepth _lhsIconfig ) ) of _maxScopeDepth -> ( case ( ( if _maxScopeDepth == 0 || _lhsIscopeLevel /= _maxScopeDepth then id else (:) $ warn _statsImtokenPos ScopePyramids ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_unusedVars _lhsIconfig) || _lhsIisRepeat then id else (++) $ M.foldrWithKey (\k (_, pos) ls -> warn pos (UnusedVariable k) : ls) [] _deadVars ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Block_Block_1 ) ) of (sem_Block_1) -> (_lhsOcopy, sem_Block_1) ) ) ) ) ) -- Declaration ------------------------------------------------- -- cata sem_Declaration :: Declaration -> T_Declaration sem_Declaration (x1, x2) = (sem_Declaration_Tuple (sem_PrefixExp x1) (sem_MaybeMExpr x2)) -- semantic domain type T_Declaration = (Declaration, T_Declaration_1) type T_Declaration_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Declaration = Inh_Declaration {config_Inh_Declaration :: LintSettings, funcName_Inh_Declaration :: String, globalDefinitions_Inh_Declaration :: (M.Map String [Region]), isInModule_Inh_Declaration :: Bool, isMeta_Inh_Declaration :: Bool, localDefinition_Inh_Declaration :: Bool, loopLevel_Inh_Declaration :: Int, mtokenPos_Inh_Declaration :: Region, scopeLevel_Inh_Declaration :: Int, scopes_Inh_Declaration :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Declaration :: DeterminedVariableStyle} data Syn_Declaration = Syn_Declaration {copy_Syn_Declaration :: Declaration, globalDefinitions_Syn_Declaration :: (M.Map String [Region]), identifier_Syn_Declaration :: String, isInModule_Syn_Declaration :: Bool, mtokenPos_Syn_Declaration :: Region, scopes_Syn_Declaration :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Declaration :: DeterminedVariableStyle, warnings_Syn_Declaration :: ([String -> LintMessage])} wrap_Declaration :: T_Declaration -> Inh_Declaration -> Syn_Declaration wrap_Declaration sem (Inh_Declaration _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Declaration _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Declaration_Tuple :: T_PrefixExp -> T_MaybeMExpr -> T_Declaration sem_Declaration_Tuple x1_ x2_ = ( case (x2_) of (_x2Icopy, x2_1) -> ( case (x1_) of (_x1Icopy, _x1IhasSuffixes, _x1ImtokenPos, _x1IvarName, x1_1) -> ( case ( ( (_x1Icopy, _x2Icopy) ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Declaration_Tuple_1 :: T_Declaration_1 sem_Declaration_Tuple_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _x1OisMeta -> ( case ( ( _lhsIconfig ) ) of _x1Oconfig -> ( case ( ( tokenLabel . fromMaybe (error "fromMaybe sem Declaration loc.var") $ _x1IvarName ) ) of _var -> ( case ( ( if _lhsIlocalDefinition then M.insert _var (False, _x1ImtokenPos) (head _lhsIscopes) : tail _lhsIscopes else if isJust _x1IvarName then registerVariable _lhsIscopes _x1ImtokenPos _var _x1IhasSuffixes else _lhsIscopes ) ) of _x1Oscopes -> ( case ( ( Nothing ) ) of _x1OvarBeingDefined -> ( case ( ( False ) ) of _x1OregisterVarUse -> ( case ( ( _lhsIvariableStyle ) ) of _x1OvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _x1OscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _x1OmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _x1OloopLevel -> ( case ( ( _lhsIisInModule ) ) of _x1OisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _x1OglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _x1OfuncName -> ( case ( ( False ) ) of _x1OtopLevel -> ( case ( ( False ) ) of _x1OinParentheses -> ( case ( ( False ) ) of _x1OisNegation -> ( case (x1_1 _x1Oconfig _x1OfuncName _x1OglobalDefinitions _x1OinParentheses _x1OisInModule _x1OisMeta _x1OisNegation _x1OloopLevel _x1OmtokenPos _x1OregisterVarUse _x1OscopeLevel _x1Oscopes _x1OtopLevel _x1OvarBeingDefined _x1OvariableStyle) of (_x1IglobalDefinitions, _x1Iidentifier, _x1IisInModule, _x1IisSimpleExpression, _x1IisSingleVar, _x1Iscopes, _x1IvariableStyle, _x1Iwarnings) -> ( case ( ( _x1Iscopes ) ) of _x2Oscopes -> ( case ( ( _lhsIisMeta ) ) of _x2OisMeta -> ( case ( ( _x1IisInModule ) ) of _x2OisInModule -> ( case ( ( _x1IglobalDefinitions ) ) of _x2OglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _x2Oconfig -> ( case ( ( if _x1IhasSuffixes || not _lhsIlocalDefinition then Nothing else _x1IvarName ) ) of _x2OvarBeingDefined -> ( case ( ( _x1IvariableStyle ) ) of _x2OvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _x2OscopeLevel -> ( case ( ( _x1ImtokenPos ) ) of _x2OmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _x2OloopLevel -> ( case ( ( _lhsIfuncName ) ) of _x2OfuncName -> ( case ( ( False ) ) of _x2OisNegation -> ( case (x2_1 _x2Oconfig _x2OfuncName _x2OglobalDefinitions _x2OisInModule _x2OisMeta _x2OisNegation _x2OloopLevel _x2OmtokenPos _x2OscopeLevel _x2Oscopes _x2OvarBeingDefined _x2OvariableStyle) of (_x2IglobalDefinitions, _x2Iidentifier, _x2IisInModule, _x2IisSingleVar, _x2ImtokenPos, _x2Iscopes, _x2IvariableStyle, _x2Iwarnings) -> ( case ( ( _x2IglobalDefinitions ) ) of _globalDefinitions_augmented_syn -> ( case ( ( if _lhsIisInModule || _lhsIlocalDefinition || isVariableLocal _lhsIscopes _var || _x1IhasSuffixes then id else M.insertWith (++) _var [_x1ImtokenPos] ) ) of _globalDefinitions_augmented_f1 -> ( case ( ( foldr ($) _globalDefinitions_augmented_syn [_globalDefinitions_augmented_f1] ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _x1Iidentifier _x2Iidentifier) ) ) of _lhsOidentifier -> ( case ( ( _x2IisInModule ) ) of _lhsOisInModule -> ( case ( ( _x1ImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _x2Iscopes ) ) of _lhsOscopes -> ( case ( ( determineVariableStyle _var ) ) of _varStyle -> ( case ( ( if _lhsIlocalDefinition then combineDeterminedVarStyle _lhsIvariableStyle _varStyle else _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _x1Iwarnings ++ _x2Iwarnings ) ) of _warnings_augmented_syn -> ( case ( ( do var <- _x1IvarName if (Just var /= _x2IisSingleVar) then checkShadows _lhsIscopes var else Nothing ) ) of _shadowWarning -> ( case ( ( if not (lint_shadowing _lhsIconfig) || not _lhsIlocalDefinition || isNothing _shadowWarning then id else (:) . fromMaybe (error "fromMaybe sem Declaration +warnings") $ _shadowWarning ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_inconsistentVariableStyle _lhsIconfig) || not _lhsIlocalDefinition || not (variableStyleInconsistent _lhsIvariableStyle _varStyle) then id else (:) $ warn _x1ImtokenPos InconsistentVariableNaming ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Declaration_Tuple_1 ) ) of (sem_Declaration_1) -> (_lhsOcopy, sem_Declaration_1) ) ) ) ) ) -- Else -------------------------------------------------------- -- cata sem_Else :: Else -> T_Else sem_Else (Prelude.Just x) = (sem_Else_Just (sem_MElse x)) sem_Else Prelude.Nothing = sem_Else_Nothing -- semantic domain type T_Else = (Else, T_Else_1) type T_Else_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> (Bool, (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Else = Inh_Else {config_Inh_Else :: LintSettings, funcName_Inh_Else :: String, globalDefinitions_Inh_Else :: (M.Map String [Region]), isInModule_Inh_Else :: Bool, isMeta_Inh_Else :: Bool, loopLevel_Inh_Else :: Int, mtokenPos_Inh_Else :: Region, scopeLevel_Inh_Else :: Int, scopes_Inh_Else :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Else :: DeterminedVariableStyle} data Syn_Else = Syn_Else {copy_Syn_Else :: Else, elseExists_Syn_Else :: Bool, globalDefinitions_Syn_Else :: (M.Map String [Region]), identifier_Syn_Else :: String, isInModule_Syn_Else :: Bool, mtokenPos_Syn_Else :: Region, scopes_Syn_Else :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Else :: DeterminedVariableStyle, warnings_Syn_Else :: ([String -> LintMessage])} wrap_Else :: T_Else -> Inh_Else -> Syn_Else wrap_Else sem (Inh_Else _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Else _lhsOcopy _lhsOelseExists _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Else_Just :: T_MElse -> T_Else sem_Else_Just just_ = ( case (just_) of (_justIcopy, just_1) -> ( case ( ( Just _justIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Else_Just_1 :: T_Else_1 sem_Else_Just_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( True ) ) of _lhsOelseExists -> ( case ( ( _lhsIisMeta ) ) of _justOisMeta -> ( case ( ( _lhsIisInModule ) ) of _justOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _justOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _justOconfig -> ( case ( ( M.empty : _lhsIscopes ) ) of _justOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _justOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _justOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _justOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _justOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _justOfuncName -> ( case (just_1 _justOconfig _justOfuncName _justOglobalDefinitions _justOisInModule _justOisMeta _justOloopLevel _justOmtokenPos _justOscopeLevel _justOscopes _justOvariableStyle) of (_justIelseExists, _justIglobalDefinitions, _justIidentifier, _justIisInModule, _justImtokenPos, _justIscopes, _justIstatementCount, _justIvariableStyle, _justIwarnings) -> ( case ( ( _justIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _justIidentifier ) ) of _lhsOidentifier -> ( case ( ( _justIisInModule ) ) of _lhsOisInModule -> ( case ( ( _justImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _justIscopes ) ) of _lhsOscopes -> ( case ( ( _justIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _justIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( Region (rgStart _justImtokenPos) (customAdvanceToken (rgStart _justImtokenPos) T.Else) ) ) of _keywordPos -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _justIstatementCount > 0 then id else (:) $ warn _keywordPos EmptyElse ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Else_Just_1 ) ) of (sem_Else_1) -> (_lhsOcopy, sem_Else_1) ) ) ) ) sem_Else_Nothing :: T_Else sem_Else_Nothing = ( case ( ( Nothing ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Else_Nothing_1 :: T_Else_1 sem_Else_Nothing_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( False ) ) of _lhsOelseExists -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_Else_Nothing_1 ) ) of (sem_Else_1) -> (_lhsOcopy, sem_Else_1) ) ) ) -- ElseIf ------------------------------------------------------ -- cata sem_ElseIf :: ElseIf -> T_ElseIf sem_ElseIf (x1, x2) = (sem_ElseIf_Tuple (sem_MExpr x1) (sem_Block x2)) -- semantic domain type T_ElseIf = (ElseIf, T_ElseIf_1) type T_ElseIf_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_ElseIf = Inh_ElseIf {config_Inh_ElseIf :: LintSettings, funcName_Inh_ElseIf :: String, globalDefinitions_Inh_ElseIf :: (M.Map String [Region]), isInModule_Inh_ElseIf :: Bool, isMeta_Inh_ElseIf :: Bool, loopLevel_Inh_ElseIf :: Int, mtokenPos_Inh_ElseIf :: Region, scopeLevel_Inh_ElseIf :: Int, scopes_Inh_ElseIf :: ([M.Map String (Bool, Region)]), variableStyle_Inh_ElseIf :: DeterminedVariableStyle} data Syn_ElseIf = Syn_ElseIf {copy_Syn_ElseIf :: ElseIf, globalDefinitions_Syn_ElseIf :: (M.Map String [Region]), identifier_Syn_ElseIf :: String, isInModule_Syn_ElseIf :: Bool, mtokenPos_Syn_ElseIf :: Region, scopes_Syn_ElseIf :: ([M.Map String (Bool, Region)]), variableStyle_Syn_ElseIf :: DeterminedVariableStyle, warnings_Syn_ElseIf :: ([String -> LintMessage])} wrap_ElseIf :: T_ElseIf -> Inh_ElseIf -> Syn_ElseIf wrap_ElseIf sem (Inh_ElseIf _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_ElseIf _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_ElseIf_Tuple :: T_MExpr -> T_Block -> T_ElseIf sem_ElseIf_Tuple x1_ x2_ = ( case (x2_) of (_x2Icopy, x2_1) -> ( case (x1_) of (_x1Icopy, _x1ImtokenPos, x1_1) -> ( case ( ( (_x1Icopy, _x2Icopy) ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_ElseIf_Tuple_1 :: T_ElseIf_1 sem_ElseIf_Tuple_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _x2OisMeta -> ( case ( ( _lhsIisInModule ) ) of _x1OisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _x1OvariableStyle -> ( case ( ( _lhsIscopes ) ) of _x1Oscopes -> ( case ( ( _lhsIscopeLevel ) ) of _x1OscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _x1OmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _x1OloopLevel -> ( case ( ( _lhsIisMeta ) ) of _x1OisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _x1OglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _x1OfuncName -> ( case ( ( _lhsIconfig ) ) of _x1Oconfig -> ( case ( ( Nothing ) ) of _x1OvarBeingDefined -> ( case ( ( True ) ) of _x1OtopLevel -> ( case ( ( False ) ) of _x1OinParentheses -> ( case ( ( False ) ) of _x1OisNegation -> ( case (x1_1 _x1Oconfig _x1OfuncName _x1OglobalDefinitions _x1OinParentheses _x1OisInModule _x1OisMeta _x1OisNegation _x1OloopLevel _x1OmtokenPos _x1OscopeLevel _x1Oscopes _x1OtopLevel _x1OvarBeingDefined _x1OvariableStyle) of (_x1IglobalDefinitions, _x1Iidentifier, _x1IisInModule, _x1IisSimpleExpression, _x1IisSingleVar, _x1Iscopes, _x1IvariableStyle, _x1Iwarnings) -> ( case ( ( _x1IisInModule ) ) of _x2OisInModule -> ( case ( ( _x1IglobalDefinitions ) ) of _x2OglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _x2Oconfig -> ( case ( ( M.empty : _x1Iscopes ) ) of _x2Oscopes -> ( case ( ( _x1IvariableStyle ) ) of _x2OvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _x2OscopeLevel -> ( case ( ( _x1ImtokenPos ) ) of _x2OmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _x2OloopLevel -> ( case ( ( _lhsIfuncName ) ) of _x2OfuncName -> ( case ( ( False ) ) of _x2OisRepeat -> ( case (x2_1 _x2Oconfig _x2OfuncName _x2OglobalDefinitions _x2OisInModule _x2OisMeta _x2OisRepeat _x2OloopLevel _x2OmtokenPos _x2OscopeLevel _x2Oscopes _x2OvariableStyle) of (_x2IglobalDefinitions, _x2Iidentifier, _x2IisIfStatement, _x2IisInModule, _x2ImtokenPos, _x2Iscopes, _x2IstatementCount, _x2IvariableStyle, _x2Iwarnings) -> ( case ( ( _x2IglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _x1Iidentifier _x2Iidentifier) ) ) of _lhsOidentifier -> ( case ( ( _x2IisInModule ) ) of _lhsOisInModule -> ( case ( ( _x2ImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _x2Iscopes ) ) of _lhsOscopes -> ( case ( ( _x2IvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _x1Iwarnings ++ _x2Iwarnings ) ) of _warnings_augmented_syn -> ( case ( ( Region (rgStart _lhsImtokenPos) (customAdvanceToken (rgStart _lhsImtokenPos) T.Elseif) ) ) of _keywordPos -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _x2IstatementCount > 0 then id else (:) $ warn _keywordPos EmptyElseIf ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_ElseIf_Tuple_1 ) ) of (sem_ElseIf_1) -> (_lhsOcopy, sem_ElseIf_1) ) ) ) ) ) -- ElseIfList -------------------------------------------------- -- cata sem_ElseIfList :: ElseIfList -> T_ElseIfList sem_ElseIfList list = (Prelude.foldr sem_ElseIfList_Cons sem_ElseIfList_Nil (Prelude.map sem_MElseIf list)) -- semantic domain type T_ElseIfList = (ElseIfList, T_ElseIfList_1) type T_ElseIfList_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> (Bool, (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_ElseIfList = Inh_ElseIfList {config_Inh_ElseIfList :: LintSettings, funcName_Inh_ElseIfList :: String, globalDefinitions_Inh_ElseIfList :: (M.Map String [Region]), isInModule_Inh_ElseIfList :: Bool, isMeta_Inh_ElseIfList :: Bool, loopLevel_Inh_ElseIfList :: Int, mtokenPos_Inh_ElseIfList :: Region, scopeLevel_Inh_ElseIfList :: Int, scopes_Inh_ElseIfList :: ([M.Map String (Bool, Region)]), variableStyle_Inh_ElseIfList :: DeterminedVariableStyle} data Syn_ElseIfList = Syn_ElseIfList {copy_Syn_ElseIfList :: ElseIfList, elseExists_Syn_ElseIfList :: Bool, globalDefinitions_Syn_ElseIfList :: (M.Map String [Region]), identifier_Syn_ElseIfList :: String, isInModule_Syn_ElseIfList :: Bool, mtokenPos_Syn_ElseIfList :: Region, scopes_Syn_ElseIfList :: ([M.Map String (Bool, Region)]), variableStyle_Syn_ElseIfList :: DeterminedVariableStyle, warnings_Syn_ElseIfList :: ([String -> LintMessage])} wrap_ElseIfList :: T_ElseIfList -> Inh_ElseIfList -> Syn_ElseIfList wrap_ElseIfList sem (Inh_ElseIfList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_ElseIfList _lhsOcopy _lhsOelseExists _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_ElseIfList_Cons :: T_MElseIf -> T_ElseIfList -> T_ElseIfList sem_ElseIfList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_ElseIfList_Cons_1 :: T_ElseIfList_1 sem_ElseIfList_Cons_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( True ) ) of _lhsOelseExists -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOvariableStyle) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdImtokenPos, _hdIscopes, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case (tl_1 _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOvariableStyle) of (_tlIelseExists, _tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _tlImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_ElseIfList_Cons_1 ) ) of (sem_ElseIfList_1) -> (_lhsOcopy, sem_ElseIfList_1) ) ) ) ) ) sem_ElseIfList_Nil :: T_ElseIfList sem_ElseIfList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_ElseIfList_Nil_1 :: T_ElseIfList_1 sem_ElseIfList_Nil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( False ) ) of _lhsOelseExists -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_ElseIfList_Nil_1 ) ) of (sem_ElseIfList_1) -> (_lhsOcopy, sem_ElseIfList_1) ) ) ) -- Expr -------------------------------------------------------- -- cata sem_Expr :: Expr -> T_Expr sem_Expr (ANil) = (sem_Expr_ANil) sem_Expr (AFalse) = (sem_Expr_AFalse) sem_Expr (ATrue) = (sem_Expr_ATrue) sem_Expr (ANumber _num) = (sem_Expr_ANumber _num) sem_Expr (AString _str) = (sem_Expr_AString (sem_MToken _str)) sem_Expr (AVarArg) = (sem_Expr_AVarArg) sem_Expr (AnonymousFunc _pars _body) = (sem_Expr_AnonymousFunc _pars (sem_Block _body)) sem_Expr (APrefixExpr _pexpr) = (sem_Expr_APrefixExpr (sem_PrefixExp _pexpr)) sem_Expr (ATableConstructor _fields) = (sem_Expr_ATableConstructor (sem_FieldList _fields)) sem_Expr (BinOpExpr _op _left _right) = (sem_Expr_BinOpExpr (sem_BinOp _op) (sem_MExpr _left) (sem_MExpr _right)) sem_Expr (UnOpExpr _op _right) = (sem_Expr_UnOpExpr (sem_UnOp _op) (sem_MExpr _right)) -- semantic domain type T_Expr = (Expr, T_Expr_1) type T_Expr_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> Bool -> (Maybe MToken) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, (Maybe MToken), Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Expr = Inh_Expr {config_Inh_Expr :: LintSettings, funcName_Inh_Expr :: String, globalDefinitions_Inh_Expr :: (M.Map String [Region]), inParentheses_Inh_Expr :: Bool, isInModule_Inh_Expr :: Bool, isMeta_Inh_Expr :: Bool, isNegation_Inh_Expr :: Bool, loopLevel_Inh_Expr :: Int, mtokenPos_Inh_Expr :: Region, scopeLevel_Inh_Expr :: Int, scopes_Inh_Expr :: ([M.Map String (Bool, Region)]), topLevel_Inh_Expr :: Bool, varBeingDefined_Inh_Expr :: (Maybe MToken), variableStyle_Inh_Expr :: DeterminedVariableStyle} data Syn_Expr = Syn_Expr {copy_Syn_Expr :: Expr, globalDefinitions_Syn_Expr :: (M.Map String [Region]), identifier_Syn_Expr :: String, isInModule_Syn_Expr :: Bool, isSimpleExpression_Syn_Expr :: Bool, isSingleVar_Syn_Expr :: (Maybe MToken), mtokenPos_Syn_Expr :: Region, scopes_Syn_Expr :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Expr :: DeterminedVariableStyle, warnings_Syn_Expr :: ([String -> LintMessage])} wrap_Expr :: T_Expr -> Inh_Expr -> Syn_Expr wrap_Expr sem (Inh_Expr _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle in (Syn_Expr _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisSimpleExpression _lhsOisSingleVar _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Expr_ANil :: T_Expr sem_Expr_ANil = ( case ( ( ANil ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_ANil_1 :: T_Expr_1 sem_Expr_ANil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_Expr_ANil_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) sem_Expr_AFalse :: T_Expr sem_Expr_AFalse = ( case ( ( AFalse ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_AFalse_1 :: T_Expr_1 sem_Expr_AFalse_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_Expr_AFalse_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) sem_Expr_ATrue :: T_Expr sem_Expr_ATrue = ( case ( ( ATrue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_ATrue_1 :: T_Expr_1 sem_Expr_ATrue_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_Expr_ATrue_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) sem_Expr_ANumber :: String -> T_Expr sem_Expr_ANumber num_ = ( case ( ( ANumber num_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_ANumber_1 :: T_Expr_1 sem_Expr_ANumber_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_Expr_ANumber_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) sem_Expr_AString :: T_MToken -> T_Expr sem_Expr_AString str_ = ( case (str_) of (_strIcopy, _strImtok, _strImtokenPos, str_1) -> ( case ( ( AString _strIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_AString_1 :: T_Expr_1 sem_Expr_AString_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _strOglobalDefinitions -> ( case ( ( _lhsIscopes ) ) of _strOscopes -> ( case ( ( _lhsImtokenPos ) ) of _strOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _strOisMeta -> ( case ( ( _lhsIisInModule ) ) of _strOisInModule -> ( case ( ( _lhsIfuncName ) ) of _strOfuncName -> ( case ( ( _lhsIconfig ) ) of _strOconfig -> ( case (str_1 _strOconfig _strOfuncName _strOglobalDefinitions _strOisInModule _strOisMeta _strOmtokenPos _strOscopes) of (_strIglobalDefinitions, _strIidentifier, _strIisInModule, _strIscopes, _strIwarnings) -> ( case ( ( _strIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _strIidentifier ) ) of _lhsOidentifier -> ( case ( ( _strIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _strImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _strIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _strIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_AString_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) sem_Expr_AVarArg :: T_Expr sem_Expr_AVarArg = ( case ( ( AVarArg ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_AVarArg_1 :: T_Expr_1 sem_Expr_AVarArg_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_Expr_AVarArg_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) sem_Expr_AnonymousFunc :: ([MToken]) -> T_Block -> T_Expr sem_Expr_AnonymousFunc pars_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case ( ( AnonymousFunc pars_ _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_AnonymousFunc_1 :: T_Expr_1 sem_Expr_AnonymousFunc_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIisInModule ) ) of _bodyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( _lhsIisMeta || findSelf pars_ ) ) of _bodyOisMeta -> ( case ( ( M.fromList $ map (\mt -> (tokenLabel mt, (not . lint_unusedParameters $ _lhsIconfig, mpos mt))) pars_ ) ) of _introduces -> ( case ( ( _introduces : _lhsIscopes ) ) of _bodyOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _bodyIidentifier ) ) of _lhsOidentifier -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( filter (/= MToken emptyRg VarArg) $ pars_ ) ) of _argIdentifiers -> ( case ( ( if not (lint_shadowing _lhsIconfig) then id else (++) . catMaybes . map (checkShadows _lhsIscopes) $ _argIdentifiers ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_AnonymousFunc_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) sem_Expr_APrefixExpr :: T_PrefixExp -> T_Expr sem_Expr_APrefixExpr pexpr_ = ( case (pexpr_) of (_pexprIcopy, _pexprIhasSuffixes, _pexprImtokenPos, _pexprIvarName, pexpr_1) -> ( case ( ( APrefixExpr _pexprIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_APrefixExpr_1 :: T_Expr_1 sem_Expr_APrefixExpr_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIvarBeingDefined ) ) of _pexprOvarBeingDefined -> ( case ( ( _lhsIscopes ) ) of _pexprOscopes -> ( case ( ( _lhsIisMeta ) ) of _pexprOisMeta -> ( case ( ( _lhsIisInModule ) ) of _pexprOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _pexprOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _pexprOconfig -> ( case ( ( True ) ) of _pexprOregisterVarUse -> ( case ( ( _lhsIvariableStyle ) ) of _pexprOvariableStyle -> ( case ( ( _lhsItopLevel ) ) of _pexprOtopLevel -> ( case ( ( _lhsIscopeLevel ) ) of _pexprOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _pexprOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _pexprOloopLevel -> ( case ( ( _lhsIisNegation ) ) of _pexprOisNegation -> ( case ( ( _lhsIinParentheses ) ) of _pexprOinParentheses -> ( case ( ( _lhsIfuncName ) ) of _pexprOfuncName -> ( case (pexpr_1 _pexprOconfig _pexprOfuncName _pexprOglobalDefinitions _pexprOinParentheses _pexprOisInModule _pexprOisMeta _pexprOisNegation _pexprOloopLevel _pexprOmtokenPos _pexprOregisterVarUse _pexprOscopeLevel _pexprOscopes _pexprOtopLevel _pexprOvarBeingDefined _pexprOvariableStyle) of (_pexprIglobalDefinitions, _pexprIidentifier, _pexprIisInModule, _pexprIisSimpleExpression, _pexprIisSingleVar, _pexprIscopes, _pexprIvariableStyle, _pexprIwarnings) -> ( case ( ( _pexprIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _pexprIidentifier ) ) of _lhsOidentifier -> ( case ( ( _pexprIisInModule ) ) of _lhsOisInModule -> ( case ( ( _pexprIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( _pexprIisSingleVar ) ) of _lhsOisSingleVar -> ( case ( ( _pexprImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _pexprIscopes ) ) of _lhsOscopes -> ( case ( ( _pexprIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _pexprIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_APrefixExpr_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) sem_Expr_ATableConstructor :: T_FieldList -> T_Expr sem_Expr_ATableConstructor fields_ = ( case (fields_) of (_fieldsIcopy, fields_1) -> ( case ( ( ATableConstructor _fieldsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_ATableConstructor_1 :: T_Expr_1 sem_Expr_ATableConstructor_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _fieldsOscopes -> ( case ( ( _lhsIisMeta ) ) of _fieldsOisMeta -> ( case ( ( _lhsIisInModule ) ) of _fieldsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _fieldsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _fieldsOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _fieldsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _fieldsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _fieldsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _fieldsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _fieldsOfuncName -> ( case ( ( S.empty ) ) of _fieldsOfieldNames -> ( case (fields_1 _fieldsOconfig _fieldsOfieldNames _fieldsOfuncName _fieldsOglobalDefinitions _fieldsOisInModule _fieldsOisMeta _fieldsOloopLevel _fieldsOmtokenPos _fieldsOscopeLevel _fieldsOscopes _fieldsOvariableStyle) of (_fieldsIfieldNames, _fieldsIglobalDefinitions, _fieldsIidentifier, _fieldsIisInModule, _fieldsImtokenPos, _fieldsIscopes, _fieldsIvariableStyle, _fieldsIwarnings) -> ( case ( ( _fieldsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _fieldsIidentifier ) ) of _lhsOidentifier -> ( case ( ( _fieldsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _fieldsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _fieldsIscopes ) ) of _lhsOscopes -> ( case ( ( _fieldsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _fieldsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_ATableConstructor_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) sem_Expr_BinOpExpr :: T_BinOp -> T_MExpr -> T_MExpr -> T_Expr sem_Expr_BinOpExpr op_ left_ right_ = ( case (right_) of (_rightIcopy, _rightImtokenPos, right_1) -> ( case (left_) of (_leftIcopy, _leftImtokenPos, left_1) -> ( case (op_) of (_opIcopy, op_1) -> ( case ( ( BinOpExpr _opIcopy _leftIcopy _rightIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_BinOpExpr_1 :: T_Expr_1 sem_Expr_BinOpExpr_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _opOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _opOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _opOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _opOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _opOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _opOisMeta -> ( case ( ( _lhsIisInModule ) ) of _opOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _opOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _opOfuncName -> ( case ( ( _lhsIconfig ) ) of _opOconfig -> ( case (op_1 _opOconfig _opOfuncName _opOglobalDefinitions _opOisInModule _opOisMeta _opOloopLevel _opOmtokenPos _opOscopeLevel _opOscopes _opOvariableStyle) of (_opIglobalDefinitions, _opIidentifier, _opIisInModule, _opImtokenPos, _opIscopes, _opIvariableStyle, _opIwarnings) -> ( case ( ( _opIscopes ) ) of _leftOscopes -> ( case ( ( _lhsIisMeta ) ) of _leftOisMeta -> ( case ( ( _lhsIconfig ) ) of _leftOconfig -> ( case ( ( Nothing ) ) of _leftOvarBeingDefined -> ( case ( ( _opIvariableStyle ) ) of _leftOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _leftOscopeLevel -> ( case ( ( _opImtokenPos ) ) of _leftOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _leftOloopLevel -> ( case ( ( _opIisInModule ) ) of _leftOisInModule -> ( case ( ( _opIglobalDefinitions ) ) of _leftOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _leftOfuncName -> ( case ( ( False ) ) of _leftOtopLevel -> ( case ( ( False ) ) of _leftOinParentheses -> ( case ( ( False ) ) of _leftOisNegation -> ( case (left_1 _leftOconfig _leftOfuncName _leftOglobalDefinitions _leftOinParentheses _leftOisInModule _leftOisMeta _leftOisNegation _leftOloopLevel _leftOmtokenPos _leftOscopeLevel _leftOscopes _leftOtopLevel _leftOvarBeingDefined _leftOvariableStyle) of (_leftIglobalDefinitions, _leftIidentifier, _leftIisInModule, _leftIisSimpleExpression, _leftIisSingleVar, _leftIscopes, _leftIvariableStyle, _leftIwarnings) -> ( case ( ( _leftIscopes ) ) of _rightOscopes -> ( case ( ( _lhsIisMeta ) ) of _rightOisMeta -> ( case ( ( _leftIisInModule ) ) of _rightOisInModule -> ( case ( ( _leftIglobalDefinitions ) ) of _rightOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _rightOconfig -> ( case ( ( Nothing ) ) of _rightOvarBeingDefined -> ( case ( ( _leftIvariableStyle ) ) of _rightOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _rightOscopeLevel -> ( case ( ( _leftImtokenPos ) ) of _rightOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _rightOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _rightOfuncName -> ( case ( ( False ) ) of _rightOtopLevel -> ( case ( ( False ) ) of _rightOinParentheses -> ( case ( ( False ) ) of _rightOisNegation -> ( case (right_1 _rightOconfig _rightOfuncName _rightOglobalDefinitions _rightOinParentheses _rightOisInModule _rightOisMeta _rightOisNegation _rightOloopLevel _rightOmtokenPos _rightOscopeLevel _rightOscopes _rightOtopLevel _rightOvarBeingDefined _rightOvariableStyle) of (_rightIglobalDefinitions, _rightIidentifier, _rightIisInModule, _rightIisSimpleExpression, _rightIisSingleVar, _rightIscopes, _rightIvariableStyle, _rightIwarnings) -> ( case ( ( _rightIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _opIidentifier (const _leftIidentifier _rightIidentifier)) ) ) of _lhsOidentifier -> ( case ( ( _rightIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisSimpleExpression -> ( case ( ( (const (const Nothing) _leftIisSingleVar _rightIisSingleVar) ) ) of _lhsOisSingleVar -> ( case ( ( _rightImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _rightIscopes ) ) of _lhsOscopes -> ( case ( ( _rightIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _opIwarnings ++ _leftIwarnings ++ _rightIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( oppositeBinOp _opIcopy ) ) of _stupidNegation -> ( case ( ( if not (lint_doubleNegations _lhsIconfig) || not _lhsIisNegation || isNothing _stupidNegation then id else (:) $ warn _lhsImtokenPos $ SillyNegation $ fromMaybe (error "fromMaybe sem Expr loc.stupidNegation") _stupidNegation ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_BinOpExpr_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) ) ) sem_Expr_UnOpExpr :: T_UnOp -> T_MExpr -> T_Expr sem_Expr_UnOpExpr op_ right_ = ( case (right_) of (_rightIcopy, _rightImtokenPos, right_1) -> ( case (op_) of (_opIcopy, op_1) -> ( case ( ( UnOpExpr _opIcopy _rightIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Expr_UnOpExpr_1 :: T_Expr_1 sem_Expr_UnOpExpr_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _opOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _opOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _opOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _opOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _opOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _opOisMeta -> ( case ( ( _lhsIisInModule ) ) of _opOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _opOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _opOfuncName -> ( case ( ( _lhsIconfig ) ) of _opOconfig -> ( case (op_1 _opOconfig _opOfuncName _opOglobalDefinitions _opOisInModule _opOisMeta _opOloopLevel _opOmtokenPos _opOscopeLevel _opOscopes _opOvariableStyle) of (_opIglobalDefinitions, _opIidentifier, _opIisInModule, _opIisNegation, _opImtokenPos, _opIscopes, _opIvariableStyle, _opIwarnings) -> ( case ( ( _opIscopes ) ) of _rightOscopes -> ( case ( ( _lhsIisMeta ) ) of _rightOisMeta -> ( case ( ( _opIisInModule ) ) of _rightOisInModule -> ( case ( ( _opIglobalDefinitions ) ) of _rightOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _rightOconfig -> ( case ( ( Nothing ) ) of _rightOvarBeingDefined -> ( case ( ( _opIvariableStyle ) ) of _rightOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _rightOscopeLevel -> ( case ( ( _opImtokenPos ) ) of _rightOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _rightOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _rightOfuncName -> ( case ( ( False ) ) of _rightOtopLevel -> ( case ( ( False ) ) of _rightOinParentheses -> ( case ( ( _opIisNegation ) ) of _rightOisNegation -> ( case (right_1 _rightOconfig _rightOfuncName _rightOglobalDefinitions _rightOinParentheses _rightOisInModule _rightOisMeta _rightOisNegation _rightOloopLevel _rightOmtokenPos _rightOscopeLevel _rightOscopes _rightOtopLevel _rightOvarBeingDefined _rightOvariableStyle) of (_rightIglobalDefinitions, _rightIidentifier, _rightIisInModule, _rightIisSimpleExpression, _rightIisSingleVar, _rightIscopes, _rightIvariableStyle, _rightIwarnings) -> ( case ( ( _rightIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _opIidentifier _rightIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _rightIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisSimpleExpression -> ( case ( ( _rightIisSingleVar ) ) of _lhsOisSingleVar -> ( case ( ( _rightImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _rightIscopes ) ) of _lhsOscopes -> ( case ( ( _rightIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _opIwarnings ++ _rightIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Expr_UnOpExpr_1 ) ) of (sem_Expr_1) -> (_lhsOcopy, sem_Expr_1) ) ) ) ) ) -- ExprSuffixList ---------------------------------------------- -- cata sem_ExprSuffixList :: ExprSuffixList -> T_ExprSuffixList sem_ExprSuffixList list = (Prelude.foldr sem_ExprSuffixList_Cons sem_ExprSuffixList_Nil (Prelude.map sem_PFExprSuffix list)) -- semantic domain type T_ExprSuffixList = (ExprSuffixList, T_ExprSuffixList_1) type T_ExprSuffixList_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_ExprSuffixList = Inh_ExprSuffixList {config_Inh_ExprSuffixList :: LintSettings, funcName_Inh_ExprSuffixList :: String, globalDefinitions_Inh_ExprSuffixList :: (M.Map String [Region]), isInModule_Inh_ExprSuffixList :: Bool, isMeta_Inh_ExprSuffixList :: Bool, loopLevel_Inh_ExprSuffixList :: Int, mtokenPos_Inh_ExprSuffixList :: Region, scopeLevel_Inh_ExprSuffixList :: Int, scopes_Inh_ExprSuffixList :: ([M.Map String (Bool, Region)]), variableStyle_Inh_ExprSuffixList :: DeterminedVariableStyle} data Syn_ExprSuffixList = Syn_ExprSuffixList {copy_Syn_ExprSuffixList :: ExprSuffixList, globalDefinitions_Syn_ExprSuffixList :: (M.Map String [Region]), identifier_Syn_ExprSuffixList :: String, isInModule_Syn_ExprSuffixList :: Bool, isSimpleExpression_Syn_ExprSuffixList :: Bool, mtokenPos_Syn_ExprSuffixList :: Region, scopes_Syn_ExprSuffixList :: ([M.Map String (Bool, Region)]), variableStyle_Syn_ExprSuffixList :: DeterminedVariableStyle, warnings_Syn_ExprSuffixList :: ([String -> LintMessage])} wrap_ExprSuffixList :: T_ExprSuffixList -> Inh_ExprSuffixList -> Syn_ExprSuffixList wrap_ExprSuffixList sem (Inh_ExprSuffixList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_ExprSuffixList _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisSimpleExpression _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_ExprSuffixList_Cons :: T_PFExprSuffix -> T_ExprSuffixList -> T_ExprSuffixList sem_ExprSuffixList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_ExprSuffixList_Cons_1 :: T_ExprSuffixList_1 sem_ExprSuffixList_Cons_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOvariableStyle) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdIisSimpleExpression, _hdImtokenPos, _hdIscopes, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case (tl_1 _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOvariableStyle) of (_tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlIisSimpleExpression, _tlImtokenPos, _tlIscopes, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdIisSimpleExpression && _tlIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( _tlImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_ExprSuffixList_Cons_1 ) ) of (sem_ExprSuffixList_1) -> (_lhsOcopy, sem_ExprSuffixList_1) ) ) ) ) ) sem_ExprSuffixList_Nil :: T_ExprSuffixList sem_ExprSuffixList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_ExprSuffixList_Nil_1 :: T_ExprSuffixList_1 sem_ExprSuffixList_Nil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_ExprSuffixList_Nil_1 ) ) of (sem_ExprSuffixList_1) -> (_lhsOcopy, sem_ExprSuffixList_1) ) ) ) -- Field ------------------------------------------------------- -- cata sem_Field :: Field -> T_Field sem_Field (ExprField _key _value _sep) = (sem_Field_ExprField (sem_MExpr _key) (sem_MExpr _value) (sem_FieldSep _sep)) sem_Field (NamedField _key _value _sep) = (sem_Field_NamedField (sem_MToken _key) (sem_MExpr _value) (sem_FieldSep _sep)) sem_Field (UnnamedField _value _sep) = (sem_Field_UnnamedField (sem_MExpr _value) (sem_FieldSep _sep)) -- semantic domain type T_Field = (Field, T_Field_1) type T_Field_1 = LintSettings -> (S.Set Token) -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((S.Set Token), (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Field = Inh_Field {config_Inh_Field :: LintSettings, fieldNames_Inh_Field :: (S.Set Token), funcName_Inh_Field :: String, globalDefinitions_Inh_Field :: (M.Map String [Region]), isInModule_Inh_Field :: Bool, isMeta_Inh_Field :: Bool, loopLevel_Inh_Field :: Int, mtokenPos_Inh_Field :: Region, scopeLevel_Inh_Field :: Int, scopes_Inh_Field :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Field :: DeterminedVariableStyle} data Syn_Field = Syn_Field {copy_Syn_Field :: Field, fieldNames_Syn_Field :: (S.Set Token), globalDefinitions_Syn_Field :: (M.Map String [Region]), identifier_Syn_Field :: String, isInModule_Syn_Field :: Bool, mtokenPos_Syn_Field :: Region, scopes_Syn_Field :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Field :: DeterminedVariableStyle, warnings_Syn_Field :: ([String -> LintMessage])} wrap_Field :: T_Field -> Inh_Field -> Syn_Field wrap_Field sem (Inh_Field _lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Field _lhsOcopy _lhsOfieldNames _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Field_ExprField :: T_MExpr -> T_MExpr -> T_FieldSep -> T_Field sem_Field_ExprField key_ value_ sep_ = ( case (sep_) of (_sepIcopy, sep_1) -> ( case (value_) of (_valueIcopy, _valueImtokenPos, value_1) -> ( case (key_) of (_keyIcopy, _keyImtokenPos, key_1) -> ( case ( ( ExprField _keyIcopy _valueIcopy _sepIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Field_ExprField_1 :: T_Field_1 sem_Field_ExprField_1 = ( \_lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIfieldNames ) ) of _lhsOfieldNames -> ( case ( ( _lhsIscopes ) ) of _keyOscopes -> ( case ( ( _lhsIisMeta ) ) of _keyOisMeta -> ( case ( ( _lhsIconfig ) ) of _keyOconfig -> ( case ( ( Nothing ) ) of _keyOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _keyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _keyOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _keyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _keyOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _keyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _keyOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _keyOfuncName -> ( case ( ( True ) ) of _keyOtopLevel -> ( case ( ( True ) ) of _keyOinParentheses -> ( case ( ( False ) ) of _keyOisNegation -> ( case (key_1 _keyOconfig _keyOfuncName _keyOglobalDefinitions _keyOinParentheses _keyOisInModule _keyOisMeta _keyOisNegation _keyOloopLevel _keyOmtokenPos _keyOscopeLevel _keyOscopes _keyOtopLevel _keyOvarBeingDefined _keyOvariableStyle) of (_keyIglobalDefinitions, _keyIidentifier, _keyIisInModule, _keyIisSimpleExpression, _keyIisSingleVar, _keyIscopes, _keyIvariableStyle, _keyIwarnings) -> ( case ( ( _keyIscopes ) ) of _valueOscopes -> ( case ( ( _lhsIisMeta ) ) of _valueOisMeta -> ( case ( ( _keyIisInModule ) ) of _valueOisInModule -> ( case ( ( _keyIglobalDefinitions ) ) of _valueOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _valueOconfig -> ( case ( ( Nothing ) ) of _valueOvarBeingDefined -> ( case ( ( _keyIvariableStyle ) ) of _valueOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _valueOscopeLevel -> ( case ( ( _keyImtokenPos ) ) of _valueOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valueOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _valueOfuncName -> ( case ( ( True ) ) of _valueOtopLevel -> ( case ( ( True ) ) of _valueOinParentheses -> ( case ( ( False ) ) of _valueOisNegation -> ( case (value_1 _valueOconfig _valueOfuncName _valueOglobalDefinitions _valueOinParentheses _valueOisInModule _valueOisMeta _valueOisNegation _valueOloopLevel _valueOmtokenPos _valueOscopeLevel _valueOscopes _valueOtopLevel _valueOvarBeingDefined _valueOvariableStyle) of (_valueIglobalDefinitions, _valueIidentifier, _valueIisInModule, _valueIisSimpleExpression, _valueIisSingleVar, _valueIscopes, _valueIvariableStyle, _valueIwarnings) -> ( case ( ( _valueIglobalDefinitions ) ) of _sepOglobalDefinitions -> ( case ( ( _valueIvariableStyle ) ) of _sepOvariableStyle -> ( case ( ( _valueIscopes ) ) of _sepOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _sepOscopeLevel -> ( case ( ( _valueImtokenPos ) ) of _sepOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _sepOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _sepOisMeta -> ( case ( ( _valueIisInModule ) ) of _sepOisInModule -> ( case ( ( _lhsIfuncName ) ) of _sepOfuncName -> ( case ( ( _lhsIconfig ) ) of _sepOconfig -> ( case (sep_1 _sepOconfig _sepOfuncName _sepOglobalDefinitions _sepOisInModule _sepOisMeta _sepOloopLevel _sepOmtokenPos _sepOscopeLevel _sepOscopes _sepOvariableStyle) of (_sepIglobalDefinitions, _sepIidentifier, _sepIisInModule, _sepImtokenPos, _sepIscopes, _sepIvariableStyle, _sepIwarnings) -> ( case ( ( _sepIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _keyIidentifier (const _valueIidentifier _sepIidentifier)) ) ) of _lhsOidentifier -> ( case ( ( _sepIisInModule ) ) of _lhsOisInModule -> ( case ( ( _keyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _sepIscopes ) ) of _lhsOscopes -> ( case ( ( _sepIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _keyIwarnings ++ _valueIwarnings ++ _sepIwarnings ) ) of _lhsOwarnings -> (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Field_ExprField_1 ) ) of (sem_Field_1) -> (_lhsOcopy, sem_Field_1) ) ) ) ) ) ) sem_Field_NamedField :: T_MToken -> T_MExpr -> T_FieldSep -> T_Field sem_Field_NamedField key_ value_ sep_ = ( case (sep_) of (_sepIcopy, sep_1) -> ( case (value_) of (_valueIcopy, _valueImtokenPos, value_1) -> ( case (key_) of (_keyIcopy, _keyImtok, _keyImtokenPos, key_1) -> ( case ( ( NamedField _keyIcopy _valueIcopy _sepIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Field_NamedField_1 :: T_Field_1 sem_Field_NamedField_1 = ( \_lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( S.insert _keyImtok _lhsIfieldNames ) ) of _lhsOfieldNames -> ( case ( ( _lhsIscopes ) ) of _keyOscopes -> ( case ( ( _keyImtokenPos ) ) of _mtokenPos -> ( case ( ( _mtokenPos ) ) of _keyOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _keyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _keyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _keyOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _keyOfuncName -> ( case ( ( _lhsIconfig ) ) of _keyOconfig -> ( case (key_1 _keyOconfig _keyOfuncName _keyOglobalDefinitions _keyOisInModule _keyOisMeta _keyOmtokenPos _keyOscopes) of (_keyIglobalDefinitions, _keyIidentifier, _keyIisInModule, _keyIscopes, _keyIwarnings) -> ( case ( ( _keyIscopes ) ) of _valueOscopes -> ( case ( ( _lhsIisMeta ) ) of _valueOisMeta -> ( case ( ( _keyIisInModule ) ) of _valueOisInModule -> ( case ( ( _keyIglobalDefinitions ) ) of _valueOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _valueOconfig -> ( case ( ( Nothing ) ) of _valueOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _valueOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _valueOscopeLevel -> ( case ( ( _mtokenPos ) ) of _valueOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valueOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _valueOfuncName -> ( case ( ( True ) ) of _valueOtopLevel -> ( case ( ( True ) ) of _valueOinParentheses -> ( case ( ( False ) ) of _valueOisNegation -> ( case (value_1 _valueOconfig _valueOfuncName _valueOglobalDefinitions _valueOinParentheses _valueOisInModule _valueOisMeta _valueOisNegation _valueOloopLevel _valueOmtokenPos _valueOscopeLevel _valueOscopes _valueOtopLevel _valueOvarBeingDefined _valueOvariableStyle) of (_valueIglobalDefinitions, _valueIidentifier, _valueIisInModule, _valueIisSimpleExpression, _valueIisSingleVar, _valueIscopes, _valueIvariableStyle, _valueIwarnings) -> ( case ( ( _valueIglobalDefinitions ) ) of _sepOglobalDefinitions -> ( case ( ( _valueIvariableStyle ) ) of _sepOvariableStyle -> ( case ( ( _valueIscopes ) ) of _sepOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _sepOscopeLevel -> ( case ( ( _mtokenPos ) ) of _sepOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _sepOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _sepOisMeta -> ( case ( ( _valueIisInModule ) ) of _sepOisInModule -> ( case ( ( _lhsIfuncName ) ) of _sepOfuncName -> ( case ( ( _lhsIconfig ) ) of _sepOconfig -> ( case (sep_1 _sepOconfig _sepOfuncName _sepOglobalDefinitions _sepOisInModule _sepOisMeta _sepOloopLevel _sepOmtokenPos _sepOscopeLevel _sepOscopes _sepOvariableStyle) of (_sepIglobalDefinitions, _sepIidentifier, _sepIisInModule, _sepImtokenPos, _sepIscopes, _sepIvariableStyle, _sepIwarnings) -> ( case ( ( _sepIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _keyIidentifier (const _valueIidentifier _sepIidentifier)) ) ) of _lhsOidentifier -> ( case ( ( _sepIisInModule ) ) of _lhsOisInModule -> ( case ( ( _mtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _sepIscopes ) ) of _lhsOscopes -> ( case ( ( _sepIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _keyIwarnings ++ _valueIwarnings ++ _sepIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_duplicateTableKeys _lhsIconfig) || not (S.member _keyImtok _lhsIfieldNames) then id else (:) $ warn _keyImtokenPos $ DuplicateKeyInTable _keyImtok ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Field_NamedField_1 ) ) of (sem_Field_1) -> (_lhsOcopy, sem_Field_1) ) ) ) ) ) ) sem_Field_UnnamedField :: T_MExpr -> T_FieldSep -> T_Field sem_Field_UnnamedField value_ sep_ = ( case (sep_) of (_sepIcopy, sep_1) -> ( case (value_) of (_valueIcopy, _valueImtokenPos, value_1) -> ( case ( ( UnnamedField _valueIcopy _sepIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Field_UnnamedField_1 :: T_Field_1 sem_Field_UnnamedField_1 = ( \_lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIfieldNames ) ) of _lhsOfieldNames -> ( case ( ( _lhsIscopes ) ) of _valueOscopes -> ( case ( ( _lhsIisMeta ) ) of _valueOisMeta -> ( case ( ( _lhsIisInModule ) ) of _valueOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _valueOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _valueOconfig -> ( case ( ( Nothing ) ) of _valueOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _valueOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _valueOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _valueOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valueOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _valueOfuncName -> ( case ( ( True ) ) of _valueOtopLevel -> ( case ( ( True ) ) of _valueOinParentheses -> ( case ( ( False ) ) of _valueOisNegation -> ( case (value_1 _valueOconfig _valueOfuncName _valueOglobalDefinitions _valueOinParentheses _valueOisInModule _valueOisMeta _valueOisNegation _valueOloopLevel _valueOmtokenPos _valueOscopeLevel _valueOscopes _valueOtopLevel _valueOvarBeingDefined _valueOvariableStyle) of (_valueIglobalDefinitions, _valueIidentifier, _valueIisInModule, _valueIisSimpleExpression, _valueIisSingleVar, _valueIscopes, _valueIvariableStyle, _valueIwarnings) -> ( case ( ( _valueIglobalDefinitions ) ) of _sepOglobalDefinitions -> ( case ( ( _valueIvariableStyle ) ) of _sepOvariableStyle -> ( case ( ( _valueIscopes ) ) of _sepOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _sepOscopeLevel -> ( case ( ( _valueImtokenPos ) ) of _sepOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _sepOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _sepOisMeta -> ( case ( ( _valueIisInModule ) ) of _sepOisInModule -> ( case ( ( _lhsIfuncName ) ) of _sepOfuncName -> ( case ( ( _lhsIconfig ) ) of _sepOconfig -> ( case (sep_1 _sepOconfig _sepOfuncName _sepOglobalDefinitions _sepOisInModule _sepOisMeta _sepOloopLevel _sepOmtokenPos _sepOscopeLevel _sepOscopes _sepOvariableStyle) of (_sepIglobalDefinitions, _sepIidentifier, _sepIisInModule, _sepImtokenPos, _sepIscopes, _sepIvariableStyle, _sepIwarnings) -> ( case ( ( _sepIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _valueIidentifier _sepIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _sepIisInModule ) ) of _lhsOisInModule -> ( case ( ( _sepImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _sepIscopes ) ) of _lhsOscopes -> ( case ( ( _sepIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _valueIwarnings ++ _sepIwarnings ) ) of _lhsOwarnings -> (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Field_UnnamedField_1 ) ) of (sem_Field_1) -> (_lhsOcopy, sem_Field_1) ) ) ) ) ) -- FieldList --------------------------------------------------- -- cata sem_FieldList :: FieldList -> T_FieldList sem_FieldList list = (Prelude.foldr sem_FieldList_Cons sem_FieldList_Nil (Prelude.map sem_Field list)) -- semantic domain type T_FieldList = (FieldList, T_FieldList_1) type T_FieldList_1 = LintSettings -> (S.Set Token) -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((S.Set Token), (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_FieldList = Inh_FieldList {config_Inh_FieldList :: LintSettings, fieldNames_Inh_FieldList :: (S.Set Token), funcName_Inh_FieldList :: String, globalDefinitions_Inh_FieldList :: (M.Map String [Region]), isInModule_Inh_FieldList :: Bool, isMeta_Inh_FieldList :: Bool, loopLevel_Inh_FieldList :: Int, mtokenPos_Inh_FieldList :: Region, scopeLevel_Inh_FieldList :: Int, scopes_Inh_FieldList :: ([M.Map String (Bool, Region)]), variableStyle_Inh_FieldList :: DeterminedVariableStyle} data Syn_FieldList = Syn_FieldList {copy_Syn_FieldList :: FieldList, fieldNames_Syn_FieldList :: (S.Set Token), globalDefinitions_Syn_FieldList :: (M.Map String [Region]), identifier_Syn_FieldList :: String, isInModule_Syn_FieldList :: Bool, mtokenPos_Syn_FieldList :: Region, scopes_Syn_FieldList :: ([M.Map String (Bool, Region)]), variableStyle_Syn_FieldList :: DeterminedVariableStyle, warnings_Syn_FieldList :: ([String -> LintMessage])} wrap_FieldList :: T_FieldList -> Inh_FieldList -> Syn_FieldList wrap_FieldList sem (Inh_FieldList _lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_FieldList _lhsOcopy _lhsOfieldNames _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_FieldList_Cons :: T_Field -> T_FieldList -> T_FieldList sem_FieldList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_FieldList_Cons_1 :: T_FieldList_1 sem_FieldList_Cons_1 = ( \_lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIfieldNames ) ) of _hdOfieldNames -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case (hd_1 _hdOconfig _hdOfieldNames _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOvariableStyle) of (_hdIfieldNames, _hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdImtokenPos, _hdIscopes, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIfieldNames ) ) of _tlOfieldNames -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case (tl_1 _tlOconfig _tlOfieldNames _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOvariableStyle) of (_tlIfieldNames, _tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIfieldNames ) ) of _lhsOfieldNames -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_FieldList_Cons_1 ) ) of (sem_FieldList_1) -> (_lhsOcopy, sem_FieldList_1) ) ) ) ) ) sem_FieldList_Nil :: T_FieldList sem_FieldList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_FieldList_Nil_1 :: T_FieldList_1 sem_FieldList_Nil_1 = ( \_lhsIconfig _lhsIfieldNames _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIfieldNames ) ) of _lhsOfieldNames -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOfieldNames, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_FieldList_Nil_1 ) ) of (sem_FieldList_1) -> (_lhsOcopy, sem_FieldList_1) ) ) ) -- FieldSep ---------------------------------------------------- -- cata sem_FieldSep :: FieldSep -> T_FieldSep sem_FieldSep (CommaSep) = (sem_FieldSep_CommaSep) sem_FieldSep (SemicolonSep) = (sem_FieldSep_SemicolonSep) sem_FieldSep (NoSep) = (sem_FieldSep_NoSep) -- semantic domain type T_FieldSep = (FieldSep, T_FieldSep_1) type T_FieldSep_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_FieldSep = Inh_FieldSep {config_Inh_FieldSep :: LintSettings, funcName_Inh_FieldSep :: String, globalDefinitions_Inh_FieldSep :: (M.Map String [Region]), isInModule_Inh_FieldSep :: Bool, isMeta_Inh_FieldSep :: Bool, loopLevel_Inh_FieldSep :: Int, mtokenPos_Inh_FieldSep :: Region, scopeLevel_Inh_FieldSep :: Int, scopes_Inh_FieldSep :: ([M.Map String (Bool, Region)]), variableStyle_Inh_FieldSep :: DeterminedVariableStyle} data Syn_FieldSep = Syn_FieldSep {copy_Syn_FieldSep :: FieldSep, globalDefinitions_Syn_FieldSep :: (M.Map String [Region]), identifier_Syn_FieldSep :: String, isInModule_Syn_FieldSep :: Bool, mtokenPos_Syn_FieldSep :: Region, scopes_Syn_FieldSep :: ([M.Map String (Bool, Region)]), variableStyle_Syn_FieldSep :: DeterminedVariableStyle, warnings_Syn_FieldSep :: ([String -> LintMessage])} wrap_FieldSep :: T_FieldSep -> Inh_FieldSep -> Syn_FieldSep wrap_FieldSep sem (Inh_FieldSep _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_FieldSep _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_FieldSep_CommaSep :: T_FieldSep sem_FieldSep_CommaSep = ( case ( ( CommaSep ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_FieldSep_CommaSep_1 :: T_FieldSep_1 sem_FieldSep_CommaSep_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_FieldSep_CommaSep_1 ) ) of (sem_FieldSep_1) -> (_lhsOcopy, sem_FieldSep_1) ) ) ) sem_FieldSep_SemicolonSep :: T_FieldSep sem_FieldSep_SemicolonSep = ( case ( ( SemicolonSep ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_FieldSep_SemicolonSep_1 :: T_FieldSep_1 sem_FieldSep_SemicolonSep_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_FieldSep_SemicolonSep_1 ) ) of (sem_FieldSep_1) -> (_lhsOcopy, sem_FieldSep_1) ) ) ) sem_FieldSep_NoSep :: T_FieldSep sem_FieldSep_NoSep = ( case ( ( NoSep ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_FieldSep_NoSep_1 :: T_FieldSep_1 sem_FieldSep_NoSep_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_FieldSep_NoSep_1 ) ) of (sem_FieldSep_1) -> (_lhsOcopy, sem_FieldSep_1) ) ) ) -- FuncName ---------------------------------------------------- -- cata sem_FuncName :: FuncName -> T_FuncName sem_FuncName (FuncName _names _meta) = (sem_FuncName_FuncName _names _meta) -- semantic domain type T_FuncName = (FuncName, Bool, T_FuncName_1) type T_FuncName_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), Bool, String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_FuncName = Inh_FuncName {config_Inh_FuncName :: LintSettings, funcName_Inh_FuncName :: String, globalDefinitions_Inh_FuncName :: (M.Map String [Region]), isInModule_Inh_FuncName :: Bool, isMeta_Inh_FuncName :: Bool, loopLevel_Inh_FuncName :: Int, mtokenPos_Inh_FuncName :: Region, scopeLevel_Inh_FuncName :: Int, scopes_Inh_FuncName :: ([M.Map String (Bool, Region)]), variableStyle_Inh_FuncName :: DeterminedVariableStyle} data Syn_FuncName = Syn_FuncName {copy_Syn_FuncName :: FuncName, globalDefinitions_Syn_FuncName :: (M.Map String [Region]), hasSuffixes_Syn_FuncName :: Bool, identifier_Syn_FuncName :: String, isInModule_Syn_FuncName :: Bool, isMeta_Syn_FuncName :: Bool, mtokenPos_Syn_FuncName :: Region, scopes_Syn_FuncName :: ([M.Map String (Bool, Region)]), variableStyle_Syn_FuncName :: DeterminedVariableStyle, warnings_Syn_FuncName :: ([String -> LintMessage])} wrap_FuncName :: T_FuncName -> Inh_FuncName -> Syn_FuncName wrap_FuncName sem (Inh_FuncName _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, _lhsOisMeta, sem_1) = sem (_lhsOglobalDefinitions, _lhsOhasSuffixes, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_FuncName _lhsOcopy _lhsOglobalDefinitions _lhsOhasSuffixes _lhsOidentifier _lhsOisInModule _lhsOisMeta _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_FuncName_FuncName :: ([MToken]) -> (Maybe MToken) -> T_FuncName sem_FuncName_FuncName names_ meta_ = ( case ( ( FuncName names_ meta_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( isJust meta_ ) ) of _lhsOisMeta -> ( case ( ( let sem_FuncName_FuncName_1 :: T_FuncName_1 sem_FuncName_FuncName_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( length names_ > 1 ) ) of _lhsOhasSuffixes -> ( case ( ( tokenLabel . head $ names_ ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( mpos (head names_) ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOhasSuffixes, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_FuncName_FuncName_1 ) ) of (sem_FuncName_1) -> (_lhsOcopy, _lhsOisMeta, sem_FuncName_1) ) ) ) ) -- MElse ------------------------------------------------------- -- cata sem_MElse :: MElse -> T_MElse sem_MElse (MElse _pos _body) = (sem_MElse_MElse (sem_Region _pos) (sem_Block _body)) -- semantic domain type T_MElse = (MElse, T_MElse_1) type T_MElse_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> (Bool, (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), Int, DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MElse = Inh_MElse {config_Inh_MElse :: LintSettings, funcName_Inh_MElse :: String, globalDefinitions_Inh_MElse :: (M.Map String [Region]), isInModule_Inh_MElse :: Bool, isMeta_Inh_MElse :: Bool, loopLevel_Inh_MElse :: Int, mtokenPos_Inh_MElse :: Region, scopeLevel_Inh_MElse :: Int, scopes_Inh_MElse :: ([M.Map String (Bool, Region)]), variableStyle_Inh_MElse :: DeterminedVariableStyle} data Syn_MElse = Syn_MElse {copy_Syn_MElse :: MElse, elseExists_Syn_MElse :: Bool, globalDefinitions_Syn_MElse :: (M.Map String [Region]), identifier_Syn_MElse :: String, isInModule_Syn_MElse :: Bool, mtokenPos_Syn_MElse :: Region, scopes_Syn_MElse :: ([M.Map String (Bool, Region)]), statementCount_Syn_MElse :: Int, variableStyle_Syn_MElse :: DeterminedVariableStyle, warnings_Syn_MElse :: ([String -> LintMessage])} wrap_MElse :: T_MElse -> Inh_MElse -> Syn_MElse wrap_MElse sem (Inh_MElse _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_MElse _lhsOcopy _lhsOelseExists _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOstatementCount _lhsOvariableStyle _lhsOwarnings) ) sem_MElse_MElse :: T_Region -> T_Block -> T_MElse sem_MElse_MElse pos_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (pos_) of (_posIcopy, _posIidentifier, _posIwarnings) -> ( case ( ( MElse _posIcopy _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MElse_MElse_1 :: T_MElse_1 sem_MElse_MElse_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( False ) ) of _lhsOelseExists -> ( case ( ( _lhsIscopes ) ) of _bodyOscopes -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _bodyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _posIidentifier _bodyIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _posIcopy ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIstatementCount ) ) of _lhsOstatementCount -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _posIwarnings ++ _bodyIwarnings ) ) of _lhsOwarnings -> (_lhsOelseExists, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MElse_MElse_1 ) ) of (sem_MElse_1) -> (_lhsOcopy, sem_MElse_1) ) ) ) ) ) -- MElseIf ----------------------------------------------------- -- cata sem_MElseIf :: MElseIf -> T_MElseIf sem_MElseIf (MElseIf _pos _elif) = (sem_MElseIf_MElseIf (sem_Region _pos) (sem_ElseIf _elif)) -- semantic domain type T_MElseIf = (MElseIf, T_MElseIf_1) type T_MElseIf_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MElseIf = Inh_MElseIf {config_Inh_MElseIf :: LintSettings, funcName_Inh_MElseIf :: String, globalDefinitions_Inh_MElseIf :: (M.Map String [Region]), isInModule_Inh_MElseIf :: Bool, isMeta_Inh_MElseIf :: Bool, loopLevel_Inh_MElseIf :: Int, mtokenPos_Inh_MElseIf :: Region, scopeLevel_Inh_MElseIf :: Int, scopes_Inh_MElseIf :: ([M.Map String (Bool, Region)]), variableStyle_Inh_MElseIf :: DeterminedVariableStyle} data Syn_MElseIf = Syn_MElseIf {copy_Syn_MElseIf :: MElseIf, globalDefinitions_Syn_MElseIf :: (M.Map String [Region]), identifier_Syn_MElseIf :: String, isInModule_Syn_MElseIf :: Bool, mtokenPos_Syn_MElseIf :: Region, scopes_Syn_MElseIf :: ([M.Map String (Bool, Region)]), variableStyle_Syn_MElseIf :: DeterminedVariableStyle, warnings_Syn_MElseIf :: ([String -> LintMessage])} wrap_MElseIf :: T_MElseIf -> Inh_MElseIf -> Syn_MElseIf wrap_MElseIf sem (Inh_MElseIf _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_MElseIf _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_MElseIf_MElseIf :: T_Region -> T_ElseIf -> T_MElseIf sem_MElseIf_MElseIf pos_ elif_ = ( case (elif_) of (_elifIcopy, elif_1) -> ( case (pos_) of (_posIcopy, _posIidentifier, _posIwarnings) -> ( case ( ( MElseIf _posIcopy _elifIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MElseIf_MElseIf_1 :: T_MElseIf_1 sem_MElseIf_MElseIf_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _elifOscopes -> ( case ( ( _lhsIisMeta ) ) of _elifOisMeta -> ( case ( ( _lhsIisInModule ) ) of _elifOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _elifOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _elifOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _elifOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _elifOscopeLevel -> ( case ( ( _lhsIloopLevel ) ) of _elifOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _elifOfuncName -> ( case ( ( _posIcopy ) ) of _elifOmtokenPos -> ( case (elif_1 _elifOconfig _elifOfuncName _elifOglobalDefinitions _elifOisInModule _elifOisMeta _elifOloopLevel _elifOmtokenPos _elifOscopeLevel _elifOscopes _elifOvariableStyle) of (_elifIglobalDefinitions, _elifIidentifier, _elifIisInModule, _elifImtokenPos, _elifIscopes, _elifIvariableStyle, _elifIwarnings) -> ( case ( ( _elifIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _posIidentifier _elifIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _elifIisInModule ) ) of _lhsOisInModule -> ( case ( ( _elifImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _elifIscopes ) ) of _lhsOscopes -> ( case ( ( _elifIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _posIwarnings ++ _elifIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MElseIf_MElseIf_1 ) ) of (sem_MElseIf_1) -> (_lhsOcopy, sem_MElseIf_1) ) ) ) ) ) -- MExpr ------------------------------------------------------- -- cata sem_MExpr :: MExpr -> T_MExpr sem_MExpr (MExpr _pos _expr) = (sem_MExpr_MExpr (sem_Region _pos) (sem_Expr _expr)) -- semantic domain type T_MExpr = (MExpr, Region, T_MExpr_1) type T_MExpr_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> Bool -> (Maybe MToken) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, (Maybe MToken), ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MExpr = Inh_MExpr {config_Inh_MExpr :: LintSettings, funcName_Inh_MExpr :: String, globalDefinitions_Inh_MExpr :: (M.Map String [Region]), inParentheses_Inh_MExpr :: Bool, isInModule_Inh_MExpr :: Bool, isMeta_Inh_MExpr :: Bool, isNegation_Inh_MExpr :: Bool, loopLevel_Inh_MExpr :: Int, mtokenPos_Inh_MExpr :: Region, scopeLevel_Inh_MExpr :: Int, scopes_Inh_MExpr :: ([M.Map String (Bool, Region)]), topLevel_Inh_MExpr :: Bool, varBeingDefined_Inh_MExpr :: (Maybe MToken), variableStyle_Inh_MExpr :: DeterminedVariableStyle} data Syn_MExpr = Syn_MExpr {copy_Syn_MExpr :: MExpr, globalDefinitions_Syn_MExpr :: (M.Map String [Region]), identifier_Syn_MExpr :: String, isInModule_Syn_MExpr :: Bool, isSimpleExpression_Syn_MExpr :: Bool, isSingleVar_Syn_MExpr :: (Maybe MToken), mtokenPos_Syn_MExpr :: Region, scopes_Syn_MExpr :: ([M.Map String (Bool, Region)]), variableStyle_Syn_MExpr :: DeterminedVariableStyle, warnings_Syn_MExpr :: ([String -> LintMessage])} wrap_MExpr :: T_MExpr -> Inh_MExpr -> Syn_MExpr wrap_MExpr sem (Inh_MExpr _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle) = ( let (_lhsOcopy, _lhsOmtokenPos, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle in (Syn_MExpr _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisSimpleExpression _lhsOisSingleVar _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_MExpr_MExpr :: T_Region -> T_Expr -> T_MExpr sem_MExpr_MExpr pos_ expr_ = ( case (expr_) of (_exprIcopy, expr_1) -> ( case (pos_) of (_posIcopy, _posIidentifier, _posIwarnings) -> ( case ( ( MExpr _posIcopy _exprIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _posIcopy ) ) of _lhsOmtokenPos -> ( case ( ( let sem_MExpr_MExpr_1 :: T_MExpr_1 sem_MExpr_MExpr_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIvarBeingDefined ) ) of _exprOvarBeingDefined -> ( case ( ( _lhsIscopes ) ) of _exprOscopes -> ( case ( ( _lhsIisMeta ) ) of _exprOisMeta -> ( case ( ( _lhsIisInModule ) ) of _exprOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _exprOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _exprOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _exprOvariableStyle -> ( case ( ( _lhsItopLevel ) ) of _exprOtopLevel -> ( case ( ( _lhsIscopeLevel ) ) of _exprOscopeLevel -> ( case ( ( _lhsIloopLevel ) ) of _exprOloopLevel -> ( case ( ( _lhsIisNegation ) ) of _exprOisNegation -> ( case ( ( _lhsIinParentheses ) ) of _exprOinParentheses -> ( case ( ( _lhsIfuncName ) ) of _exprOfuncName -> ( case ( ( _posIcopy ) ) of _exprOmtokenPos -> ( case (expr_1 _exprOconfig _exprOfuncName _exprOglobalDefinitions _exprOinParentheses _exprOisInModule _exprOisMeta _exprOisNegation _exprOloopLevel _exprOmtokenPos _exprOscopeLevel _exprOscopes _exprOtopLevel _exprOvarBeingDefined _exprOvariableStyle) of (_exprIglobalDefinitions, _exprIidentifier, _exprIisInModule, _exprIisSimpleExpression, _exprIisSingleVar, _exprImtokenPos, _exprIscopes, _exprIvariableStyle, _exprIwarnings) -> ( case ( ( _exprIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _posIidentifier _exprIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _exprIisInModule ) ) of _lhsOisInModule -> ( case ( ( _exprIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( _exprIisSingleVar ) ) of _lhsOisSingleVar -> ( case ( ( _exprIscopes ) ) of _lhsOscopes -> ( case ( ( _exprIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _posIwarnings ++ _exprIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MExpr_MExpr_1 ) ) of (sem_MExpr_1) -> (_lhsOcopy, _lhsOmtokenPos, sem_MExpr_1) ) ) ) ) ) ) -- MExprList --------------------------------------------------- -- cata sem_MExprList :: MExprList -> T_MExprList sem_MExprList list = (Prelude.foldr sem_MExprList_Cons sem_MExprList_Nil (Prelude.map sem_MExpr list)) -- semantic domain type T_MExprList = (MExprList, T_MExprList_1) type T_MExprList_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> Bool -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MExprList = Inh_MExprList {config_Inh_MExprList :: LintSettings, funcName_Inh_MExprList :: String, globalDefinitions_Inh_MExprList :: (M.Map String [Region]), inParentheses_Inh_MExprList :: Bool, isInModule_Inh_MExprList :: Bool, isMeta_Inh_MExprList :: Bool, loopLevel_Inh_MExprList :: Int, mtokenPos_Inh_MExprList :: Region, scopeLevel_Inh_MExprList :: Int, scopes_Inh_MExprList :: ([M.Map String (Bool, Region)]), topLevel_Inh_MExprList :: Bool, variableStyle_Inh_MExprList :: DeterminedVariableStyle} data Syn_MExprList = Syn_MExprList {copy_Syn_MExprList :: MExprList, globalDefinitions_Syn_MExprList :: (M.Map String [Region]), identifier_Syn_MExprList :: String, isInModule_Syn_MExprList :: Bool, mtokenPos_Syn_MExprList :: Region, scopes_Syn_MExprList :: ([M.Map String (Bool, Region)]), variableStyle_Syn_MExprList :: DeterminedVariableStyle, warnings_Syn_MExprList :: ([String -> LintMessage])} wrap_MExprList :: T_MExprList -> Inh_MExprList -> Syn_MExprList wrap_MExprList sem (Inh_MExprList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvariableStyle in (Syn_MExprList _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_MExprList_Cons :: T_MExpr -> T_MExprList -> T_MExprList sem_MExprList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, _hdImtokenPos, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MExprList_Cons_1 :: T_MExprList_1 sem_MExprList_Cons_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( Nothing ) ) of _hdOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsItopLevel ) ) of _hdOtopLevel -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIinParentheses ) ) of _hdOinParentheses -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case ( ( False ) ) of _hdOisNegation -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOinParentheses _hdOisInModule _hdOisMeta _hdOisNegation _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOtopLevel _hdOvarBeingDefined _hdOvariableStyle) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdIisSimpleExpression, _hdIisSingleVar, _hdIscopes, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _lhsItopLevel ) ) of _tlOtopLevel -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIinParentheses ) ) of _tlOinParentheses -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case (tl_1 _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOinParentheses _tlOisInModule _tlOisMeta _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOtopLevel _tlOvariableStyle) of (_tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MExprList_Cons_1 ) ) of (sem_MExprList_1) -> (_lhsOcopy, sem_MExprList_1) ) ) ) ) ) sem_MExprList_Nil :: T_MExprList sem_MExprList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MExprList_Nil_1 :: T_MExprList_1 sem_MExprList_Nil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_MExprList_Nil_1 ) ) of (sem_MExprList_1) -> (_lhsOcopy, sem_MExprList_1) ) ) ) -- MStat ------------------------------------------------------- -- cata sem_MStat :: MStat -> T_MStat sem_MStat (MStat _pos _stat) = (sem_MStat_MStat (sem_Region _pos) (sem_Stat _stat)) -- semantic domain type T_MStat = (MStat, T_MStat_1) type T_MStat_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), Int, DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MStat = Inh_MStat {config_Inh_MStat :: LintSettings, funcName_Inh_MStat :: String, globalDefinitions_Inh_MStat :: (M.Map String [Region]), isInModule_Inh_MStat :: Bool, isMeta_Inh_MStat :: Bool, loopLevel_Inh_MStat :: Int, mtokenPos_Inh_MStat :: Region, scopeLevel_Inh_MStat :: Int, scopes_Inh_MStat :: ([M.Map String (Bool, Region)]), variableStyle_Inh_MStat :: DeterminedVariableStyle} data Syn_MStat = Syn_MStat {copy_Syn_MStat :: MStat, globalDefinitions_Syn_MStat :: (M.Map String [Region]), identifier_Syn_MStat :: String, isIfStatement_Syn_MStat :: Bool, isInModule_Syn_MStat :: Bool, mtokenPos_Syn_MStat :: Region, scopes_Syn_MStat :: ([M.Map String (Bool, Region)]), statementCount_Syn_MStat :: Int, variableStyle_Syn_MStat :: DeterminedVariableStyle, warnings_Syn_MStat :: ([String -> LintMessage])} wrap_MStat :: T_MStat -> Inh_MStat -> Syn_MStat wrap_MStat sem (Inh_MStat _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_MStat _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisIfStatement _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOstatementCount _lhsOvariableStyle _lhsOwarnings) ) sem_MStat_MStat :: T_Region -> T_Stat -> T_MStat sem_MStat_MStat pos_ stat_ = ( case (stat_) of (_statIcopy, stat_1) -> ( case (pos_) of (_posIcopy, _posIidentifier, _posIwarnings) -> ( case ( ( MStat _posIcopy _statIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MStat_MStat_1 :: T_MStat_1 sem_MStat_MStat_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _statOscopes -> ( case ( ( _lhsIisMeta ) ) of _statOisMeta -> ( case ( ( _lhsIisInModule ) ) of _statOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _statOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _statOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _statOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _statOscopeLevel -> ( case ( ( _lhsIloopLevel ) ) of _statOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _statOfuncName -> ( case ( ( _posIcopy ) ) of _statOmtokenPos -> ( case (stat_1 _statOconfig _statOfuncName _statOglobalDefinitions _statOisInModule _statOisMeta _statOloopLevel _statOmtokenPos _statOscopeLevel _statOscopes _statOvariableStyle) of (_statIglobalDefinitions, _statIidentifier, _statIisIfStatement, _statIisInModule, _statImtokenPos, _statIscopes, _statIvariableStyle, _statIwarnings) -> ( case ( ( _statIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _posIidentifier _statIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _statIisIfStatement ) ) of _lhsOisIfStatement -> ( case ( ( _statIisInModule ) ) of _lhsOisInModule -> ( case ( ( _posIcopy ) ) of _lhsOmtokenPos -> ( case ( ( _statIscopes ) ) of _lhsOscopes -> ( case ( ( 1 ) ) of _lhsOstatementCount -> ( case ( ( _statIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _posIwarnings ++ _statIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MStat_MStat_1 ) ) of (sem_MStat_1) -> (_lhsOcopy, sem_MStat_1) ) ) ) ) ) -- MStatList --------------------------------------------------- -- cata sem_MStatList :: MStatList -> T_MStatList sem_MStatList list = (Prelude.foldr sem_MStatList_Cons sem_MStatList_Nil (Prelude.map sem_MStat list)) -- semantic domain type T_MStatList = (MStatList, T_MStatList_1) type T_MStatList_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), Int, DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MStatList = Inh_MStatList {config_Inh_MStatList :: LintSettings, funcName_Inh_MStatList :: String, globalDefinitions_Inh_MStatList :: (M.Map String [Region]), isInModule_Inh_MStatList :: Bool, isMeta_Inh_MStatList :: Bool, loopLevel_Inh_MStatList :: Int, mtokenPos_Inh_MStatList :: Region, scopeLevel_Inh_MStatList :: Int, scopes_Inh_MStatList :: ([M.Map String (Bool, Region)]), variableStyle_Inh_MStatList :: DeterminedVariableStyle} data Syn_MStatList = Syn_MStatList {copy_Syn_MStatList :: MStatList, globalDefinitions_Syn_MStatList :: (M.Map String [Region]), identifier_Syn_MStatList :: String, isIfStatement_Syn_MStatList :: Bool, isInModule_Syn_MStatList :: Bool, mtokenPos_Syn_MStatList :: Region, scopes_Syn_MStatList :: ([M.Map String (Bool, Region)]), statementCount_Syn_MStatList :: Int, variableStyle_Syn_MStatList :: DeterminedVariableStyle, warnings_Syn_MStatList :: ([String -> LintMessage])} wrap_MStatList :: T_MStatList -> Inh_MStatList -> Syn_MStatList wrap_MStatList sem (Inh_MStatList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_MStatList _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisIfStatement _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOstatementCount _lhsOvariableStyle _lhsOwarnings) ) sem_MStatList_Cons :: T_MStat -> T_MStatList -> T_MStatList sem_MStatList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MStatList_Cons_1 :: T_MStatList_1 sem_MStatList_Cons_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOvariableStyle) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisIfStatement, _hdIisInModule, _hdImtokenPos, _hdIscopes, _hdIstatementCount, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case (tl_1 _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOvariableStyle) of (_tlIglobalDefinitions, _tlIidentifier, _tlIisIfStatement, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIstatementCount, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _hdIisIfStatement || _tlIisIfStatement ) ) of _lhsOisIfStatement -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _hdIstatementCount + _tlIstatementCount ) ) of _lhsOstatementCount -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MStatList_Cons_1 ) ) of (sem_MStatList_1) -> (_lhsOcopy, sem_MStatList_1) ) ) ) ) ) sem_MStatList_Nil :: T_MStatList sem_MStatList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MStatList_Nil_1 :: T_MStatList_1 sem_MStatList_Nil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( 0 ) ) of _lhsOstatementCount -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOstatementCount, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) in sem_MStatList_Nil_1 ) ) of (sem_MStatList_1) -> (_lhsOcopy, sem_MStatList_1) ) ) ) -- MToken ------------------------------------------------------ -- cata sem_MToken :: MToken -> T_MToken sem_MToken (MToken _mpos _mtok) = (sem_MToken_MToken (sem_Region _mpos) (sem_Token _mtok)) -- semantic domain type T_MToken = (MToken, Token, Region, T_MToken_1) type T_MToken_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Region -> ([M.Map String (Bool, Region)]) -> ((M.Map String [Region]), String, Bool, ([M.Map String (Bool, Region)]), ([String -> LintMessage])) data Inh_MToken = Inh_MToken {config_Inh_MToken :: LintSettings, funcName_Inh_MToken :: String, globalDefinitions_Inh_MToken :: (M.Map String [Region]), isInModule_Inh_MToken :: Bool, isMeta_Inh_MToken :: Bool, mtokenPos_Inh_MToken :: Region, scopes_Inh_MToken :: ([M.Map String (Bool, Region)])} data Syn_MToken = Syn_MToken {copy_Syn_MToken :: MToken, globalDefinitions_Syn_MToken :: (M.Map String [Region]), identifier_Syn_MToken :: String, isInModule_Syn_MToken :: Bool, mtok_Syn_MToken :: Token, mtokenPos_Syn_MToken :: Region, scopes_Syn_MToken :: ([M.Map String (Bool, Region)]), warnings_Syn_MToken :: ([String -> LintMessage])} wrap_MToken :: T_MToken -> Inh_MToken -> Syn_MToken wrap_MToken sem (Inh_MToken _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes) = ( let (_lhsOcopy, _lhsOmtok, _lhsOmtokenPos, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOscopes, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes in (Syn_MToken _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtok _lhsOmtokenPos _lhsOscopes _lhsOwarnings) ) sem_MToken_MToken :: T_Region -> T_Token -> T_MToken sem_MToken_MToken mpos_ mtok_ = ( case (mtok_) of (_mtokIcopy, _mtokIidentifier, _mtokIwarnings) -> ( case (mpos_) of (_mposIcopy, _mposIidentifier, _mposIwarnings) -> ( case ( ( MToken _mposIcopy _mtokIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _mtokIcopy ) ) of _lhsOmtok -> ( case ( ( _mposIcopy ) ) of _lhsOmtokenPos -> ( case ( ( let sem_MToken_MToken_1 :: T_MToken_1 sem_MToken_MToken_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _mtokIidentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _mposIwarnings ++ _mtokIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_goto_identifier _lhsIconfig) || _mtokIidentifier /= "goto" then id else (:) $ warn _mposIcopy GotoAsIdentifier ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOscopes, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_MToken_MToken_1 ) ) of (sem_MToken_1) -> (_lhsOcopy, _lhsOmtok, _lhsOmtokenPos, sem_MToken_1) ) ) ) ) ) ) ) -- MTokenList -------------------------------------------------- -- cata sem_MTokenList :: MTokenList -> T_MTokenList sem_MTokenList list = (Prelude.foldr sem_MTokenList_Cons sem_MTokenList_Nil (Prelude.map sem_MToken list)) -- semantic domain type T_MTokenList = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Region -> ([M.Map String (Bool, Region)]) -> (MTokenList, (M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), ([String -> LintMessage])) data Inh_MTokenList = Inh_MTokenList {config_Inh_MTokenList :: LintSettings, funcName_Inh_MTokenList :: String, globalDefinitions_Inh_MTokenList :: (M.Map String [Region]), isInModule_Inh_MTokenList :: Bool, isMeta_Inh_MTokenList :: Bool, mtokenPos_Inh_MTokenList :: Region, scopes_Inh_MTokenList :: ([M.Map String (Bool, Region)])} data Syn_MTokenList = Syn_MTokenList {copy_Syn_MTokenList :: MTokenList, globalDefinitions_Syn_MTokenList :: (M.Map String [Region]), identifier_Syn_MTokenList :: String, isInModule_Syn_MTokenList :: Bool, mtokenPos_Syn_MTokenList :: Region, scopes_Syn_MTokenList :: ([M.Map String (Bool, Region)]), warnings_Syn_MTokenList :: ([String -> LintMessage])} wrap_MTokenList :: T_MTokenList -> Inh_MTokenList -> Syn_MTokenList wrap_MTokenList sem (Inh_MTokenList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes) = ( let (_lhsOcopy, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOwarnings) = sem _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes in (Syn_MTokenList _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOwarnings) ) sem_MTokenList_Cons :: T_MToken -> T_MTokenList -> T_MTokenList sem_MTokenList_Cons hd_ tl_ = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case (hd_) of (_hdIcopy, _hdImtok, _hdImtokenPos, hd_1) -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOmtokenPos _hdOscopes) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdIscopes, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case (tl_ _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOmtokenPos _tlOscopes) of (_tlIcopy, _tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIwarnings) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_MTokenList_Nil :: T_MTokenList sem_MTokenList_Nil = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsImtokenPos _lhsIscopes -> ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOwarnings) ) ) ) ) ) ) ) ) ) -- MaybeMExpr -------------------------------------------------- -- cata sem_MaybeMExpr :: MaybeMExpr -> T_MaybeMExpr sem_MaybeMExpr (Prelude.Just x) = (sem_MaybeMExpr_Just (sem_MExpr x)) sem_MaybeMExpr Prelude.Nothing = sem_MaybeMExpr_Nothing -- semantic domain type T_MaybeMExpr = (MaybeMExpr, T_MaybeMExpr_1) type T_MaybeMExpr_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> (Maybe MToken) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, (Maybe MToken), Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_MaybeMExpr = Inh_MaybeMExpr {config_Inh_MaybeMExpr :: LintSettings, funcName_Inh_MaybeMExpr :: String, globalDefinitions_Inh_MaybeMExpr :: (M.Map String [Region]), isInModule_Inh_MaybeMExpr :: Bool, isMeta_Inh_MaybeMExpr :: Bool, isNegation_Inh_MaybeMExpr :: Bool, loopLevel_Inh_MaybeMExpr :: Int, mtokenPos_Inh_MaybeMExpr :: Region, scopeLevel_Inh_MaybeMExpr :: Int, scopes_Inh_MaybeMExpr :: ([M.Map String (Bool, Region)]), varBeingDefined_Inh_MaybeMExpr :: (Maybe MToken), variableStyle_Inh_MaybeMExpr :: DeterminedVariableStyle} data Syn_MaybeMExpr = Syn_MaybeMExpr {copy_Syn_MaybeMExpr :: MaybeMExpr, globalDefinitions_Syn_MaybeMExpr :: (M.Map String [Region]), identifier_Syn_MaybeMExpr :: String, isInModule_Syn_MaybeMExpr :: Bool, isSingleVar_Syn_MaybeMExpr :: (Maybe MToken), mtokenPos_Syn_MaybeMExpr :: Region, scopes_Syn_MaybeMExpr :: ([M.Map String (Bool, Region)]), variableStyle_Syn_MaybeMExpr :: DeterminedVariableStyle, warnings_Syn_MaybeMExpr :: ([String -> LintMessage])} wrap_MaybeMExpr :: T_MaybeMExpr -> Inh_MaybeMExpr -> Syn_MaybeMExpr wrap_MaybeMExpr sem (Inh_MaybeMExpr _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvarBeingDefined _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvarBeingDefined _lhsIvariableStyle in (Syn_MaybeMExpr _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisSingleVar _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_MaybeMExpr_Just :: T_MExpr -> T_MaybeMExpr sem_MaybeMExpr_Just just_ = ( case (just_) of (_justIcopy, _justImtokenPos, just_1) -> ( case ( ( Just _justIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MaybeMExpr_Just_1 :: T_MaybeMExpr_1 sem_MaybeMExpr_Just_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIvarBeingDefined ) ) of _justOvarBeingDefined -> ( case ( ( _lhsIscopes ) ) of _justOscopes -> ( case ( ( _lhsIisMeta ) ) of _justOisMeta -> ( case ( ( _lhsIisInModule ) ) of _justOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _justOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _justOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _justOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _justOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _justOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _justOloopLevel -> ( case ( ( _lhsIisNegation ) ) of _justOisNegation -> ( case ( ( _lhsIfuncName ) ) of _justOfuncName -> ( case ( ( False ) ) of _justOtopLevel -> ( case ( ( False ) ) of _justOinParentheses -> ( case (just_1 _justOconfig _justOfuncName _justOglobalDefinitions _justOinParentheses _justOisInModule _justOisMeta _justOisNegation _justOloopLevel _justOmtokenPos _justOscopeLevel _justOscopes _justOtopLevel _justOvarBeingDefined _justOvariableStyle) of (_justIglobalDefinitions, _justIidentifier, _justIisInModule, _justIisSimpleExpression, _justIisSingleVar, _justIscopes, _justIvariableStyle, _justIwarnings) -> ( case ( ( _justIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _justIidentifier ) ) of _lhsOidentifier -> ( case ( ( _justIisInModule ) ) of _lhsOisInModule -> ( case ( ( _justIisSingleVar ) ) of _lhsOisSingleVar -> ( case ( ( _justImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _justIscopes ) ) of _lhsOscopes -> ( case ( ( _justIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _justIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_MaybeMExpr_Just_1 ) ) of (sem_MaybeMExpr_1) -> (_lhsOcopy, sem_MaybeMExpr_1) ) ) ) ) sem_MaybeMExpr_Nothing :: T_MaybeMExpr sem_MaybeMExpr_Nothing = ( case ( ( Nothing ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_MaybeMExpr_Nothing_1 :: T_MaybeMExpr_1 sem_MaybeMExpr_Nothing_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSingleVar, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_MaybeMExpr_Nothing_1 ) ) of (sem_MaybeMExpr_1) -> (_lhsOcopy, sem_MaybeMExpr_1) ) ) ) -- PFExprSuffix ------------------------------------------------ -- cata sem_PFExprSuffix :: PFExprSuffix -> T_PFExprSuffix sem_PFExprSuffix (Call _args) = (sem_PFExprSuffix_Call (sem_Args _args)) sem_PFExprSuffix (MetaCall _fn _args) = (sem_PFExprSuffix_MetaCall (sem_MToken _fn) (sem_Args _args)) sem_PFExprSuffix (ExprIndex _index) = (sem_PFExprSuffix_ExprIndex (sem_MExpr _index)) sem_PFExprSuffix (DotIndex _index) = (sem_PFExprSuffix_DotIndex (sem_MToken _index)) -- semantic domain type T_PFExprSuffix = (PFExprSuffix, T_PFExprSuffix_1) type T_PFExprSuffix_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_PFExprSuffix = Inh_PFExprSuffix {config_Inh_PFExprSuffix :: LintSettings, funcName_Inh_PFExprSuffix :: String, globalDefinitions_Inh_PFExprSuffix :: (M.Map String [Region]), isInModule_Inh_PFExprSuffix :: Bool, isMeta_Inh_PFExprSuffix :: Bool, loopLevel_Inh_PFExprSuffix :: Int, mtokenPos_Inh_PFExprSuffix :: Region, scopeLevel_Inh_PFExprSuffix :: Int, scopes_Inh_PFExprSuffix :: ([M.Map String (Bool, Region)]), variableStyle_Inh_PFExprSuffix :: DeterminedVariableStyle} data Syn_PFExprSuffix = Syn_PFExprSuffix {copy_Syn_PFExprSuffix :: PFExprSuffix, globalDefinitions_Syn_PFExprSuffix :: (M.Map String [Region]), identifier_Syn_PFExprSuffix :: String, isInModule_Syn_PFExprSuffix :: Bool, isSimpleExpression_Syn_PFExprSuffix :: Bool, mtokenPos_Syn_PFExprSuffix :: Region, scopes_Syn_PFExprSuffix :: ([M.Map String (Bool, Region)]), variableStyle_Syn_PFExprSuffix :: DeterminedVariableStyle, warnings_Syn_PFExprSuffix :: ([String -> LintMessage])} wrap_PFExprSuffix :: T_PFExprSuffix -> Inh_PFExprSuffix -> Syn_PFExprSuffix wrap_PFExprSuffix sem (Inh_PFExprSuffix _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_PFExprSuffix _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisSimpleExpression _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_PFExprSuffix_Call :: T_Args -> T_PFExprSuffix sem_PFExprSuffix_Call args_ = ( case (args_) of (_argsIcopy, args_1) -> ( case ( ( Call _argsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_PFExprSuffix_Call_1 :: T_PFExprSuffix_1 sem_PFExprSuffix_Call_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _argsOscopes -> ( case ( ( _lhsIisMeta ) ) of _argsOisMeta -> ( case ( ( _lhsIisInModule ) ) of _argsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _argsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _argsOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _argsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _argsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _argsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _argsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _argsOfuncName -> ( case (args_1 _argsOconfig _argsOfuncName _argsOglobalDefinitions _argsOisInModule _argsOisMeta _argsOloopLevel _argsOmtokenPos _argsOscopeLevel _argsOscopes _argsOvariableStyle) of (_argsIglobalDefinitions, _argsIidentifier, _argsIisInModule, _argsImtokenPos, _argsIscopes, _argsIvariableStyle, _argsIwarnings) -> ( case ( ( _argsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _argsIidentifier ) ) of _lhsOidentifier -> ( case ( ( _argsIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisSimpleExpression -> ( case ( ( _argsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _argsIscopes ) ) of _lhsOscopes -> ( case ( ( _argsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _argsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PFExprSuffix_Call_1 ) ) of (sem_PFExprSuffix_1) -> (_lhsOcopy, sem_PFExprSuffix_1) ) ) ) ) sem_PFExprSuffix_MetaCall :: T_MToken -> T_Args -> T_PFExprSuffix sem_PFExprSuffix_MetaCall fn_ args_ = ( case (args_) of (_argsIcopy, args_1) -> ( case (fn_) of (_fnIcopy, _fnImtok, _fnImtokenPos, fn_1) -> ( case ( ( MetaCall _fnIcopy _argsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_PFExprSuffix_MetaCall_1 :: T_PFExprSuffix_1 sem_PFExprSuffix_MetaCall_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _fnOscopes -> ( case ( ( _lhsImtokenPos ) ) of _fnOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _fnOisMeta -> ( case ( ( _lhsIisInModule ) ) of _fnOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _fnOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _fnOfuncName -> ( case ( ( _lhsIconfig ) ) of _fnOconfig -> ( case (fn_1 _fnOconfig _fnOfuncName _fnOglobalDefinitions _fnOisInModule _fnOisMeta _fnOmtokenPos _fnOscopes) of (_fnIglobalDefinitions, _fnIidentifier, _fnIisInModule, _fnIscopes, _fnIwarnings) -> ( case ( ( _fnIscopes ) ) of _argsOscopes -> ( case ( ( _lhsIisMeta ) ) of _argsOisMeta -> ( case ( ( _fnIisInModule ) ) of _argsOisInModule -> ( case ( ( _fnIglobalDefinitions ) ) of _argsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _argsOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _argsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _argsOscopeLevel -> ( case ( ( _fnImtokenPos ) ) of _argsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _argsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _argsOfuncName -> ( case (args_1 _argsOconfig _argsOfuncName _argsOglobalDefinitions _argsOisInModule _argsOisMeta _argsOloopLevel _argsOmtokenPos _argsOscopeLevel _argsOscopes _argsOvariableStyle) of (_argsIglobalDefinitions, _argsIidentifier, _argsIisInModule, _argsImtokenPos, _argsIscopes, _argsIvariableStyle, _argsIwarnings) -> ( case ( ( _argsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _fnIidentifier _argsIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _argsIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisSimpleExpression -> ( case ( ( _argsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _argsIscopes ) ) of _lhsOscopes -> ( case ( ( _argsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _fnIwarnings ++ _argsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PFExprSuffix_MetaCall_1 ) ) of (sem_PFExprSuffix_1) -> (_lhsOcopy, sem_PFExprSuffix_1) ) ) ) ) ) sem_PFExprSuffix_ExprIndex :: T_MExpr -> T_PFExprSuffix sem_PFExprSuffix_ExprIndex index_ = ( case (index_) of (_indexIcopy, _indexImtokenPos, index_1) -> ( case ( ( ExprIndex _indexIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_PFExprSuffix_ExprIndex_1 :: T_PFExprSuffix_1 sem_PFExprSuffix_ExprIndex_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _indexOscopes -> ( case ( ( _lhsIisMeta ) ) of _indexOisMeta -> ( case ( ( _lhsIisInModule ) ) of _indexOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _indexOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _indexOconfig -> ( case ( ( Nothing ) ) of _indexOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _indexOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _indexOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _indexOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _indexOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _indexOfuncName -> ( case ( ( True ) ) of _indexOtopLevel -> ( case ( ( True ) ) of _indexOinParentheses -> ( case ( ( False ) ) of _indexOisNegation -> ( case (index_1 _indexOconfig _indexOfuncName _indexOglobalDefinitions _indexOinParentheses _indexOisInModule _indexOisMeta _indexOisNegation _indexOloopLevel _indexOmtokenPos _indexOscopeLevel _indexOscopes _indexOtopLevel _indexOvarBeingDefined _indexOvariableStyle) of (_indexIglobalDefinitions, _indexIidentifier, _indexIisInModule, _indexIisSimpleExpression, _indexIisSingleVar, _indexIscopes, _indexIvariableStyle, _indexIwarnings) -> ( case ( ( _indexIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _indexIidentifier ) ) of _lhsOidentifier -> ( case ( ( _indexIisInModule ) ) of _lhsOisInModule -> ( case ( ( _indexIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( _indexImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _indexIscopes ) ) of _lhsOscopes -> ( case ( ( _indexIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _indexIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PFExprSuffix_ExprIndex_1 ) ) of (sem_PFExprSuffix_1) -> (_lhsOcopy, sem_PFExprSuffix_1) ) ) ) ) sem_PFExprSuffix_DotIndex :: T_MToken -> T_PFExprSuffix sem_PFExprSuffix_DotIndex index_ = ( case (index_) of (_indexIcopy, _indexImtok, _indexImtokenPos, index_1) -> ( case ( ( DotIndex _indexIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_PFExprSuffix_DotIndex_1 :: T_PFExprSuffix_1 sem_PFExprSuffix_DotIndex_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _indexOglobalDefinitions -> ( case ( ( _lhsIscopes ) ) of _indexOscopes -> ( case ( ( _lhsImtokenPos ) ) of _indexOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _indexOisMeta -> ( case ( ( _lhsIisInModule ) ) of _indexOisInModule -> ( case ( ( _lhsIfuncName ) ) of _indexOfuncName -> ( case ( ( _lhsIconfig ) ) of _indexOconfig -> ( case (index_1 _indexOconfig _indexOfuncName _indexOglobalDefinitions _indexOisInModule _indexOisMeta _indexOmtokenPos _indexOscopes) of (_indexIglobalDefinitions, _indexIidentifier, _indexIisInModule, _indexIscopes, _indexIwarnings) -> ( case ( ( _indexIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _indexIidentifier ) ) of _lhsOidentifier -> ( case ( ( _indexIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisSimpleExpression -> ( case ( ( _indexImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _indexIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _indexIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PFExprSuffix_DotIndex_1 ) ) of (sem_PFExprSuffix_1) -> (_lhsOcopy, sem_PFExprSuffix_1) ) ) ) ) -- PrefixExp --------------------------------------------------- -- cata sem_PrefixExp :: PrefixExp -> T_PrefixExp sem_PrefixExp (PFVar _name _suffixes) = (sem_PrefixExp_PFVar (sem_MToken _name) (sem_ExprSuffixList _suffixes)) sem_PrefixExp (ExprVar _expr _suffixes) = (sem_PrefixExp_ExprVar (sem_MExpr _expr) (sem_ExprSuffixList _suffixes)) -- semantic domain type T_PrefixExp = (PrefixExp, Bool, Region, (Maybe MToken), T_PrefixExp_1) type T_PrefixExp_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Bool -> Int -> Region -> Bool -> Int -> ([M.Map String (Bool, Region)]) -> Bool -> (Maybe MToken) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, (Maybe MToken), ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_PrefixExp = Inh_PrefixExp {config_Inh_PrefixExp :: LintSettings, funcName_Inh_PrefixExp :: String, globalDefinitions_Inh_PrefixExp :: (M.Map String [Region]), inParentheses_Inh_PrefixExp :: Bool, isInModule_Inh_PrefixExp :: Bool, isMeta_Inh_PrefixExp :: Bool, isNegation_Inh_PrefixExp :: Bool, loopLevel_Inh_PrefixExp :: Int, mtokenPos_Inh_PrefixExp :: Region, registerVarUse_Inh_PrefixExp :: Bool, scopeLevel_Inh_PrefixExp :: Int, scopes_Inh_PrefixExp :: ([M.Map String (Bool, Region)]), topLevel_Inh_PrefixExp :: Bool, varBeingDefined_Inh_PrefixExp :: (Maybe MToken), variableStyle_Inh_PrefixExp :: DeterminedVariableStyle} data Syn_PrefixExp = Syn_PrefixExp {copy_Syn_PrefixExp :: PrefixExp, globalDefinitions_Syn_PrefixExp :: (M.Map String [Region]), hasSuffixes_Syn_PrefixExp :: Bool, identifier_Syn_PrefixExp :: String, isInModule_Syn_PrefixExp :: Bool, isSimpleExpression_Syn_PrefixExp :: Bool, isSingleVar_Syn_PrefixExp :: (Maybe MToken), mtokenPos_Syn_PrefixExp :: Region, scopes_Syn_PrefixExp :: ([M.Map String (Bool, Region)]), varName_Syn_PrefixExp :: (Maybe MToken), variableStyle_Syn_PrefixExp :: DeterminedVariableStyle, warnings_Syn_PrefixExp :: ([String -> LintMessage])} wrap_PrefixExp :: T_PrefixExp -> Inh_PrefixExp -> Syn_PrefixExp wrap_PrefixExp sem (Inh_PrefixExp _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIregisterVarUse _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle) = ( let (_lhsOcopy, _lhsOhasSuffixes, _lhsOmtokenPos, _lhsOvarName, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIregisterVarUse _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle in (Syn_PrefixExp _lhsOcopy _lhsOglobalDefinitions _lhsOhasSuffixes _lhsOidentifier _lhsOisInModule _lhsOisSimpleExpression _lhsOisSingleVar _lhsOmtokenPos _lhsOscopes _lhsOvarName _lhsOvariableStyle _lhsOwarnings) ) sem_PrefixExp_PFVar :: T_MToken -> T_ExprSuffixList -> T_PrefixExp sem_PrefixExp_PFVar name_ suffixes_ = ( case (suffixes_) of (_suffixesIcopy, suffixes_1) -> ( case (name_) of (_nameIcopy, _nameImtok, _nameImtokenPos, name_1) -> ( case ( ( PFVar _nameIcopy _suffixesIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( not . null $ _suffixesIcopy ) ) of _lhsOhasSuffixes -> ( case ( ( _nameImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( Just _nameIcopy ) ) of _varName -> ( case ( ( _varName ) ) of _lhsOvarName -> ( case ( ( let sem_PrefixExp_PFVar_1 :: T_PrefixExp_1 sem_PrefixExp_PFVar_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIregisterVarUse _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( if isJust _lhsIvarBeingDefined && _lhsIvarBeingDefined == _varName then case _lhsIscopes of deepestScope : otherScopes -> deepestScope : registerVariable otherScopes _nameImtokenPos (show _nameImtok) _lhsIregisterVarUse noScopes -> noScopes else registerVariable _lhsIscopes _nameImtokenPos (show _nameImtok) _lhsIregisterVarUse ) ) of _foundVars -> ( case ( ( _foundVars ) ) of _nameOscopes -> ( case ( ( _lhsImtokenPos ) ) of _nameOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _nameOisMeta -> ( case ( ( _lhsIisInModule ) ) of _nameOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _nameOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _nameOfuncName -> ( case ( ( _lhsIconfig ) ) of _nameOconfig -> ( case (name_1 _nameOconfig _nameOfuncName _nameOglobalDefinitions _nameOisInModule _nameOisMeta _nameOmtokenPos _nameOscopes) of (_nameIglobalDefinitions, _nameIidentifier, _nameIisInModule, _nameIscopes, _nameIwarnings) -> ( case ( ( _nameIscopes ) ) of _suffixesOscopes -> ( case ( ( _lhsIisMeta ) ) of _suffixesOisMeta -> ( case ( ( _nameIisInModule ) ) of _suffixesOisInModule -> ( case ( ( _nameIglobalDefinitions ) ) of _suffixesOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _suffixesOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _suffixesOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _suffixesOscopeLevel -> ( case ( ( _nameImtokenPos ) ) of _suffixesOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _suffixesOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _suffixesOfuncName -> ( case (suffixes_1 _suffixesOconfig _suffixesOfuncName _suffixesOglobalDefinitions _suffixesOisInModule _suffixesOisMeta _suffixesOloopLevel _suffixesOmtokenPos _suffixesOscopeLevel _suffixesOscopes _suffixesOvariableStyle) of (_suffixesIglobalDefinitions, _suffixesIidentifier, _suffixesIisInModule, _suffixesIisSimpleExpression, _suffixesImtokenPos, _suffixesIscopes, _suffixesIvariableStyle, _suffixesIwarnings) -> ( case ( ( _suffixesIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _nameIidentifier _suffixesIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _suffixesIisInModule ) ) of _lhsOisInModule -> ( case ( ( _suffixesIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( if null _suffixesIcopy then _varName else Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _suffixesIscopes ) ) of _lhsOscopes -> ( case ( ( _suffixesIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _nameIwarnings ++ _suffixesIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( tokenLabel _nameIcopy ) ) of _name -> ( case ( ( if not (lint_beginnerMistakes _lhsIconfig) || _lhsIisMeta || _name /= "self" then id else (:) $ warn _nameImtokenPos SelfInNonMeta ) ) of _warnings_augmented_f3 -> ( case ( ( if not (lint_beginnerMistakes _lhsIconfig) || not _lhsIisMeta || _name /= "self" || _lhsIfuncName /= "ENT" || _suffixesIidentifier /= "Entity" then id else (:) $ warn _nameImtokenPos SelfEntity ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_beginnerMistakes _lhsIconfig) || not _lhsIisMeta || _name /= "self" || _lhsIfuncName /= "SWEP" || _suffixesIidentifier /= "Weapon" then id else (:) $ warn _nameImtokenPos SelfWeapon ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2, _warnings_augmented_f3] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PrefixExp_PFVar_1 ) ) of (sem_PrefixExp_1) -> (_lhsOcopy, _lhsOhasSuffixes, _lhsOmtokenPos, _lhsOvarName, sem_PrefixExp_1) ) ) ) ) ) ) ) ) ) sem_PrefixExp_ExprVar :: T_MExpr -> T_ExprSuffixList -> T_PrefixExp sem_PrefixExp_ExprVar expr_ suffixes_ = ( case (suffixes_) of (_suffixesIcopy, suffixes_1) -> ( case (expr_) of (_exprIcopy, _exprImtokenPos, expr_1) -> ( case ( ( ExprVar _exprIcopy _suffixesIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( False ) ) of _lhsOhasSuffixes -> ( case ( ( _exprImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( Nothing ) ) of _lhsOvarName -> ( case ( ( let sem_PrefixExp_ExprVar_1 :: T_PrefixExp_1 sem_PrefixExp_ExprVar_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIinParentheses _lhsIisInModule _lhsIisMeta _lhsIisNegation _lhsIloopLevel _lhsImtokenPos _lhsIregisterVarUse _lhsIscopeLevel _lhsIscopes _lhsItopLevel _lhsIvarBeingDefined _lhsIvariableStyle -> ( case ( ( _lhsIvarBeingDefined ) ) of _exprOvarBeingDefined -> ( case ( ( _lhsIscopes ) ) of _exprOscopes -> ( case ( ( _lhsIisMeta ) ) of _exprOisMeta -> ( case ( ( _lhsIconfig ) ) of _exprOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _exprOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _exprOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _exprOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _exprOloopLevel -> ( case ( ( _lhsIisNegation ) ) of _exprOisNegation -> ( case ( ( _lhsIisInModule ) ) of _exprOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _exprOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _exprOfuncName -> ( case ( ( True ) ) of _exprOtopLevel -> ( case ( ( True ) ) of _exprOinParentheses -> ( case (expr_1 _exprOconfig _exprOfuncName _exprOglobalDefinitions _exprOinParentheses _exprOisInModule _exprOisMeta _exprOisNegation _exprOloopLevel _exprOmtokenPos _exprOscopeLevel _exprOscopes _exprOtopLevel _exprOvarBeingDefined _exprOvariableStyle) of (_exprIglobalDefinitions, _exprIidentifier, _exprIisInModule, _exprIisSimpleExpression, _exprIisSingleVar, _exprIscopes, _exprIvariableStyle, _exprIwarnings) -> ( case ( ( _exprIscopes ) ) of _suffixesOscopes -> ( case ( ( _lhsIisMeta ) ) of _suffixesOisMeta -> ( case ( ( _exprIisInModule ) ) of _suffixesOisInModule -> ( case ( ( _exprIglobalDefinitions ) ) of _suffixesOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _suffixesOconfig -> ( case ( ( _exprIvariableStyle ) ) of _suffixesOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _suffixesOscopeLevel -> ( case ( ( _exprImtokenPos ) ) of _suffixesOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _suffixesOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _suffixesOfuncName -> ( case (suffixes_1 _suffixesOconfig _suffixesOfuncName _suffixesOglobalDefinitions _suffixesOisInModule _suffixesOisMeta _suffixesOloopLevel _suffixesOmtokenPos _suffixesOscopeLevel _suffixesOscopes _suffixesOvariableStyle) of (_suffixesIglobalDefinitions, _suffixesIidentifier, _suffixesIisInModule, _suffixesIisSimpleExpression, _suffixesImtokenPos, _suffixesIscopes, _suffixesIvariableStyle, _suffixesIwarnings) -> ( case ( ( _suffixesIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _exprIidentifier _suffixesIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _suffixesIisInModule ) ) of _lhsOisInModule -> ( case ( ( _exprIisSimpleExpression && _suffixesIisSimpleExpression ) ) of _lhsOisSimpleExpression -> ( case ( ( Nothing ) ) of _lhsOisSingleVar -> ( case ( ( _suffixesIscopes ) ) of _lhsOscopes -> ( case ( ( _suffixesIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _exprIwarnings ++ _suffixesIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if lint_redundantParentheses _lhsIconfig && null _suffixesIcopy && (_lhsIinParentheses || (not _lhsItopLevel && _exprIisSimpleExpression)) then (:) $ warn _lhsImtokenPos UnnecessaryParentheses else id ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisSimpleExpression, _lhsOisSingleVar, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_PrefixExp_ExprVar_1 ) ) of (sem_PrefixExp_1) -> (_lhsOcopy, _lhsOhasSuffixes, _lhsOmtokenPos, _lhsOvarName, sem_PrefixExp_1) ) ) ) ) ) ) ) ) -- Region ------------------------------------------------------ -- cata sem_Region :: Region -> T_Region sem_Region (Region _start _end) = (sem_Region_Region _start _end) -- semantic domain type T_Region = (Region, String, ([String -> LintMessage])) data Inh_Region = Inh_Region {} data Syn_Region = Syn_Region {copy_Syn_Region :: Region, identifier_Syn_Region :: String, warnings_Syn_Region :: ([String -> LintMessage])} wrap_Region :: T_Region -> Inh_Region -> Syn_Region wrap_Region sem (Inh_Region) = ( let (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) = sem in (Syn_Region _lhsOcopy _lhsOidentifier _lhsOwarnings) ) sem_Region_Region :: LineColPos -> LineColPos -> T_Region sem_Region_Region start_ end_ = ( case ( ( Region start_ end_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) -- Stat -------------------------------------------------------- -- cata sem_Stat :: Stat -> T_Stat sem_Stat (Def _vars) = (sem_Stat_Def (sem_VarsList _vars)) sem_Stat (LocDef _vars) = (sem_Stat_LocDef (sem_VarsList _vars)) sem_Stat (AFuncCall _fn) = (sem_Stat_AFuncCall (sem_PrefixExp _fn)) sem_Stat (ALabel _lbl) = (sem_Stat_ALabel (sem_MToken _lbl)) sem_Stat (ABreak) = (sem_Stat_ABreak) sem_Stat (AContinue) = (sem_Stat_AContinue) sem_Stat (AGoto _lbl) = (sem_Stat_AGoto (sem_MToken _lbl)) sem_Stat (ADo _body) = (sem_Stat_ADo (sem_Block _body)) sem_Stat (AWhile _cond _body) = (sem_Stat_AWhile (sem_MExpr _cond) (sem_Block _body)) sem_Stat (ARepeat _body _cond) = (sem_Stat_ARepeat (sem_Block _body) (sem_MExpr _cond)) sem_Stat (AIf _cond _body _elifs _els) = (sem_Stat_AIf (sem_MExpr _cond) (sem_Block _body) (sem_ElseIfList _elifs) (sem_Else _els)) sem_Stat (ANFor _var _val _to _step _body) = (sem_Stat_ANFor (sem_MToken _var) (sem_MExpr _val) (sem_MExpr _to) (sem_MExpr _step) (sem_Block _body)) sem_Stat (AGFor _vars _vals _body) = (sem_Stat_AGFor _vars (sem_MExprList _vals) (sem_Block _body)) sem_Stat (AFunc _name _args _body) = (sem_Stat_AFunc (sem_FuncName _name) _args (sem_Block _body)) sem_Stat (ALocFunc _name _args _body) = (sem_Stat_ALocFunc (sem_FuncName _name) _args (sem_Block _body)) -- semantic domain type T_Stat = (Stat, T_Stat_1) type T_Stat_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_Stat = Inh_Stat {config_Inh_Stat :: LintSettings, funcName_Inh_Stat :: String, globalDefinitions_Inh_Stat :: (M.Map String [Region]), isInModule_Inh_Stat :: Bool, isMeta_Inh_Stat :: Bool, loopLevel_Inh_Stat :: Int, mtokenPos_Inh_Stat :: Region, scopeLevel_Inh_Stat :: Int, scopes_Inh_Stat :: ([M.Map String (Bool, Region)]), variableStyle_Inh_Stat :: DeterminedVariableStyle} data Syn_Stat = Syn_Stat {copy_Syn_Stat :: Stat, globalDefinitions_Syn_Stat :: (M.Map String [Region]), identifier_Syn_Stat :: String, isIfStatement_Syn_Stat :: Bool, isInModule_Syn_Stat :: Bool, mtokenPos_Syn_Stat :: Region, scopes_Syn_Stat :: ([M.Map String (Bool, Region)]), variableStyle_Syn_Stat :: DeterminedVariableStyle, warnings_Syn_Stat :: ([String -> LintMessage])} wrap_Stat :: T_Stat -> Inh_Stat -> Syn_Stat wrap_Stat sem (Inh_Stat _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_Stat _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisIfStatement _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_Stat_Def :: T_VarsList -> T_Stat sem_Stat_Def vars_ = ( case (vars_) of (_varsIcopy, vars_1) -> ( case ( ( Def _varsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_Def_1 :: T_Stat_1 sem_Stat_Def_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _varsOscopes -> ( case ( ( _lhsIisMeta ) ) of _varsOisMeta -> ( case ( ( _lhsIisInModule ) ) of _varsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _varsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _varsOconfig -> ( case ( ( False ) ) of _varsOlocalDefinition -> ( case ( ( _lhsIvariableStyle ) ) of _varsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _varsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _varsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _varsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _varsOfuncName -> ( case (vars_1 _varsOconfig _varsOfuncName _varsOglobalDefinitions _varsOisInModule _varsOisMeta _varsOlocalDefinition _varsOloopLevel _varsOmtokenPos _varsOscopeLevel _varsOscopes _varsOvariableStyle) of (_varsIglobalDefinitions, _varsIidentifier, _varsIisInModule, _varsImtokenPos, _varsIscopes, _varsIvariableStyle, _varsIwarnings) -> ( case ( ( _varsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _varsIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _varsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _varsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _varsIscopes ) ) of _lhsOscopes -> ( case ( ( _varsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _varsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_Def_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_LocDef :: T_VarsList -> T_Stat sem_Stat_LocDef vars_ = ( case (vars_) of (_varsIcopy, vars_1) -> ( case ( ( LocDef _varsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_LocDef_1 :: T_Stat_1 sem_Stat_LocDef_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _varsOscopes -> ( case ( ( _lhsIisMeta ) ) of _varsOisMeta -> ( case ( ( _lhsIisInModule ) ) of _varsOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _varsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _varsOconfig -> ( case ( ( True ) ) of _varsOlocalDefinition -> ( case ( ( _lhsIvariableStyle ) ) of _varsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _varsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _varsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _varsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _varsOfuncName -> ( case (vars_1 _varsOconfig _varsOfuncName _varsOglobalDefinitions _varsOisInModule _varsOisMeta _varsOlocalDefinition _varsOloopLevel _varsOmtokenPos _varsOscopeLevel _varsOscopes _varsOvariableStyle) of (_varsIglobalDefinitions, _varsIidentifier, _varsIisInModule, _varsImtokenPos, _varsIscopes, _varsIvariableStyle, _varsIwarnings) -> ( case ( ( _varsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _varsIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _varsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _varsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _varsIscopes ) ) of _lhsOscopes -> ( case ( ( _varsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _varsIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_LocDef_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_AFuncCall :: T_PrefixExp -> T_Stat sem_Stat_AFuncCall fn_ = ( case (fn_) of (_fnIcopy, _fnIhasSuffixes, _fnImtokenPos, _fnIvarName, fn_1) -> ( case ( ( AFuncCall _fnIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AFuncCall_1 :: T_Stat_1 sem_Stat_AFuncCall_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _fnOscopes -> ( case ( ( _lhsIisMeta ) ) of _fnOisMeta -> ( case ( ( _lhsIisInModule ) ) of _fnOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _fnOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _fnOconfig -> ( case ( ( Nothing ) ) of _fnOvarBeingDefined -> ( case ( ( True ) ) of _fnOregisterVarUse -> ( case ( ( _lhsIvariableStyle ) ) of _fnOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _fnOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _fnOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _fnOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _fnOfuncName -> ( case ( ( True ) ) of _fnOtopLevel -> ( case ( ( False ) ) of _fnOinParentheses -> ( case ( ( False ) ) of _fnOisNegation -> ( case (fn_1 _fnOconfig _fnOfuncName _fnOglobalDefinitions _fnOinParentheses _fnOisInModule _fnOisMeta _fnOisNegation _fnOloopLevel _fnOmtokenPos _fnOregisterVarUse _fnOscopeLevel _fnOscopes _fnOtopLevel _fnOvarBeingDefined _fnOvariableStyle) of (_fnIglobalDefinitions, _fnIidentifier, _fnIisInModule, _fnIisSimpleExpression, _fnIisSingleVar, _fnIscopes, _fnIvariableStyle, _fnIwarnings) -> ( case ( ( _fnIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _fnIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( (tokenLabel <$> _fnIvarName) == Just "module" ) ) of _isModuleCall -> ( case ( ( _lhsIisInModule || _isModuleCall ) ) of _lhsOisInModule -> ( case ( ( _fnImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _fnIscopes ) ) of _lhsOscopes -> ( case ( ( _fnIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _fnIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AFuncCall_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_ALabel :: T_MToken -> T_Stat sem_Stat_ALabel lbl_ = ( case (lbl_) of (_lblIcopy, _lblImtok, _lblImtokenPos, lbl_1) -> ( case ( ( ALabel _lblIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ALabel_1 :: T_Stat_1 sem_Stat_ALabel_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lblOglobalDefinitions -> ( case ( ( _lhsIscopes ) ) of _lblOscopes -> ( case ( ( _lhsImtokenPos ) ) of _lblOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _lblOisMeta -> ( case ( ( _lhsIisInModule ) ) of _lblOisInModule -> ( case ( ( _lhsIfuncName ) ) of _lblOfuncName -> ( case ( ( _lhsIconfig ) ) of _lblOconfig -> ( case (lbl_1 _lblOconfig _lblOfuncName _lblOglobalDefinitions _lblOisInModule _lblOisMeta _lblOmtokenPos _lblOscopes) of (_lblIglobalDefinitions, _lblIidentifier, _lblIisInModule, _lblIscopes, _lblIwarnings) -> ( case ( ( _lblIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _lblIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _lblIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lblImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lblIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _lblIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_ALabel_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_ABreak :: T_Stat sem_Stat_ABreak = ( case ( ( ABreak ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ABreak_1 :: T_Stat_1 sem_Stat_ABreak_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_Stat_ABreak_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) sem_Stat_AContinue :: T_Stat sem_Stat_AContinue = ( case ( ( AContinue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AContinue_1 :: T_Stat_1 sem_Stat_AContinue_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_Stat_AContinue_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) sem_Stat_AGoto :: T_MToken -> T_Stat sem_Stat_AGoto lbl_ = ( case (lbl_) of (_lblIcopy, _lblImtok, _lblImtokenPos, lbl_1) -> ( case ( ( AGoto _lblIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AGoto_1 :: T_Stat_1 sem_Stat_AGoto_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lblOglobalDefinitions -> ( case ( ( _lhsIscopes ) ) of _lblOscopes -> ( case ( ( _lhsImtokenPos ) ) of _lblOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _lblOisMeta -> ( case ( ( _lhsIisInModule ) ) of _lblOisInModule -> ( case ( ( _lhsIfuncName ) ) of _lblOfuncName -> ( case ( ( _lhsIconfig ) ) of _lblOconfig -> ( case (lbl_1 _lblOconfig _lblOfuncName _lblOglobalDefinitions _lblOisInModule _lblOisMeta _lblOmtokenPos _lblOscopes) of (_lblIglobalDefinitions, _lblIidentifier, _lblIisInModule, _lblIscopes, _lblIwarnings) -> ( case ( ( _lblIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _lblIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _lblIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lblImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lblIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _lblIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_gotos _lhsIconfig) || _lhsIloopLevel >= 2 then id else (:) $ warn _lblImtokenPos AvoidGoto ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AGoto_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_ADo :: T_Block -> T_Stat sem_Stat_ADo body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case ( ( ADo _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ADo_1 :: T_Stat_1 sem_Stat_ADo_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _bodyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( M.empty : _lhsIscopes ) ) of _bodyOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( _bodyIidentifier ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _lhsImtokenPos EmptyDoBlock ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_ADo_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) sem_Stat_AWhile :: T_MExpr -> T_Block -> T_Stat sem_Stat_AWhile cond_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (cond_) of (_condIcopy, _condImtokenPos, cond_1) -> ( case ( ( AWhile _condIcopy _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AWhile_1 :: T_Stat_1 sem_Stat_AWhile_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _condOisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _condOvariableStyle -> ( case ( ( _lhsIscopes ) ) of _condOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _condOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _condOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _condOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _condOisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _condOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _condOfuncName -> ( case ( ( _lhsIconfig ) ) of _condOconfig -> ( case ( ( Nothing ) ) of _condOvarBeingDefined -> ( case ( ( True ) ) of _condOtopLevel -> ( case ( ( False ) ) of _condOinParentheses -> ( case ( ( False ) ) of _condOisNegation -> ( case (cond_1 _condOconfig _condOfuncName _condOglobalDefinitions _condOinParentheses _condOisInModule _condOisMeta _condOisNegation _condOloopLevel _condOmtokenPos _condOscopeLevel _condOscopes _condOtopLevel _condOvarBeingDefined _condOvariableStyle) of (_condIglobalDefinitions, _condIidentifier, _condIisInModule, _condIisSimpleExpression, _condIisSingleVar, _condIscopes, _condIvariableStyle, _condIwarnings) -> ( case ( ( _condIisInModule ) ) of _bodyOisInModule -> ( case ( ( _condIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( M.empty : _condIscopes ) ) of _bodyOscopes -> ( case ( ( _condIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _condImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case ( ( _lhsIloopLevel + 1 ) ) of _bodyOloopLevel -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _condIidentifier _bodyIidentifier) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _condIwarnings ++ _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _lhsImtokenPos EmptyWhileLoop ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AWhile_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) sem_Stat_ARepeat :: T_Block -> T_MExpr -> T_Stat sem_Stat_ARepeat body_ cond_ = ( case (cond_) of (_condIcopy, _condImtokenPos, cond_1) -> ( case (body_) of (_bodyIcopy, body_1) -> ( case ( ( ARepeat _bodyIcopy _condIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ARepeat_1 :: T_Stat_1 sem_Stat_ARepeat_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( M.empty : _lhsIscopes ) ) of _bodyOscopes -> ( case ( ( True ) ) of _bodyOisRepeat -> ( case ( ( _lhsIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIisInModule ) ) of _bodyOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( _lhsIloopLevel + 1 ) ) of _bodyOloopLevel -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIscopes ) ) of _condOscopes -> ( case ( ( _lhsIisMeta ) ) of _condOisMeta -> ( case ( ( _bodyIisInModule ) ) of _condOisInModule -> ( case ( ( _bodyIglobalDefinitions ) ) of _condOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _condOconfig -> ( case ( ( Nothing ) ) of _condOvarBeingDefined -> ( case ( ( _bodyIvariableStyle ) ) of _condOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _condOscopeLevel -> ( case ( ( _bodyImtokenPos ) ) of _condOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _condOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _condOfuncName -> ( case ( ( True ) ) of _condOtopLevel -> ( case ( ( False ) ) of _condOinParentheses -> ( case ( ( False ) ) of _condOisNegation -> ( case (cond_1 _condOconfig _condOfuncName _condOglobalDefinitions _condOinParentheses _condOisInModule _condOisMeta _condOisNegation _condOloopLevel _condOmtokenPos _condOscopeLevel _condOscopes _condOtopLevel _condOvarBeingDefined _condOvariableStyle) of (_condIglobalDefinitions, _condIidentifier, _condIisInModule, _condIisSimpleExpression, _condIisSingleVar, _condIscopes, _condIvariableStyle, _condIwarnings) -> ( case ( ( _condIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _bodyIidentifier _condIidentifier) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _condIisInModule ) ) of _lhsOisInModule -> ( case ( ( _condImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( tail _condIscopes ) ) of _lhsOscopes -> ( case ( ( _condIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _bodyIwarnings ++ _condIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _lhsImtokenPos EmptyRepeat ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_ARepeat_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) sem_Stat_AIf :: T_MExpr -> T_Block -> T_ElseIfList -> T_Else -> T_Stat sem_Stat_AIf cond_ body_ elifs_ els_ = ( case (els_) of (_elsIcopy, els_1) -> ( case (elifs_) of (_elifsIcopy, elifs_1) -> ( case (body_) of (_bodyIcopy, body_1) -> ( case (cond_) of (_condIcopy, _condImtokenPos, cond_1) -> ( case ( ( AIf _condIcopy _bodyIcopy _elifsIcopy _elsIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AIf_1 :: T_Stat_1 sem_Stat_AIf_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( _lhsIscopes ) ) of _condOscopes -> ( case ( ( _lhsIisMeta ) ) of _condOisMeta -> ( case ( ( _lhsIconfig ) ) of _condOconfig -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case ( ( Nothing ) ) of _condOvarBeingDefined -> ( case ( ( _lhsIvariableStyle ) ) of _condOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _condOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _condOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _condOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _condOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _condOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _condOfuncName -> ( case ( ( True ) ) of _condOtopLevel -> ( case ( ( False ) ) of _condOinParentheses -> ( case ( ( False ) ) of _condOisNegation -> ( case (cond_1 _condOconfig _condOfuncName _condOglobalDefinitions _condOinParentheses _condOisInModule _condOisMeta _condOisNegation _condOloopLevel _condOmtokenPos _condOscopeLevel _condOscopes _condOtopLevel _condOvarBeingDefined _condOvariableStyle) of (_condIglobalDefinitions, _condIidentifier, _condIisInModule, _condIisSimpleExpression, _condIisSingleVar, _condIscopes, _condIvariableStyle, _condIwarnings) -> ( case ( ( M.empty : _condIscopes ) ) of _bodyOscopes -> ( case ( ( _condIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _condImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _condIisInModule ) ) of _bodyOisInModule -> ( case ( ( _condIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIscopes ) ) of _elifsOscopes -> ( case ( ( _lhsIisMeta ) ) of _elifsOisMeta -> ( case ( ( _lhsIconfig ) ) of _elifsOconfig -> ( case ( ( _bodyIvariableStyle ) ) of _elifsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _elifsOscopeLevel -> ( case ( ( _lhsIloopLevel ) ) of _elifsOloopLevel -> ( case ( ( _bodyIisInModule ) ) of _elifsOisInModule -> ( case ( ( _bodyIglobalDefinitions ) ) of _elifsOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _elifsOfuncName -> ( case ( ( _lhsImtokenPos ) ) of _elifsOmtokenPos -> ( case (elifs_1 _elifsOconfig _elifsOfuncName _elifsOglobalDefinitions _elifsOisInModule _elifsOisMeta _elifsOloopLevel _elifsOmtokenPos _elifsOscopeLevel _elifsOscopes _elifsOvariableStyle) of (_elifsIelseExists, _elifsIglobalDefinitions, _elifsIidentifier, _elifsIisInModule, _elifsImtokenPos, _elifsIscopes, _elifsIvariableStyle, _elifsIwarnings) -> ( case ( ( _elifsIscopes ) ) of _elsOscopes -> ( case ( ( _lhsIisMeta ) ) of _elsOisMeta -> ( case ( ( _elifsIisInModule ) ) of _elsOisInModule -> ( case ( ( _elifsIglobalDefinitions ) ) of _elsOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _elsOconfig -> ( case ( ( _elifsIvariableStyle ) ) of _elsOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _elsOscopeLevel -> ( case ( ( _lhsIloopLevel ) ) of _elsOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _elsOfuncName -> ( case ( ( _lhsImtokenPos ) ) of _elsOmtokenPos -> ( case (els_1 _elsOconfig _elsOfuncName _elsOglobalDefinitions _elsOisInModule _elsOisMeta _elsOloopLevel _elsOmtokenPos _elsOscopeLevel _elsOscopes _elsOvariableStyle) of (_elsIelseExists, _elsIglobalDefinitions, _elsIidentifier, _elsIisInModule, _elsImtokenPos, _elsIscopes, _elsIvariableStyle, _elsIwarnings) -> ( case ( ( _elsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _condIidentifier (const _bodyIidentifier (const _elifsIidentifier _elsIidentifier))) ) ) of _lhsOidentifier -> ( case ( ( not _elifsIelseExists && not _elsIelseExists ) ) of _lhsOisIfStatement -> ( case ( ( _elsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _elsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _elsIscopes ) ) of _lhsOscopes -> ( case ( ( _elsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _condIwarnings ++ _bodyIwarnings ++ _elifsIwarnings ++ _elsIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( Region (rgStart _lhsImtokenPos) (customAdvanceToken (rgStart _lhsImtokenPos) If) ) ) of _keywordPos -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _keywordPos EmptyIf ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_redundantIfStatements _lhsIconfig) || _bodyIstatementCount /= 1 || not _bodyIisIfStatement || _elifsIelseExists || _elsIelseExists then id else (:) $ warn _bodyImtokenPos DoubleIf ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AIf_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) ) ) sem_Stat_ANFor :: T_MToken -> T_MExpr -> T_MExpr -> T_MExpr -> T_Block -> T_Stat sem_Stat_ANFor var_ val_ to_ step_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (step_) of (_stepIcopy, _stepImtokenPos, step_1) -> ( case (to_) of (_toIcopy, _toImtokenPos, to_1) -> ( case (val_) of (_valIcopy, _valImtokenPos, val_1) -> ( case (var_) of (_varIcopy, _varImtok, _varImtokenPos, var_1) -> ( case ( ( ANFor _varIcopy _valIcopy _toIcopy _stepIcopy _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ANFor_1 :: T_Stat_1 sem_Stat_ANFor_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _varOisInModule -> ( case ( ( _lhsIscopes ) ) of _varOscopes -> ( case ( ( _lhsImtokenPos ) ) of _varOmtokenPos -> ( case ( ( _lhsIisMeta ) ) of _varOisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _varOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _varOfuncName -> ( case ( ( _lhsIconfig ) ) of _varOconfig -> ( case (var_1 _varOconfig _varOfuncName _varOglobalDefinitions _varOisInModule _varOisMeta _varOmtokenPos _varOscopes) of (_varIglobalDefinitions, _varIidentifier, _varIisInModule, _varIscopes, _varIwarnings) -> ( case ( ( _varIisInModule ) ) of _valOisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _valOvariableStyle -> ( case ( ( _varIscopes ) ) of _valOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _valOscopeLevel -> ( case ( ( _varImtokenPos ) ) of _valOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _valOisMeta -> ( case ( ( _varIglobalDefinitions ) ) of _valOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _valOfuncName -> ( case ( ( _lhsIconfig ) ) of _valOconfig -> ( case ( ( Nothing ) ) of _valOvarBeingDefined -> ( case ( ( True ) ) of _valOtopLevel -> ( case ( ( False ) ) of _valOinParentheses -> ( case ( ( False ) ) of _valOisNegation -> ( case (val_1 _valOconfig _valOfuncName _valOglobalDefinitions _valOinParentheses _valOisInModule _valOisMeta _valOisNegation _valOloopLevel _valOmtokenPos _valOscopeLevel _valOscopes _valOtopLevel _valOvarBeingDefined _valOvariableStyle) of (_valIglobalDefinitions, _valIidentifier, _valIisInModule, _valIisSimpleExpression, _valIisSingleVar, _valIscopes, _valIvariableStyle, _valIwarnings) -> ( case ( ( _valIisInModule ) ) of _toOisInModule -> ( case ( ( _valIvariableStyle ) ) of _toOvariableStyle -> ( case ( ( _valIscopes ) ) of _toOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _toOscopeLevel -> ( case ( ( _valImtokenPos ) ) of _toOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _toOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _toOisMeta -> ( case ( ( _valIglobalDefinitions ) ) of _toOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _toOfuncName -> ( case ( ( _lhsIconfig ) ) of _toOconfig -> ( case ( ( Nothing ) ) of _toOvarBeingDefined -> ( case ( ( True ) ) of _toOtopLevel -> ( case ( ( False ) ) of _toOinParentheses -> ( case ( ( False ) ) of _toOisNegation -> ( case (to_1 _toOconfig _toOfuncName _toOglobalDefinitions _toOinParentheses _toOisInModule _toOisMeta _toOisNegation _toOloopLevel _toOmtokenPos _toOscopeLevel _toOscopes _toOtopLevel _toOvarBeingDefined _toOvariableStyle) of (_toIglobalDefinitions, _toIidentifier, _toIisInModule, _toIisSimpleExpression, _toIisSingleVar, _toIscopes, _toIvariableStyle, _toIwarnings) -> ( case ( ( _toIisInModule ) ) of _stepOisInModule -> ( case ( ( _toIvariableStyle ) ) of _stepOvariableStyle -> ( case ( ( _toIscopes ) ) of _stepOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _stepOscopeLevel -> ( case ( ( _toImtokenPos ) ) of _stepOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _stepOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _stepOisMeta -> ( case ( ( _toIglobalDefinitions ) ) of _stepOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _stepOfuncName -> ( case ( ( _lhsIconfig ) ) of _stepOconfig -> ( case ( ( Nothing ) ) of _stepOvarBeingDefined -> ( case ( ( True ) ) of _stepOtopLevel -> ( case ( ( False ) ) of _stepOinParentheses -> ( case ( ( False ) ) of _stepOisNegation -> ( case (step_1 _stepOconfig _stepOfuncName _stepOglobalDefinitions _stepOinParentheses _stepOisInModule _stepOisMeta _stepOisNegation _stepOloopLevel _stepOmtokenPos _stepOscopeLevel _stepOscopes _stepOtopLevel _stepOvarBeingDefined _stepOvariableStyle) of (_stepIglobalDefinitions, _stepIidentifier, _stepIisInModule, _stepIisSimpleExpression, _stepIisSingleVar, _stepIscopes, _stepIvariableStyle, _stepIwarnings) -> ( case ( ( _stepIisInModule ) ) of _bodyOisInModule -> ( case ( ( _stepIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( M.singleton _varIidentifier (not (lint_unusedLoopVars _lhsIconfig), _varImtokenPos) : _stepIscopes ) ) of _bodyOscopes -> ( case ( ( _stepIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _stepImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case ( ( _lhsIloopLevel + 1 ) ) of _bodyOloopLevel -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _varIidentifier (const _valIidentifier (const _toIidentifier (const _stepIidentifier _bodyIidentifier)))) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _varIwarnings ++ _valIwarnings ++ _toIwarnings ++ _stepIwarnings ++ _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( checkShadows _lhsIscopes _varIcopy ) ) of _shadowWarning -> ( case ( ( if not (lint_shadowing _lhsIconfig) || isNothing _shadowWarning then id else (:) . fromMaybe (error "fromMaybe ANFor +warnings") $ _shadowWarning ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _lhsImtokenPos EmptyFor ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_ANFor_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) ) ) ) sem_Stat_AGFor :: ([MToken]) -> T_MExprList -> T_Block -> T_Stat sem_Stat_AGFor vars_ vals_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (vals_) of (_valsIcopy, vals_1) -> ( case ( ( AGFor vars_ _valsIcopy _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AGFor_1 :: T_Stat_1 sem_Stat_AGFor_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisMeta ) ) of _bodyOisMeta -> ( case ( ( _lhsIisInModule ) ) of _valsOisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _valsOvariableStyle -> ( case ( ( _lhsIscopes ) ) of _valsOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _valsOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _valsOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _valsOloopLevel -> ( case ( ( _lhsIisMeta ) ) of _valsOisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _valsOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _valsOfuncName -> ( case ( ( _lhsIconfig ) ) of _valsOconfig -> ( case ( ( True ) ) of _valsOtopLevel -> ( case ( ( True ) ) of _valsOinParentheses -> ( case (vals_1 _valsOconfig _valsOfuncName _valsOglobalDefinitions _valsOinParentheses _valsOisInModule _valsOisMeta _valsOloopLevel _valsOmtokenPos _valsOscopeLevel _valsOscopes _valsOtopLevel _valsOvariableStyle) of (_valsIglobalDefinitions, _valsIidentifier, _valsIisInModule, _valsImtokenPos, _valsIscopes, _valsIvariableStyle, _valsIwarnings) -> ( case ( ( _valsIisInModule ) ) of _bodyOisInModule -> ( case ( ( _valsIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( M.fromList $ map (\mt -> (tokenLabel mt, (not (lint_unusedLoopVars _lhsIconfig), mpos mt))) vars_ ) ) of _introduces -> ( case ( ( _introduces : _valsIscopes ) ) of _bodyOscopes -> ( case ( ( _valsIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _valsImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIfuncName ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case ( ( _lhsIloopLevel + 1 ) ) of _bodyOloopLevel -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _valsIidentifier _bodyIidentifier) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _valsIwarnings ++ _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_shadowing _lhsIconfig) then id else (++) . catMaybes . map (checkShadows _lhsIscopes) $ vars_ ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_emptyBlocks _lhsIconfig) || _bodyIstatementCount > 0 then id else (:) $ warn _lhsImtokenPos EmptyFor ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AGFor_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) sem_Stat_AFunc :: T_FuncName -> ([MToken]) -> T_Block -> T_Stat sem_Stat_AFunc name_ args_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (name_) of (_nameIcopy, _nameIisMeta, name_1) -> ( case ( ( AFunc _nameIcopy args_ _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_AFunc_1 :: T_Stat_1 sem_Stat_AFunc_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisInModule ) ) of _nameOisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _nameOvariableStyle -> ( case ( ( _lhsIscopes ) ) of _nameOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _nameOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _nameOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _nameOloopLevel -> ( case ( ( _nameIisMeta || findSelf args_ || _lhsIisMeta ) ) of _isMeta -> ( case ( ( _isMeta ) ) of _nameOisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _nameOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _nameOfuncName -> ( case ( ( _lhsIconfig ) ) of _nameOconfig -> ( case (name_1 _nameOconfig _nameOfuncName _nameOglobalDefinitions _nameOisInModule _nameOisMeta _nameOloopLevel _nameOmtokenPos _nameOscopeLevel _nameOscopes _nameOvariableStyle) of (_nameIglobalDefinitions, _nameIhasSuffixes, _nameIidentifier, _nameIisInModule, _nameImtokenPos, _nameIscopes, _nameIvariableStyle, _nameIwarnings) -> ( case ( ( _nameIisInModule ) ) of _bodyOisInModule -> ( case ( ( _nameIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( _isMeta ) ) of _bodyOisMeta -> ( case ( ( filter (/= MToken emptyRg VarArg) $ args_ ) ) of _argIdentifiers -> ( case ( ( (if _isMeta then M.insert "self" (True, _nameImtokenPos) else id) $ M.fromList . map (\mt -> (tokenLabel mt, (not . lint_unusedParameters $ _lhsIconfig, mpos mt))) $ _argIdentifiers ) ) of _introduces -> ( case ( ( _introduces : (registerVariable _nameIscopes _nameImtokenPos _nameIidentifier True) ) ) of _bodyOscopes -> ( case ( ( _nameIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _nameImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _nameIidentifier ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _globalDefinitions_augmented_syn -> ( case ( ( if _lhsIisInModule || isVariableLocal _lhsIscopes _nameIidentifier || _nameIisMeta || _nameIhasSuffixes then id else M.insertWith (++) _nameIidentifier [_nameImtokenPos] ) ) of _globalDefinitions_augmented_f1 -> ( case ( ( foldr ($) _globalDefinitions_augmented_syn [_globalDefinitions_augmented_f1] ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _nameIidentifier _bodyIidentifier) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _nameIwarnings ++ _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( if not (lint_shadowing _lhsIconfig) then id else (++) . catMaybes . map (checkShadows _lhsIscopes) $ _argIdentifiers ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_AFunc_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) sem_Stat_ALocFunc :: T_FuncName -> ([MToken]) -> T_Block -> T_Stat sem_Stat_ALocFunc name_ args_ body_ = ( case (body_) of (_bodyIcopy, body_1) -> ( case (name_) of (_nameIcopy, _nameIisMeta, name_1) -> ( case ( ( ALocFunc _nameIcopy args_ _bodyIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_Stat_ALocFunc_1 :: T_Stat_1 sem_Stat_ALocFunc_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIisInModule ) ) of _nameOisInModule -> ( case ( ( _lhsIvariableStyle ) ) of _nameOvariableStyle -> ( case ( ( _lhsIscopes ) ) of _nameOscopes -> ( case ( ( _lhsIscopeLevel ) ) of _nameOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _nameOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _nameOloopLevel -> ( case ( ( findSelf args_ || _lhsIisMeta ) ) of _isMeta -> ( case ( ( _isMeta ) ) of _nameOisMeta -> ( case ( ( _lhsIglobalDefinitions ) ) of _nameOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _nameOfuncName -> ( case ( ( _lhsIconfig ) ) of _nameOconfig -> ( case (name_1 _nameOconfig _nameOfuncName _nameOglobalDefinitions _nameOisInModule _nameOisMeta _nameOloopLevel _nameOmtokenPos _nameOscopeLevel _nameOscopes _nameOvariableStyle) of (_nameIglobalDefinitions, _nameIhasSuffixes, _nameIidentifier, _nameIisInModule, _nameImtokenPos, _nameIscopes, _nameIvariableStyle, _nameIwarnings) -> ( case ( ( _nameIisInModule ) ) of _bodyOisInModule -> ( case ( ( _nameIglobalDefinitions ) ) of _bodyOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _bodyOconfig -> ( case ( ( _isMeta ) ) of _bodyOisMeta -> ( case ( ( M.insert _nameIidentifier (False, _nameImtokenPos) (head _nameIscopes) : tail _nameIscopes ) ) of _passedScopes -> ( case ( ( filter (/= MToken emptyRg VarArg) $ args_ ) ) of _argIdentifiers -> ( case ( ( (if _isMeta then M.insert "self" (True, _nameImtokenPos) else id) $ M.fromList . map (\mt -> (tokenLabel mt, (not . lint_unusedParameters $ _lhsIconfig, mpos mt))) $ _argIdentifiers ) ) of _introduces -> ( case ( ( _introduces : _passedScopes ) ) of _bodyOscopes -> ( case ( ( _nameIvariableStyle ) ) of _bodyOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _bodyOscopeLevel -> ( case ( ( _nameImtokenPos ) ) of _bodyOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _bodyOloopLevel -> ( case ( ( _nameIidentifier ) ) of _bodyOfuncName -> ( case ( ( False ) ) of _bodyOisRepeat -> ( case (body_1 _bodyOconfig _bodyOfuncName _bodyOglobalDefinitions _bodyOisInModule _bodyOisMeta _bodyOisRepeat _bodyOloopLevel _bodyOmtokenPos _bodyOscopeLevel _bodyOscopes _bodyOvariableStyle) of (_bodyIglobalDefinitions, _bodyIidentifier, _bodyIisIfStatement, _bodyIisInModule, _bodyImtokenPos, _bodyIscopes, _bodyIstatementCount, _bodyIvariableStyle, _bodyIwarnings) -> ( case ( ( _bodyIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _nameIidentifier _bodyIidentifier) ) ) of _lhsOidentifier -> ( case ( ( False ) ) of _lhsOisIfStatement -> ( case ( ( _bodyIisInModule ) ) of _lhsOisInModule -> ( case ( ( _bodyImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _bodyIscopes ) ) of _lhsOscopes -> ( case ( ( _bodyIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _nameIwarnings ++ _bodyIwarnings ) ) of _warnings_augmented_syn -> ( case ( ( MToken _nameImtokenPos (Identifier _nameIidentifier) ) ) of _funcname -> ( case ( ( checkShadows _lhsIscopes _funcname ) ) of _funcNameShadows -> ( case ( ( if not (lint_shadowing _lhsIconfig) then id else (++) . catMaybes . map (checkShadows _lhsIscopes) $ _argIdentifiers ) ) of _warnings_augmented_f2 -> ( case ( ( if not (lint_shadowing _lhsIconfig) || isNothing _funcNameShadows then id else (:) . fromMaybe (error "fromMaybe ALocFunc +warnings") $ _funcNameShadows ) ) of _warnings_augmented_f1 -> ( case ( ( foldr ($) _warnings_augmented_syn [_warnings_augmented_f1, _warnings_augmented_f2] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisIfStatement, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_Stat_ALocFunc_1 ) ) of (sem_Stat_1) -> (_lhsOcopy, sem_Stat_1) ) ) ) ) ) -- Token ------------------------------------------------------- -- cata sem_Token :: Token -> T_Token sem_Token (Whitespace _space) = (sem_Token_Whitespace _space) sem_Token (DashComment _comment) = (sem_Token_DashComment _comment) sem_Token (DashBlockComment _depth _comment) = (sem_Token_DashBlockComment _depth _comment) sem_Token (SlashComment _comment) = (sem_Token_SlashComment _comment) sem_Token (SlashBlockComment _comment) = (sem_Token_SlashBlockComment _comment) sem_Token (Semicolon) = (sem_Token_Semicolon) sem_Token (TNumber _num) = (sem_Token_TNumber _num) sem_Token (DQString _str) = (sem_Token_DQString _str) sem_Token (SQString _str) = (sem_Token_SQString _str) sem_Token (MLString _str) = (sem_Token_MLString _str) sem_Token (TTrue) = (sem_Token_TTrue) sem_Token (TFalse) = (sem_Token_TFalse) sem_Token (Nil) = (sem_Token_Nil) sem_Token (VarArg) = (sem_Token_VarArg) sem_Token (Plus) = (sem_Token_Plus) sem_Token (Minus) = (sem_Token_Minus) sem_Token (Multiply) = (sem_Token_Multiply) sem_Token (Divide) = (sem_Token_Divide) sem_Token (Modulus) = (sem_Token_Modulus) sem_Token (Power) = (sem_Token_Power) sem_Token (TEq) = (sem_Token_TEq) sem_Token (TNEq) = (sem_Token_TNEq) sem_Token (TCNEq) = (sem_Token_TCNEq) sem_Token (TLEQ) = (sem_Token_TLEQ) sem_Token (TGEQ) = (sem_Token_TGEQ) sem_Token (TLT) = (sem_Token_TLT) sem_Token (TGT) = (sem_Token_TGT) sem_Token (Equals) = (sem_Token_Equals) sem_Token (Concatenate) = (sem_Token_Concatenate) sem_Token (Colon) = (sem_Token_Colon) sem_Token (Dot) = (sem_Token_Dot) sem_Token (Comma) = (sem_Token_Comma) sem_Token (Hash) = (sem_Token_Hash) sem_Token (Not) = (sem_Token_Not) sem_Token (CNot) = (sem_Token_CNot) sem_Token (And) = (sem_Token_And) sem_Token (CAnd) = (sem_Token_CAnd) sem_Token (Or) = (sem_Token_Or) sem_Token (COr) = (sem_Token_COr) sem_Token (Function) = (sem_Token_Function) sem_Token (Local) = (sem_Token_Local) sem_Token (If) = (sem_Token_If) sem_Token (Then) = (sem_Token_Then) sem_Token (Elseif) = (sem_Token_Elseif) sem_Token (Else) = (sem_Token_Else) sem_Token (For) = (sem_Token_For) sem_Token (In) = (sem_Token_In) sem_Token (Do) = (sem_Token_Do) sem_Token (While) = (sem_Token_While) sem_Token (Until) = (sem_Token_Until) sem_Token (Repeat) = (sem_Token_Repeat) sem_Token (Continue) = (sem_Token_Continue) sem_Token (Break) = (sem_Token_Break) sem_Token (Return) = (sem_Token_Return) sem_Token (End) = (sem_Token_End) sem_Token (LRound) = (sem_Token_LRound) sem_Token (RRound) = (sem_Token_RRound) sem_Token (LCurly) = (sem_Token_LCurly) sem_Token (RCurly) = (sem_Token_RCurly) sem_Token (LSquare) = (sem_Token_LSquare) sem_Token (RSquare) = (sem_Token_RSquare) sem_Token (Label _whitespaceBefore _lbl _whitespaceAfter) = (sem_Token_Label _whitespaceBefore _lbl _whitespaceAfter) sem_Token (Identifier _ident) = (sem_Token_Identifier _ident) -- semantic domain type T_Token = (Token, String, ([String -> LintMessage])) data Inh_Token = Inh_Token {} data Syn_Token = Syn_Token {copy_Syn_Token :: Token, identifier_Syn_Token :: String, warnings_Syn_Token :: ([String -> LintMessage])} wrap_Token :: T_Token -> Inh_Token -> Syn_Token wrap_Token sem (Inh_Token) = ( let (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) = sem in (Syn_Token _lhsOcopy _lhsOidentifier _lhsOwarnings) ) sem_Token_Whitespace :: String -> T_Token sem_Token_Whitespace space_ = ( case ( ( Whitespace space_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_DashComment :: String -> T_Token sem_Token_DashComment comment_ = ( case ( ( DashComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_DashBlockComment :: Int -> String -> T_Token sem_Token_DashBlockComment depth_ comment_ = ( case ( ( DashBlockComment depth_ comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_SlashComment :: String -> T_Token sem_Token_SlashComment comment_ = ( case ( ( SlashComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_SlashBlockComment :: String -> T_Token sem_Token_SlashBlockComment comment_ = ( case ( ( SlashBlockComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Semicolon :: T_Token sem_Token_Semicolon = ( case ( ( Semicolon ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TNumber :: String -> T_Token sem_Token_TNumber num_ = ( case ( ( TNumber num_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_DQString :: String -> T_Token sem_Token_DQString str_ = ( case ( ( DQString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_SQString :: String -> T_Token sem_Token_SQString str_ = ( case ( ( SQString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_MLString :: String -> T_Token sem_Token_MLString str_ = ( case ( ( MLString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TTrue :: T_Token sem_Token_TTrue = ( case ( ( TTrue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TFalse :: T_Token sem_Token_TFalse = ( case ( ( TFalse ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Nil :: T_Token sem_Token_Nil = ( case ( ( Nil ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_VarArg :: T_Token sem_Token_VarArg = ( case ( ( VarArg ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Plus :: T_Token sem_Token_Plus = ( case ( ( Plus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Minus :: T_Token sem_Token_Minus = ( case ( ( Minus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Multiply :: T_Token sem_Token_Multiply = ( case ( ( Multiply ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Divide :: T_Token sem_Token_Divide = ( case ( ( Divide ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Modulus :: T_Token sem_Token_Modulus = ( case ( ( Modulus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Power :: T_Token sem_Token_Power = ( case ( ( Power ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TEq :: T_Token sem_Token_TEq = ( case ( ( TEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TNEq :: T_Token sem_Token_TNEq = ( case ( ( TNEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TCNEq :: T_Token sem_Token_TCNEq = ( case ( ( TCNEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TLEQ :: T_Token sem_Token_TLEQ = ( case ( ( TLEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TGEQ :: T_Token sem_Token_TGEQ = ( case ( ( TGEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TLT :: T_Token sem_Token_TLT = ( case ( ( TLT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_TGT :: T_Token sem_Token_TGT = ( case ( ( TGT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Equals :: T_Token sem_Token_Equals = ( case ( ( Equals ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Concatenate :: T_Token sem_Token_Concatenate = ( case ( ( Concatenate ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Colon :: T_Token sem_Token_Colon = ( case ( ( Colon ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Dot :: T_Token sem_Token_Dot = ( case ( ( Dot ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Comma :: T_Token sem_Token_Comma = ( case ( ( Comma ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Hash :: T_Token sem_Token_Hash = ( case ( ( Hash ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Not :: T_Token sem_Token_Not = ( case ( ( Not ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_CNot :: T_Token sem_Token_CNot = ( case ( ( CNot ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_And :: T_Token sem_Token_And = ( case ( ( And ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_CAnd :: T_Token sem_Token_CAnd = ( case ( ( CAnd ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Or :: T_Token sem_Token_Or = ( case ( ( Or ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_COr :: T_Token sem_Token_COr = ( case ( ( COr ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Function :: T_Token sem_Token_Function = ( case ( ( Function ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Local :: T_Token sem_Token_Local = ( case ( ( Local ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_If :: T_Token sem_Token_If = ( case ( ( If ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Then :: T_Token sem_Token_Then = ( case ( ( Then ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Elseif :: T_Token sem_Token_Elseif = ( case ( ( Elseif ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Else :: T_Token sem_Token_Else = ( case ( ( Else ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_For :: T_Token sem_Token_For = ( case ( ( For ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_In :: T_Token sem_Token_In = ( case ( ( In ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Do :: T_Token sem_Token_Do = ( case ( ( Do ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_While :: T_Token sem_Token_While = ( case ( ( While ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Until :: T_Token sem_Token_Until = ( case ( ( Until ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Repeat :: T_Token sem_Token_Repeat = ( case ( ( Repeat ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Continue :: T_Token sem_Token_Continue = ( case ( ( Continue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Break :: T_Token sem_Token_Break = ( case ( ( Break ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Return :: T_Token sem_Token_Return = ( case ( ( Return ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_End :: T_Token sem_Token_End = ( case ( ( End ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_LRound :: T_Token sem_Token_LRound = ( case ( ( LRound ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_RRound :: T_Token sem_Token_RRound = ( case ( ( RRound ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_LCurly :: T_Token sem_Token_LCurly = ( case ( ( LCurly ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_RCurly :: T_Token sem_Token_RCurly = ( case ( ( RCurly ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_LSquare :: T_Token sem_Token_LSquare = ( case ( ( LSquare ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_RSquare :: T_Token sem_Token_RSquare = ( case ( ( RSquare ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Label :: String -> String -> String -> T_Token sem_Token_Label whitespaceBefore_ lbl_ whitespaceAfter_ = ( case ( ( Label whitespaceBefore_ lbl_ whitespaceAfter_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( lbl_ ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) sem_Token_Identifier :: String -> T_Token sem_Token_Identifier ident_ = ( case ( ( Identifier ident_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( ident_ ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) -- TokenList --------------------------------------------------- -- cata sem_TokenList :: TokenList -> T_TokenList sem_TokenList list = (Prelude.foldr sem_TokenList_Cons sem_TokenList_Nil (Prelude.map sem_Token list)) -- semantic domain type T_TokenList = (TokenList, String, ([String -> LintMessage])) data Inh_TokenList = Inh_TokenList {} data Syn_TokenList = Syn_TokenList {copy_Syn_TokenList :: TokenList, identifier_Syn_TokenList :: String, warnings_Syn_TokenList :: ([String -> LintMessage])} wrap_TokenList :: T_TokenList -> Inh_TokenList -> Syn_TokenList wrap_TokenList sem (Inh_TokenList) = ( let (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) = sem in (Syn_TokenList _lhsOcopy _lhsOidentifier _lhsOwarnings) ) sem_TokenList_Cons :: T_Token -> T_TokenList -> T_TokenList sem_TokenList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, _tlIidentifier, _tlIwarnings) -> ( case (hd_) of (_hdIcopy, _hdIidentifier, _hdIwarnings) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) ) ) sem_TokenList_Nil :: T_TokenList sem_TokenList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOcopy, _lhsOidentifier, _lhsOwarnings) ) ) ) ) -- UnOp -------------------------------------------------------- -- cata sem_UnOp :: UnOp -> T_UnOp sem_UnOp (UnMinus) = (sem_UnOp_UnMinus) sem_UnOp (ANot) = (sem_UnOp_ANot) sem_UnOp (AHash) = (sem_UnOp_AHash) -- semantic domain type T_UnOp = (UnOp, T_UnOp_1) type T_UnOp_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_UnOp = Inh_UnOp {config_Inh_UnOp :: LintSettings, funcName_Inh_UnOp :: String, globalDefinitions_Inh_UnOp :: (M.Map String [Region]), isInModule_Inh_UnOp :: Bool, isMeta_Inh_UnOp :: Bool, loopLevel_Inh_UnOp :: Int, mtokenPos_Inh_UnOp :: Region, scopeLevel_Inh_UnOp :: Int, scopes_Inh_UnOp :: ([M.Map String (Bool, Region)]), variableStyle_Inh_UnOp :: DeterminedVariableStyle} data Syn_UnOp = Syn_UnOp {copy_Syn_UnOp :: UnOp, globalDefinitions_Syn_UnOp :: (M.Map String [Region]), identifier_Syn_UnOp :: String, isInModule_Syn_UnOp :: Bool, isNegation_Syn_UnOp :: Bool, mtokenPos_Syn_UnOp :: Region, scopes_Syn_UnOp :: ([M.Map String (Bool, Region)]), variableStyle_Syn_UnOp :: DeterminedVariableStyle, warnings_Syn_UnOp :: ([String -> LintMessage])} wrap_UnOp :: T_UnOp -> Inh_UnOp -> Syn_UnOp wrap_UnOp sem (Inh_UnOp _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisNegation, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_UnOp _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOisNegation _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_UnOp_UnMinus :: T_UnOp sem_UnOp_UnMinus = ( case ( ( UnMinus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_UnOp_UnMinus_1 :: T_UnOp_1 sem_UnOp_UnMinus_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisNegation -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisNegation, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_UnOp_UnMinus_1 ) ) of (sem_UnOp_1) -> (_lhsOcopy, sem_UnOp_1) ) ) ) sem_UnOp_ANot :: T_UnOp sem_UnOp_ANot = ( case ( ( ANot ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_UnOp_ANot_1 :: T_UnOp_1 sem_UnOp_ANot_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( True ) ) of _lhsOisNegation -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisNegation, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_UnOp_ANot_1 ) ) of (sem_UnOp_1) -> (_lhsOcopy, sem_UnOp_1) ) ) ) sem_UnOp_AHash :: T_UnOp sem_UnOp_AHash = ( case ( ( AHash ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_UnOp_AHash_1 :: T_UnOp_1 sem_UnOp_AHash_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( False ) ) of _lhsOisNegation -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOisNegation, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) in sem_UnOp_AHash_1 ) ) of (sem_UnOp_1) -> (_lhsOcopy, sem_UnOp_1) ) ) ) -- VarsList ---------------------------------------------------- -- cata sem_VarsList :: VarsList -> T_VarsList sem_VarsList list = (Prelude.foldr sem_VarsList_Cons sem_VarsList_Nil (Prelude.map sem_Declaration list)) -- semantic domain type T_VarsList = (VarsList, T_VarsList_1) type T_VarsList_1 = LintSettings -> String -> (M.Map String [Region]) -> Bool -> Bool -> Bool -> Int -> Region -> Int -> ([M.Map String (Bool, Region)]) -> DeterminedVariableStyle -> ((M.Map String [Region]), String, Bool, Region, ([M.Map String (Bool, Region)]), DeterminedVariableStyle, ([String -> LintMessage])) data Inh_VarsList = Inh_VarsList {config_Inh_VarsList :: LintSettings, funcName_Inh_VarsList :: String, globalDefinitions_Inh_VarsList :: (M.Map String [Region]), isInModule_Inh_VarsList :: Bool, isMeta_Inh_VarsList :: Bool, localDefinition_Inh_VarsList :: Bool, loopLevel_Inh_VarsList :: Int, mtokenPos_Inh_VarsList :: Region, scopeLevel_Inh_VarsList :: Int, scopes_Inh_VarsList :: ([M.Map String (Bool, Region)]), variableStyle_Inh_VarsList :: DeterminedVariableStyle} data Syn_VarsList = Syn_VarsList {copy_Syn_VarsList :: VarsList, globalDefinitions_Syn_VarsList :: (M.Map String [Region]), identifier_Syn_VarsList :: String, isInModule_Syn_VarsList :: Bool, mtokenPos_Syn_VarsList :: Region, scopes_Syn_VarsList :: ([M.Map String (Bool, Region)]), variableStyle_Syn_VarsList :: DeterminedVariableStyle, warnings_Syn_VarsList :: ([String -> LintMessage])} wrap_VarsList :: T_VarsList -> Inh_VarsList -> Syn_VarsList wrap_VarsList sem (Inh_VarsList _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle) = ( let (_lhsOcopy, sem_1) = sem (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) = sem_1 _lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle in (Syn_VarsList _lhsOcopy _lhsOglobalDefinitions _lhsOidentifier _lhsOisInModule _lhsOmtokenPos _lhsOscopes _lhsOvariableStyle _lhsOwarnings) ) sem_VarsList_Cons :: T_Declaration -> T_VarsList -> T_VarsList sem_VarsList_Cons hd_ tl_ = ( case (tl_) of (_tlIcopy, tl_1) -> ( case (hd_) of (_hdIcopy, hd_1) -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_VarsList_Cons_1 :: T_VarsList_1 sem_VarsList_Cons_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIscopes ) ) of _hdOscopes -> ( case ( ( _lhsIlocalDefinition ) ) of _hdOlocalDefinition -> ( case ( ( _lhsIisMeta ) ) of _hdOisMeta -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIvariableStyle ) ) of _hdOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _hdOscopeLevel -> ( case ( ( _lhsImtokenPos ) ) of _hdOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _hdOloopLevel -> ( case ( ( _lhsIisInModule ) ) of _hdOisInModule -> ( case ( ( _lhsIglobalDefinitions ) ) of _hdOglobalDefinitions -> ( case ( ( _lhsIfuncName ) ) of _hdOfuncName -> ( case (hd_1 _hdOconfig _hdOfuncName _hdOglobalDefinitions _hdOisInModule _hdOisMeta _hdOlocalDefinition _hdOloopLevel _hdOmtokenPos _hdOscopeLevel _hdOscopes _hdOvariableStyle) of (_hdIglobalDefinitions, _hdIidentifier, _hdIisInModule, _hdImtokenPos, _hdIscopes, _hdIvariableStyle, _hdIwarnings) -> ( case ( ( _hdIscopes ) ) of _tlOscopes -> ( case ( ( _lhsIlocalDefinition ) ) of _tlOlocalDefinition -> ( case ( ( _lhsIisMeta ) ) of _tlOisMeta -> ( case ( ( _hdIisInModule ) ) of _tlOisInModule -> ( case ( ( _hdIglobalDefinitions ) ) of _tlOglobalDefinitions -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _hdIvariableStyle ) ) of _tlOvariableStyle -> ( case ( ( _lhsIscopeLevel ) ) of _tlOscopeLevel -> ( case ( ( _hdImtokenPos ) ) of _tlOmtokenPos -> ( case ( ( _lhsIloopLevel ) ) of _tlOloopLevel -> ( case ( ( _lhsIfuncName ) ) of _tlOfuncName -> ( case (tl_1 _tlOconfig _tlOfuncName _tlOglobalDefinitions _tlOisInModule _tlOisMeta _tlOlocalDefinition _tlOloopLevel _tlOmtokenPos _tlOscopeLevel _tlOscopes _tlOvariableStyle) of (_tlIglobalDefinitions, _tlIidentifier, _tlIisInModule, _tlImtokenPos, _tlIscopes, _tlIvariableStyle, _tlIwarnings) -> ( case ( ( _tlIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( (const _hdIidentifier _tlIidentifier) ) ) of _lhsOidentifier -> ( case ( ( _tlIisInModule ) ) of _lhsOisInModule -> ( case ( ( _hdImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _tlIscopes ) ) of _lhsOscopes -> ( case ( ( _tlIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) in sem_VarsList_Cons_1 ) ) of (sem_VarsList_1) -> (_lhsOcopy, sem_VarsList_1) ) ) ) ) ) sem_VarsList_Nil :: T_VarsList sem_VarsList_Nil = ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( let sem_VarsList_Nil_1 :: T_VarsList_1 sem_VarsList_Nil_1 = ( \_lhsIconfig _lhsIfuncName _lhsIglobalDefinitions _lhsIisInModule _lhsIisMeta _lhsIlocalDefinition _lhsIloopLevel _lhsImtokenPos _lhsIscopeLevel _lhsIscopes _lhsIvariableStyle -> ( case ( ( _lhsIglobalDefinitions ) ) of _lhsOglobalDefinitions -> ( case ( ( unknownIdentifier ) ) of _lhsOidentifier -> ( case ( ( _lhsIisInModule ) ) of _lhsOisInModule -> ( case ( ( _lhsImtokenPos ) ) of _lhsOmtokenPos -> ( case ( ( _lhsIscopes ) ) of _lhsOscopes -> ( case ( ( _lhsIvariableStyle ) ) of _lhsOvariableStyle -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOglobalDefinitions, _lhsOidentifier, _lhsOisInModule, _lhsOmtokenPos, _lhsOscopes, _lhsOvariableStyle, _lhsOwarnings) ) ) ) ) ) ) ) ) in sem_VarsList_Nil_1 ) ) of (sem_VarsList_1) -> (_lhsOcopy, sem_VarsList_1) ) ) )