Moved the usageCheckPass function into the new Check module

This commit is contained in:
Neil Brown 2008-01-28 13:15:36 +00:00
parent 51d02559d0
commit 7a30a2ceb5
3 changed files with 15 additions and 14 deletions

View File

@ -16,7 +16,7 @@ You should have received a copy of the GNU General Public License along
with this program. If not, see <http://www.gnu.org/licenses/>. with this program. If not, see <http://www.gnu.org/licenses/>.
-} -}
module ArrayUsageCheck (checkArrayUsage, FlattenedExp(..), makeEquations, usageCheckPass, VarMap) where module ArrayUsageCheck (checkArrayUsage, FlattenedExp(..), makeEquations, VarMap) where
import Control.Monad.Error import Control.Monad.Error
import Control.Monad.State import Control.Monad.State
@ -29,24 +29,13 @@ import qualified Data.Set as Set
import qualified AST as A import qualified AST as A
import CompState import CompState
import Errors import Errors
import FlowGraph
import Metadata import Metadata
import Omega import Omega
import Pass
import ShowCode import ShowCode
import Types import Types
import UsageCheckAlgorithms
import UsageCheckUtils import UsageCheckUtils
import Utils import Utils
usageCheckPass :: Pass
usageCheckPass t = do g' <- buildFlowGraph labelFunctions t
g <- case g' of
Left err -> die err
Right g -> return g
sequence_ $ checkPar checkArrayUsage g
return t
checkArrayUsage :: forall m. (Die m, CSM m) => (Meta, ParItems (Maybe Decl, Vars)) -> m () checkArrayUsage :: forall m. (Die m, CSM m) => (Meta, ParItems (Maybe Decl, Vars)) -> m ()
checkArrayUsage (m,p) = mapM_ (checkIndexes m) $ Map.toList $ checkArrayUsage (m,p) = mapM_ (checkIndexes m) $ Map.toList $
groupArrayIndexes $ transformParItems snd p groupArrayIndexes $ transformParItems snd p

View File

@ -20,7 +20,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
-- the control-flow graph stuff, hence the use of functions that match the dictionary -- the control-flow graph stuff, hence the use of functions that match the dictionary
-- of functions in FlowGraph. This is also why we don't drill down into processes; -- of functions in FlowGraph. This is also why we don't drill down into processes;
-- the control-flow graph means that we only need to concentrate on each node that isn't nested. -- the control-flow graph means that we only need to concentrate on each node that isn't nested.
module Check (checkInitVar) where module Check (checkInitVar, usageCheckPass) where
import Control.Monad.Identity import Control.Monad.Identity
import Data.Graph.Inductive import Data.Graph.Inductive
@ -29,14 +29,26 @@ import qualified Data.Map as Map
import Data.Maybe import Data.Maybe
import qualified Data.Set as Set import qualified Data.Set as Set
import ArrayUsageCheck
import CompState import CompState
import Errors import Errors
import FlowAlgorithms import FlowAlgorithms
import FlowGraph import FlowGraph
import Metadata import Metadata
import Pass
import ShowCode import ShowCode
import UsageCheckAlgorithms
import UsageCheckUtils import UsageCheckUtils
usageCheckPass :: Pass
usageCheckPass t = do g' <- buildFlowGraph labelFunctions t
g <- case g' of
Left err -> die err
Right g -> return g
sequence_ $ checkPar checkArrayUsage g
return t
{- {-
Near the beginning, this piece of code was too clever for itself and applied processVarW using "everything". Near the beginning, this piece of code was too clever for itself and applied processVarW using "everything".
The problem with this is that given var@(A.SubscriptedVariable _ sub arrVar), the functions would be recursively The problem with this is that given var@(A.SubscriptedVariable _ sub arrVar), the functions would be recursively

View File

@ -19,7 +19,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
-- | Lists of passes -- | Lists of passes
module PassList (getPassList) where module PassList (getPassList) where
import ArrayUsageCheck import Check
import CompState import CompState
import GenerateC import GenerateC
import GenerateCPPCSP import GenerateCPPCSP