Moved flattenParItems to UsageCheckUtils and added a couple of deriving (Show) clauses
This commit is contained in:
parent
71915494a6
commit
73f16267a9
|
@ -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/>.
|
||||
-}
|
||||
|
||||
module ArrayUsageCheck (BackgroundKnowledge(..), checkArrayUsage, FlattenedExp(..), makeEquations, VarMap) where
|
||||
module ArrayUsageCheck (BackgroundKnowledge(..), checkArrayUsage, FlattenedExp(..), onlyConst, makeEquations, VarMap) where
|
||||
|
||||
import Control.Monad.Error
|
||||
import Control.Monad.State
|
||||
|
@ -43,12 +43,6 @@ checkArrayUsage :: forall m. (Die m, CSMR m, MonadIO m) => (Meta, ParItems Usage
|
|||
checkArrayUsage (m,p) = mapM_ (checkIndexes m) $ Map.toList $
|
||||
groupArrayIndexes $ transformParItems nodeVars p
|
||||
where
|
||||
-- Gets all the items inside a ParItems and returns them in a flat list.
|
||||
flattenParItems :: ParItems a -> [a]
|
||||
flattenParItems (SeqItems xs) = xs
|
||||
flattenParItems (ParItems ps) = concatMap flattenParItems ps
|
||||
flattenParItems (RepParItem _ p) = flattenParItems p
|
||||
|
||||
-- Takes a ParItems Vars, and returns a map from array-variable-name to a list of writes and a list of reads for that array.
|
||||
-- Returns (array name, list of written-to indexes, list of read-from indexes)
|
||||
groupArrayIndexes :: ParItems Vars -> Map.Map String (ParItems ([A.Expression], [A.Expression]))
|
||||
|
@ -202,6 +196,7 @@ data FlattenedExp
|
|||
-- ^ A modulo, with the given top and bottom (in that order)
|
||||
| Divide (Set.Set FlattenedExp) (Set.Set FlattenedExp)
|
||||
-- ^ An integer division, with the given top and bottom (in that order)
|
||||
deriving (Show)
|
||||
|
||||
instance Eq FlattenedExp where
|
||||
a == b = EQ == compare a b
|
||||
|
|
|
@ -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/>.
|
||||
-}
|
||||
|
||||
module UsageCheckUtils (customVarCompare, Decl(..), emptyVars, foldUnionVars, getVarActual, getVarProc, labelFunctions, mapUnionVars, ParItems(..), processVarW, transformParItems, UsageLabel(..), Var(..), Vars(..), vars) where
|
||||
module UsageCheckUtils (customVarCompare, Decl(..), emptyVars, flattenParItems, foldUnionVars, getVarActual, getVarProc, labelFunctions, mapUnionVars, ParItems(..), processVarW, transformParItems, UsageLabel(..), Var(..), Vars(..), vars) where
|
||||
|
||||
import Data.Generics hiding (GT)
|
||||
import Data.List
|
||||
|
@ -71,6 +71,7 @@ data ParItems a
|
|||
= SeqItems [a] -- ^ A list of items that happen only in sequence (i.e. none are in parallel with each other)
|
||||
| ParItems [ParItems a] -- ^ A list of items that are all in parallel with each other
|
||||
| RepParItem A.Replicator (ParItems a) -- ^ A list of replicated items that happen in parallel
|
||||
deriving (Show)
|
||||
|
||||
data UsageLabel = Usage
|
||||
{nodeRep :: Maybe A.Replicator
|
||||
|
@ -82,6 +83,13 @@ transformParItems f (SeqItems xs) = SeqItems $ map f xs
|
|||
transformParItems f (ParItems ps) = ParItems $ map (transformParItems f) ps
|
||||
transformParItems f (RepParItem r p) = RepParItem r (transformParItems f p)
|
||||
|
||||
-- Gets all the items inside a ParItems and returns them in a flat list.
|
||||
flattenParItems :: ParItems a -> [a]
|
||||
flattenParItems (SeqItems xs) = xs
|
||||
flattenParItems (ParItems ps) = concatMap flattenParItems ps
|
||||
flattenParItems (RepParItem _ p) = flattenParItems p
|
||||
|
||||
|
||||
emptyVars :: Vars
|
||||
emptyVars = Vars Set.empty Set.empty Set.empty
|
||||
|
||||
|
|
Loading…
Reference in New Issue
Block a user