{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -fno-warn-unused-binds #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} -- UUAGC 0.9.55 (src/GLuaFixer/AG/LexLint.ag) module GLuaFixer.AG.LexLint ( lintWarnings, fixedLexPositions, ) 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/LexLint.hs" #-} {-# LINE 15 "src/GLuaFixer/AG/LexLint.ag" #-} import Data.List import GLua.AG.Token import GLua.TokenTypes import GLuaFixer.LintMessage import GLuaFixer.LintSettings {-# LINE 28 "src/GLuaFixer/AG/LexLint.hs" #-} {-# LINE 25 "src/GLuaFixer/AG/LexLint.ag" #-} ---------------------------------------- -- C-style / Lua-style syntax inconsistencies ---------------------------------------- -- For detecting the usage of Lua/C syntax inconsistently data SyntaxUsed = SyntaxUsed {luaUsed :: Bool, cUsed :: Bool} deriving (Show) instance Semigroup SyntaxUsed where (SyntaxUsed l1 c1) <> (SyntaxUsed l2 c2) = SyntaxUsed (l1 || l2) (c1 || c2) -- Monoid instance instance Monoid SyntaxUsed where mempty = SyntaxUsed False False mTokenWarning :: Region -> Issue -> FilePath -> LintMessage mTokenWarning pos issue = LintMessage LintWarning pos issue isSingleChar :: String -> Bool isSingleChar [] = True isSingleChar ('\\' : xs) = length xs == 1 isSingleChar (_ : []) = True isSingleChar _ = False -- Locate the exact position of trailing whitespace locateTrailingWhitespace :: LineColPos -> String -> (LineColPos, String) locateTrailingWhitespace pos (' ' : xs) = (pos, xs) locateTrailingWhitespace pos ('\t' : xs) = (pos, xs) locateTrailingWhitespace pos (x : xs) = locateTrailingWhitespace (customAdvanceChr pos x) xs locateTrailingWhitespace pos [] = (pos, "") -- Locate the start of a line's indentation in a string of whitespace indentationStart :: LineColPos -> String -> LineColPos indentationStart pos = go pos pos where go :: LineColPos -> LineColPos -> String -> LineColPos go _ cur ('\n' : xs) = let next = customAdvanceChr cur '\n' in go next next xs go found cur (x : xs) = go found (customAdvanceChr cur x) xs go found _ [] = found endOfTrailingWhitespace :: (LineColPos, String) -> LineColPos endOfTrailingWhitespace (pos, ('\n' : _)) = pos endOfTrailingWhitespace (pos, (x : xs)) = endOfTrailingWhitespace (customAdvanceChr pos x, xs) endOfTrailingWhitespace (pos, []) = pos {-# LINE 76 "src/GLuaFixer/AG/LexLint.hs" #-} {-# LINE 237 "src/GLuaFixer/AG/LexLint.ag" #-} inh_MTokenList :: LintSettings -> Inh_MTokenList inh_MTokenList conf = Inh_MTokenList { config_Inh_MTokenList = conf , andSyntax_Inh_MTokenList = mempty , indentation_Inh_MTokenList = mempty , lineCommentSyntax_Inh_MTokenList = mempty , multilineCommentSyntax_Inh_MTokenList = mempty , neqSyntax_Inh_MTokenList = mempty , notSyntax_Inh_MTokenList = mempty , orSyntax_Inh_MTokenList = mempty , strSyntax_Inh_MTokenList = mempty , nextTokenPos_Inh_MTokenList = LineColPos 0 0 0 } lintWarnings :: LintSettings -> [MToken] -> [String -> LintMessage] lintWarnings conf p = warnings_Syn_MTokenList (wrap_MTokenList (sem_MTokenList p) (inh_MTokenList conf)) -- Necessary because uu-parsinglib's LineColPos walks over tabs as though they are 8 spaces. Note -- that this also applies when the code is lexed by the Parsec lexer. fixedLexPositions :: [MToken] -> [MToken] fixedLexPositions p = copy_Syn_MTokenList (wrap_MTokenList (sem_MTokenList p) (inh_MTokenList defaultLintSettings)) {-# LINE 104 "src/GLuaFixer/AG/LexLint.hs" #-} -- 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 = SyntaxUsed -> LintSettings -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> LineColPos -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> (SyntaxUsed, MToken, SyntaxUsed, SyntaxUsed, SyntaxUsed, SyntaxUsed, LineColPos, SyntaxUsed, SyntaxUsed, SyntaxUsed, ([FilePath -> LintMessage])) data Inh_MToken = Inh_MToken {andSyntax_Inh_MToken :: SyntaxUsed, config_Inh_MToken :: LintSettings, indentation_Inh_MToken :: SyntaxUsed, lineCommentSyntax_Inh_MToken :: SyntaxUsed, multilineCommentSyntax_Inh_MToken :: SyntaxUsed, neqSyntax_Inh_MToken :: SyntaxUsed, nextTokenPos_Inh_MToken :: LineColPos, notSyntax_Inh_MToken :: SyntaxUsed, orSyntax_Inh_MToken :: SyntaxUsed, strSyntax_Inh_MToken :: SyntaxUsed} data Syn_MToken = Syn_MToken {andSyntax_Syn_MToken :: SyntaxUsed, copy_Syn_MToken :: MToken, indentation_Syn_MToken :: SyntaxUsed, lineCommentSyntax_Syn_MToken :: SyntaxUsed, multilineCommentSyntax_Syn_MToken :: SyntaxUsed, neqSyntax_Syn_MToken :: SyntaxUsed, nextTokenPos_Syn_MToken :: LineColPos, notSyntax_Syn_MToken :: SyntaxUsed, orSyntax_Syn_MToken :: SyntaxUsed, strSyntax_Syn_MToken :: SyntaxUsed, warnings_Syn_MToken :: ([FilePath -> LintMessage])} wrap_MToken :: T_MToken -> Inh_MToken -> Syn_MToken wrap_MToken sem (Inh_MToken _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax) = ( let (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) = sem _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax in (Syn_MToken _lhsOandSyntax _lhsOcopy _lhsOindentation _lhsOlineCommentSyntax _lhsOmultilineCommentSyntax _lhsOneqSyntax _lhsOnextTokenPos _lhsOnotSyntax _lhsOorSyntax _lhsOstrSyntax _lhsOwarnings) ) sem_MToken_MToken :: T_Region -> T_Token -> T_MToken sem_MToken_MToken mpos_ mtok_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIconfig ) ) of _mtokOconfig -> ( case ( ( _lhsIandSyntax ) ) of _mposOandSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _mposOstrSyntax -> ( case ( ( _lhsIorSyntax ) ) of _mposOorSyntax -> ( case ( ( _lhsInotSyntax ) ) of _mposOnotSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _mposOnextTokenPos -> ( case ( ( _lhsIneqSyntax ) ) of _mposOneqSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _mposOmultilineCommentSyntax -> ( case ( ( _lhsIlineCommentSyntax ) ) of _mposOlineCommentSyntax -> ( case ( ( _lhsIindentation ) ) of _mposOindentation -> ( case ( ( _lhsIconfig ) ) of _mposOconfig -> ( case (mpos_ _mposOandSyntax _mposOconfig _mposOindentation _mposOlineCommentSyntax _mposOmultilineCommentSyntax _mposOneqSyntax _mposOnextTokenPos _mposOnotSyntax _mposOorSyntax _mposOstrSyntax) of (_mposIandSyntax, _mposIcopy, _mposIindentation, _mposIlineCommentSyntax, _mposImultilineCommentSyntax, _mposIneqSyntax, _mposInextTokenPos, _mposInotSyntax, _mposIorSyntax, _mposIstrSyntax, _mposIwarnings) -> ( case ( ( _mposIandSyntax ) ) of _mtokOandSyntax -> ( case ( ( _mposIstrSyntax ) ) of _mtokOstrSyntax -> ( case ( ( _mposIorSyntax ) ) of _mtokOorSyntax -> ( case ( ( _mposInotSyntax ) ) of _mtokOnotSyntax -> ( case ( ( _mposInextTokenPos ) ) of _mtokOnextTokenPos -> ( case ( ( _mposIneqSyntax ) ) of _mtokOneqSyntax -> ( case ( ( _mposImultilineCommentSyntax ) ) of _mtokOmultilineCommentSyntax -> ( case ( ( _mposIlineCommentSyntax ) ) of _mtokOlineCommentSyntax -> ( case ( ( _mposIindentation ) ) of _mtokOindentation -> ( case (mtok_ _mtokOandSyntax _mtokOconfig _mtokOindentation _mtokOlineCommentSyntax _mtokOmultilineCommentSyntax _mtokOneqSyntax _mtokOnextTokenPos _mtokOnotSyntax _mtokOorSyntax _mtokOstrSyntax) of (_mtokIandSyntax, _mtokIcopy, _mtokIcustomWarnings, _mtokIindentation, _mtokIlineCommentSyntax, _mtokImultilineCommentSyntax, _mtokIneqSyntax, _mtokInextTokenPos, _mtokInotSyntax, _mtokIorSyntax, _mtokIstrSyntax, _mtokItokenWarnings, _mtokIwarnings) -> ( case ( ( _mtokIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Region _lhsInextTokenPos (customAdvanceToken _lhsInextTokenPos _mtokIcopy) ) ) of _mpos -> ( case ( ( MToken _mpos _mtokIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _mtokIindentation ) ) of _lhsOindentation -> ( case ( ( _mtokIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _mtokImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _mtokIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _mtokInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _mtokInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _mtokIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _mtokIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( _mtokIcustomWarnings ++ map (mTokenWarning _mpos) _mtokItokenWarnings ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) -- 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 = SyntaxUsed -> LintSettings -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> LineColPos -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> (SyntaxUsed, MTokenList, SyntaxUsed, SyntaxUsed, SyntaxUsed, SyntaxUsed, LineColPos, SyntaxUsed, SyntaxUsed, SyntaxUsed, ([FilePath -> LintMessage])) data Inh_MTokenList = Inh_MTokenList {andSyntax_Inh_MTokenList :: SyntaxUsed, config_Inh_MTokenList :: LintSettings, indentation_Inh_MTokenList :: SyntaxUsed, lineCommentSyntax_Inh_MTokenList :: SyntaxUsed, multilineCommentSyntax_Inh_MTokenList :: SyntaxUsed, neqSyntax_Inh_MTokenList :: SyntaxUsed, nextTokenPos_Inh_MTokenList :: LineColPos, notSyntax_Inh_MTokenList :: SyntaxUsed, orSyntax_Inh_MTokenList :: SyntaxUsed, strSyntax_Inh_MTokenList :: SyntaxUsed} data Syn_MTokenList = Syn_MTokenList {andSyntax_Syn_MTokenList :: SyntaxUsed, copy_Syn_MTokenList :: MTokenList, indentation_Syn_MTokenList :: SyntaxUsed, lineCommentSyntax_Syn_MTokenList :: SyntaxUsed, multilineCommentSyntax_Syn_MTokenList :: SyntaxUsed, neqSyntax_Syn_MTokenList :: SyntaxUsed, nextTokenPos_Syn_MTokenList :: LineColPos, notSyntax_Syn_MTokenList :: SyntaxUsed, orSyntax_Syn_MTokenList :: SyntaxUsed, strSyntax_Syn_MTokenList :: SyntaxUsed, warnings_Syn_MTokenList :: ([FilePath -> LintMessage])} wrap_MTokenList :: T_MTokenList -> Inh_MTokenList -> Syn_MTokenList wrap_MTokenList sem (Inh_MTokenList _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax) = ( let (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) = sem _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax in (Syn_MTokenList _lhsOandSyntax _lhsOcopy _lhsOindentation _lhsOlineCommentSyntax _lhsOmultilineCommentSyntax _lhsOneqSyntax _lhsOnextTokenPos _lhsOnotSyntax _lhsOorSyntax _lhsOstrSyntax _lhsOwarnings) ) sem_MTokenList_Cons :: T_MToken -> T_MTokenList -> T_MTokenList sem_MTokenList_Cons hd_ tl_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIandSyntax ) ) of _hdOandSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _hdOstrSyntax -> ( case ( ( _lhsIorSyntax ) ) of _hdOorSyntax -> ( case ( ( _lhsInotSyntax ) ) of _hdOnotSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _hdOnextTokenPos -> ( case ( ( _lhsIneqSyntax ) ) of _hdOneqSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _hdOmultilineCommentSyntax -> ( case ( ( _lhsIlineCommentSyntax ) ) of _hdOlineCommentSyntax -> ( case ( ( _lhsIindentation ) ) of _hdOindentation -> ( case (hd_ _hdOandSyntax _hdOconfig _hdOindentation _hdOlineCommentSyntax _hdOmultilineCommentSyntax _hdOneqSyntax _hdOnextTokenPos _hdOnotSyntax _hdOorSyntax _hdOstrSyntax) of (_hdIandSyntax, _hdIcopy, _hdIindentation, _hdIlineCommentSyntax, _hdImultilineCommentSyntax, _hdIneqSyntax, _hdInextTokenPos, _hdInotSyntax, _hdIorSyntax, _hdIstrSyntax, _hdIwarnings) -> ( case ( ( _hdIandSyntax ) ) of _tlOandSyntax -> ( case ( ( _hdIstrSyntax ) ) of _tlOstrSyntax -> ( case ( ( _hdIorSyntax ) ) of _tlOorSyntax -> ( case ( ( _hdInotSyntax ) ) of _tlOnotSyntax -> ( case ( ( _hdInextTokenPos ) ) of _tlOnextTokenPos -> ( case ( ( _hdIneqSyntax ) ) of _tlOneqSyntax -> ( case ( ( _hdImultilineCommentSyntax ) ) of _tlOmultilineCommentSyntax -> ( case ( ( _hdIlineCommentSyntax ) ) of _tlOlineCommentSyntax -> ( case ( ( _hdIindentation ) ) of _tlOindentation -> ( case (tl_ _tlOandSyntax _tlOconfig _tlOindentation _tlOlineCommentSyntax _tlOmultilineCommentSyntax _tlOneqSyntax _tlOnextTokenPos _tlOnotSyntax _tlOorSyntax _tlOstrSyntax) of (_tlIandSyntax, _tlIcopy, _tlIindentation, _tlIlineCommentSyntax, _tlImultilineCommentSyntax, _tlIneqSyntax, _tlInextTokenPos, _tlInotSyntax, _tlIorSyntax, _tlIstrSyntax, _tlIwarnings) -> ( case ( ( _tlIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _tlIindentation ) ) of _lhsOindentation -> ( case ( ( _tlIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _tlImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _tlIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _tlInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _tlInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _tlIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _tlIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_MTokenList_Nil :: T_MTokenList sem_MTokenList_Nil = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) -- Region ------------------------------------------------------ -- cata sem_Region :: Region -> T_Region sem_Region (Region _start _end) = (sem_Region_Region _start _end) -- semantic domain type T_Region = SyntaxUsed -> LintSettings -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> LineColPos -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> (SyntaxUsed, Region, SyntaxUsed, SyntaxUsed, SyntaxUsed, SyntaxUsed, LineColPos, SyntaxUsed, SyntaxUsed, SyntaxUsed, ([FilePath -> LintMessage])) data Inh_Region = Inh_Region {andSyntax_Inh_Region :: SyntaxUsed, config_Inh_Region :: LintSettings, indentation_Inh_Region :: SyntaxUsed, lineCommentSyntax_Inh_Region :: SyntaxUsed, multilineCommentSyntax_Inh_Region :: SyntaxUsed, neqSyntax_Inh_Region :: SyntaxUsed, nextTokenPos_Inh_Region :: LineColPos, notSyntax_Inh_Region :: SyntaxUsed, orSyntax_Inh_Region :: SyntaxUsed, strSyntax_Inh_Region :: SyntaxUsed} data Syn_Region = Syn_Region {andSyntax_Syn_Region :: SyntaxUsed, copy_Syn_Region :: Region, indentation_Syn_Region :: SyntaxUsed, lineCommentSyntax_Syn_Region :: SyntaxUsed, multilineCommentSyntax_Syn_Region :: SyntaxUsed, neqSyntax_Syn_Region :: SyntaxUsed, nextTokenPos_Syn_Region :: LineColPos, notSyntax_Syn_Region :: SyntaxUsed, orSyntax_Syn_Region :: SyntaxUsed, strSyntax_Syn_Region :: SyntaxUsed, warnings_Syn_Region :: ([FilePath -> LintMessage])} wrap_Region :: T_Region -> Inh_Region -> Syn_Region wrap_Region sem (Inh_Region _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax) = ( let (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) = sem _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax in (Syn_Region _lhsOandSyntax _lhsOcopy _lhsOindentation _lhsOlineCommentSyntax _lhsOmultilineCommentSyntax _lhsOneqSyntax _lhsOnextTokenPos _lhsOnotSyntax _lhsOorSyntax _lhsOstrSyntax _lhsOwarnings) ) sem_Region_Region :: LineColPos -> LineColPos -> T_Region sem_Region_Region start_ end_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Region start_ end_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) -- 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 = SyntaxUsed -> LintSettings -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> LineColPos -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> (SyntaxUsed, Token, ([FilePath -> LintMessage]), SyntaxUsed, SyntaxUsed, SyntaxUsed, SyntaxUsed, LineColPos, SyntaxUsed, SyntaxUsed, SyntaxUsed, ([Issue]), ([FilePath -> LintMessage])) data Inh_Token = Inh_Token {andSyntax_Inh_Token :: SyntaxUsed, config_Inh_Token :: LintSettings, indentation_Inh_Token :: SyntaxUsed, lineCommentSyntax_Inh_Token :: SyntaxUsed, multilineCommentSyntax_Inh_Token :: SyntaxUsed, neqSyntax_Inh_Token :: SyntaxUsed, nextTokenPos_Inh_Token :: LineColPos, notSyntax_Inh_Token :: SyntaxUsed, orSyntax_Inh_Token :: SyntaxUsed, strSyntax_Inh_Token :: SyntaxUsed} data Syn_Token = Syn_Token {andSyntax_Syn_Token :: SyntaxUsed, copy_Syn_Token :: Token, customWarnings_Syn_Token :: ([FilePath -> LintMessage]), indentation_Syn_Token :: SyntaxUsed, lineCommentSyntax_Syn_Token :: SyntaxUsed, multilineCommentSyntax_Syn_Token :: SyntaxUsed, neqSyntax_Syn_Token :: SyntaxUsed, nextTokenPos_Syn_Token :: LineColPos, notSyntax_Syn_Token :: SyntaxUsed, orSyntax_Syn_Token :: SyntaxUsed, strSyntax_Syn_Token :: SyntaxUsed, tokenWarnings_Syn_Token :: ([Issue]), warnings_Syn_Token :: ([FilePath -> LintMessage])} wrap_Token :: T_Token -> Inh_Token -> Syn_Token wrap_Token sem (Inh_Token _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax) = ( let (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) = sem _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax in (Syn_Token _lhsOandSyntax _lhsOcopy _lhsOcustomWarnings _lhsOindentation _lhsOlineCommentSyntax _lhsOmultilineCommentSyntax _lhsOneqSyntax _lhsOnextTokenPos _lhsOnotSyntax _lhsOorSyntax _lhsOstrSyntax _lhsOtokenWarnings _lhsOwarnings) ) sem_Token_Whitespace :: String -> T_Token sem_Token_Whitespace space_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Whitespace space_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _customWarnings_augmented_syn -> ( case ( ( _lhsInextTokenPos ) ) of _curTokenPos -> ( case ( ( customAdvanceStr _curTokenPos space_ ) ) of _nextTokenPos -> ( case ( ( Region (indentationStart _curTokenPos space_) _nextTokenPos ) ) of _indentationRg -> ( case ( ( locateTrailingWhitespace _curTokenPos space_ ) ) of _whitespaceStart -> ( case ( ( endOfTrailingWhitespace _whitespaceStart ) ) of _whitespaceEnd -> ( case ( ( _lhsIindentation <> SyntaxUsed (isInfixOf "\n " space_) (isInfixOf "\n\t" space_) ) ) of _whitespaceUsed -> ( case ( ( luaUsed _whitespaceUsed && cUsed _whitespaceUsed ) ) of _inconsistent -> ( case ( ( if not (lint_trailingWhitespace _lhsIconfig) || (not (isInfixOf " \n" space_) && not (isInfixOf "\t\n" space_)) then id else (:) $ mTokenWarning (Region (fst _whitespaceStart) _whitespaceEnd) TrailingWhitespace ) ) of _customWarnings_augmented_f2 -> ( case ( ( if not (lint_whitespaceStyle _lhsIconfig) || not _inconsistent then id else (:) $ mTokenWarning _indentationRg InconsistentTabsSpaces ) ) of _customWarnings_augmented_f1 -> ( case ( ( foldr ($) _customWarnings_augmented_syn [_customWarnings_augmented_f1, _customWarnings_augmented_f2] ) ) of _lhsOcustomWarnings -> ( case ( ( if _inconsistent then mempty else _whitespaceUsed ) ) of _indentation -> ( case ( ( _indentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _nextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_DashComment :: String -> T_Token sem_Token_DashComment comment_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( DashComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsIlineCommentSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _lineCommentSyntax -> ( case ( ( _lineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "--" "//" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_DashBlockComment :: Int -> String -> T_Token sem_Token_DashBlockComment depth_ comment_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( DashBlockComment depth_ comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsImultilineCommentSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _multilineCommentSyntax -> ( case ( ( _multilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( showString "--[" . showString (replicate depth_ '-') . showChar '[' . showString comment_ . showChar ']' . showString (replicate depth_ '-') . showChar ']' $ "" ) ) of _str -> ( case ( ( customAdvanceStr _lhsInextTokenPos _str ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "--[[ ]]" "/* */" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_SlashComment :: String -> T_Token sem_Token_SlashComment comment_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( SlashComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsIlineCommentSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _lineCommentSyntax -> ( case ( ( _lineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "//" "--" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_SlashBlockComment :: String -> T_Token sem_Token_SlashBlockComment comment_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( SlashBlockComment comment_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsImultilineCommentSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _multilineCommentSyntax -> ( case ( ( _multilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( showString "/*" . showString comment_ . showString "*/" $ "" ) ) of _str -> ( case ( ( customAdvanceStr _lhsInextTokenPos _str ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "/* */" "--[[ ]]" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Semicolon :: T_Token sem_Token_Semicolon = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Semicolon ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TNumber :: String -> T_Token sem_Token_TNumber num_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TNumber num_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_DQString :: String -> T_Token sem_Token_DQString str_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( DQString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceStr _lhsInextTokenPos str_ ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsIstrSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _strSyntax -> ( case ( ( _strSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "double quoted strings" "single quoted strings" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_SQString :: String -> T_Token sem_Token_SQString str_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( SQString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceStr _lhsInextTokenPos str_ ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsIstrSyntax) || isSingleChar str_ ) ) of _consistent -> ( case ( ( SyntaxUsed False (_consistent && not (isSingleChar str_)) ) ) of _strSyntax -> ( case ( ( _strSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "single quoted strings" "double quoted strings" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_MLString :: String -> T_Token sem_Token_MLString str_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( MLString str_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceStr _lhsInextTokenPos str_ ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TTrue :: T_Token sem_Token_TTrue = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TTrue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TFalse :: T_Token sem_Token_TFalse = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TFalse ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Nil :: T_Token sem_Token_Nil = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Nil ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_VarArg :: T_Token sem_Token_VarArg = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( VarArg ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Plus :: T_Token sem_Token_Plus = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Plus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Minus :: T_Token sem_Token_Minus = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Minus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Multiply :: T_Token sem_Token_Multiply = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Multiply ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Divide :: T_Token sem_Token_Divide = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Divide ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Modulus :: T_Token sem_Token_Modulus = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Modulus ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Power :: T_Token sem_Token_Power = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Power ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TEq :: T_Token sem_Token_TEq = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TNEq :: T_Token sem_Token_TNEq = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TNEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsIneqSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _neqSyntax -> ( case ( ( _neqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "~=" "!=" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TCNEq :: T_Token sem_Token_TCNEq = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TCNEq ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsIneqSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _neqSyntax -> ( case ( ( _neqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "!=" "~=" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TLEQ :: T_Token sem_Token_TLEQ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TLEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TGEQ :: T_Token sem_Token_TGEQ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TGEQ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TLT :: T_Token sem_Token_TLT = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TLT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_TGT :: T_Token sem_Token_TGT = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( TGT ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Equals :: T_Token sem_Token_Equals = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Equals ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Concatenate :: T_Token sem_Token_Concatenate = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Concatenate ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Colon :: T_Token sem_Token_Colon = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Colon ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Dot :: T_Token sem_Token_Dot = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Dot ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Comma :: T_Token sem_Token_Comma = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Comma ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Hash :: T_Token sem_Token_Hash = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Hash ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Not :: T_Token sem_Token_Not = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Not ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsInotSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _notSyntax -> ( case ( ( _notSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "not" "!" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_CNot :: T_Token sem_Token_CNot = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( CNot ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsInotSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _notSyntax -> ( case ( ( _notSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "!" "not" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_And :: T_Token sem_Token_And = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsIandSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _andSyntax -> ( case ( ( _andSyntax ) ) of _lhsOandSyntax -> ( case ( ( And ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "and" "&&" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_CAnd :: T_Token sem_Token_CAnd = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsIandSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _andSyntax -> ( case ( ( _andSyntax ) ) of _lhsOandSyntax -> ( case ( ( CAnd ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "&&" "and" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Or :: T_Token sem_Token_Or = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Or ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . cUsed $ _lhsIorSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed _consistent False ) ) of _orSyntax -> ( case ( ( _orSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "or" "||" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_COr :: T_Token sem_Token_COr = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( COr ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( (not . lint_syntaxInconsistencies $ _lhsIconfig) || (not . luaUsed $ _lhsIorSyntax) ) ) of _consistent -> ( case ( ( SyntaxUsed False _consistent ) ) of _orSyntax -> ( case ( ( _orSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _tokenWarnings_augmented_syn -> ( case ( ( if _consistent then id else (:) $ SyntaxInconsistency "||" "or" ) ) of _tokenWarnings_augmented_f1 -> ( case ( ( foldr ($) _tokenWarnings_augmented_syn [_tokenWarnings_augmented_f1] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Function :: T_Token sem_Token_Function = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Function ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Local :: T_Token sem_Token_Local = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Local ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_If :: T_Token sem_Token_If = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( If ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Then :: T_Token sem_Token_Then = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Then ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Elseif :: T_Token sem_Token_Elseif = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Elseif ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Else :: T_Token sem_Token_Else = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Else ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_For :: T_Token sem_Token_For = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( For ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_In :: T_Token sem_Token_In = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( In ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Do :: T_Token sem_Token_Do = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Do ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_While :: T_Token sem_Token_While = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( While ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Until :: T_Token sem_Token_Until = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Until ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Repeat :: T_Token sem_Token_Repeat = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Repeat ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Continue :: T_Token sem_Token_Continue = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Continue ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Break :: T_Token sem_Token_Break = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Break ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Return :: T_Token sem_Token_Return = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Return ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_End :: T_Token sem_Token_End = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( End ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_LRound :: T_Token sem_Token_LRound = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( LRound ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_RRound :: T_Token sem_Token_RRound = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( RRound ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_LCurly :: T_Token sem_Token_LCurly = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( LCurly ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_RCurly :: T_Token sem_Token_RCurly = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( RCurly ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_LSquare :: T_Token sem_Token_LSquare = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( LSquare ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_RSquare :: T_Token sem_Token_RSquare = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( RSquare ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Label :: String -> String -> String -> T_Token sem_Token_Label whitespaceBefore_ lbl_ whitespaceAfter_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Label whitespaceBefore_ lbl_ whitespaceAfter_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceStr _lhsInextTokenPos (show _copy) ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_Token_Identifier :: String -> T_Token sem_Token_Identifier ident_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( Identifier ident_ ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( [] ) ) of _lhsOcustomWarnings -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( customAdvanceToken _lhsInextTokenPos _copy ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOcustomWarnings, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _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 = SyntaxUsed -> LintSettings -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> LineColPos -> SyntaxUsed -> SyntaxUsed -> SyntaxUsed -> (SyntaxUsed, TokenList, SyntaxUsed, SyntaxUsed, SyntaxUsed, SyntaxUsed, LineColPos, SyntaxUsed, SyntaxUsed, SyntaxUsed, ([Issue]), ([FilePath -> LintMessage])) data Inh_TokenList = Inh_TokenList {andSyntax_Inh_TokenList :: SyntaxUsed, config_Inh_TokenList :: LintSettings, indentation_Inh_TokenList :: SyntaxUsed, lineCommentSyntax_Inh_TokenList :: SyntaxUsed, multilineCommentSyntax_Inh_TokenList :: SyntaxUsed, neqSyntax_Inh_TokenList :: SyntaxUsed, nextTokenPos_Inh_TokenList :: LineColPos, notSyntax_Inh_TokenList :: SyntaxUsed, orSyntax_Inh_TokenList :: SyntaxUsed, strSyntax_Inh_TokenList :: SyntaxUsed} data Syn_TokenList = Syn_TokenList {andSyntax_Syn_TokenList :: SyntaxUsed, copy_Syn_TokenList :: TokenList, indentation_Syn_TokenList :: SyntaxUsed, lineCommentSyntax_Syn_TokenList :: SyntaxUsed, multilineCommentSyntax_Syn_TokenList :: SyntaxUsed, neqSyntax_Syn_TokenList :: SyntaxUsed, nextTokenPos_Syn_TokenList :: LineColPos, notSyntax_Syn_TokenList :: SyntaxUsed, orSyntax_Syn_TokenList :: SyntaxUsed, strSyntax_Syn_TokenList :: SyntaxUsed, tokenWarnings_Syn_TokenList :: ([Issue]), warnings_Syn_TokenList :: ([FilePath -> LintMessage])} wrap_TokenList :: T_TokenList -> Inh_TokenList -> Syn_TokenList wrap_TokenList sem (Inh_TokenList _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax) = ( let (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) = sem _lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax in (Syn_TokenList _lhsOandSyntax _lhsOcopy _lhsOindentation _lhsOlineCommentSyntax _lhsOmultilineCommentSyntax _lhsOneqSyntax _lhsOnextTokenPos _lhsOnotSyntax _lhsOorSyntax _lhsOstrSyntax _lhsOtokenWarnings _lhsOwarnings) ) sem_TokenList_Cons :: T_Token -> T_TokenList -> T_TokenList sem_TokenList_Cons hd_ tl_ = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIconfig ) ) of _tlOconfig -> ( case ( ( _lhsIconfig ) ) of _hdOconfig -> ( case ( ( _lhsIandSyntax ) ) of _hdOandSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _hdOstrSyntax -> ( case ( ( _lhsIorSyntax ) ) of _hdOorSyntax -> ( case ( ( _lhsInotSyntax ) ) of _hdOnotSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _hdOnextTokenPos -> ( case ( ( _lhsIneqSyntax ) ) of _hdOneqSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _hdOmultilineCommentSyntax -> ( case ( ( _lhsIlineCommentSyntax ) ) of _hdOlineCommentSyntax -> ( case ( ( _lhsIindentation ) ) of _hdOindentation -> ( case (hd_ _hdOandSyntax _hdOconfig _hdOindentation _hdOlineCommentSyntax _hdOmultilineCommentSyntax _hdOneqSyntax _hdOnextTokenPos _hdOnotSyntax _hdOorSyntax _hdOstrSyntax) of (_hdIandSyntax, _hdIcopy, _hdIcustomWarnings, _hdIindentation, _hdIlineCommentSyntax, _hdImultilineCommentSyntax, _hdIneqSyntax, _hdInextTokenPos, _hdInotSyntax, _hdIorSyntax, _hdIstrSyntax, _hdItokenWarnings, _hdIwarnings) -> ( case ( ( _hdIandSyntax ) ) of _tlOandSyntax -> ( case ( ( _hdIstrSyntax ) ) of _tlOstrSyntax -> ( case ( ( _hdIorSyntax ) ) of _tlOorSyntax -> ( case ( ( _hdInotSyntax ) ) of _tlOnotSyntax -> ( case ( ( _hdInextTokenPos ) ) of _tlOnextTokenPos -> ( case ( ( _hdIneqSyntax ) ) of _tlOneqSyntax -> ( case ( ( _hdImultilineCommentSyntax ) ) of _tlOmultilineCommentSyntax -> ( case ( ( _hdIlineCommentSyntax ) ) of _tlOlineCommentSyntax -> ( case ( ( _hdIindentation ) ) of _tlOindentation -> ( case (tl_ _tlOandSyntax _tlOconfig _tlOindentation _tlOlineCommentSyntax _tlOmultilineCommentSyntax _tlOneqSyntax _tlOnextTokenPos _tlOnotSyntax _tlOorSyntax _tlOstrSyntax) of (_tlIandSyntax, _tlIcopy, _tlIindentation, _tlIlineCommentSyntax, _tlImultilineCommentSyntax, _tlIneqSyntax, _tlInextTokenPos, _tlInotSyntax, _tlIorSyntax, _tlIstrSyntax, _tlItokenWarnings, _tlIwarnings) -> ( case ( ( _tlIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( (:) _hdIcopy _tlIcopy ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _tlIindentation ) ) of _lhsOindentation -> ( case ( ( _tlIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _tlImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _tlIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _tlInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _tlInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _tlIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _tlIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( _hdItokenWarnings ++ _tlItokenWarnings ) ) of _lhsOtokenWarnings -> ( case ( ( _hdIwarnings ++ _tlIwarnings ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) ) sem_TokenList_Nil :: T_TokenList sem_TokenList_Nil = ( \_lhsIandSyntax _lhsIconfig _lhsIindentation _lhsIlineCommentSyntax _lhsImultilineCommentSyntax _lhsIneqSyntax _lhsInextTokenPos _lhsInotSyntax _lhsIorSyntax _lhsIstrSyntax -> ( case ( ( _lhsIandSyntax ) ) of _lhsOandSyntax -> ( case ( ( [] ) ) of _copy -> ( case ( ( _copy ) ) of _lhsOcopy -> ( case ( ( _lhsIindentation ) ) of _lhsOindentation -> ( case ( ( _lhsIlineCommentSyntax ) ) of _lhsOlineCommentSyntax -> ( case ( ( _lhsImultilineCommentSyntax ) ) of _lhsOmultilineCommentSyntax -> ( case ( ( _lhsIneqSyntax ) ) of _lhsOneqSyntax -> ( case ( ( _lhsInextTokenPos ) ) of _lhsOnextTokenPos -> ( case ( ( _lhsInotSyntax ) ) of _lhsOnotSyntax -> ( case ( ( _lhsIorSyntax ) ) of _lhsOorSyntax -> ( case ( ( _lhsIstrSyntax ) ) of _lhsOstrSyntax -> ( case ( ( [] ) ) of _lhsOtokenWarnings -> ( case ( ( [] ) ) of _lhsOwarnings -> (_lhsOandSyntax, _lhsOcopy, _lhsOindentation, _lhsOlineCommentSyntax, _lhsOmultilineCommentSyntax, _lhsOneqSyntax, _lhsOnextTokenPos, _lhsOnotSyntax, _lhsOorSyntax, _lhsOstrSyntax, _lhsOtokenWarnings, _lhsOwarnings) ) ) ) ) ) ) ) ) ) ) ) ) ) )