Added quick preliminary support for the PERMITALIASES pragma
This commit is contained in:
parent
14df1e09b7
commit
81959bd76b
|
@ -158,7 +158,7 @@ checkArrayUsage (m,p)
|
||||||
checkIndexes m ((arrName, arrDir), indexes) = do
|
checkIndexes m ((arrName, arrDir), indexes) = do
|
||||||
sharedNames <- getCompState >>* csNameAttr
|
sharedNames <- getCompState >>* csNameAttr
|
||||||
let declNames = [x | Just x <- fmap (getDecl . snd) $ flattenParItems p]
|
let declNames = [x | Just x <- fmap (getDecl . snd) $ flattenParItems p]
|
||||||
when (Map.lookup arrName sharedNames /= Just NameShared && arrName `notElem` declNames) $
|
when (fmap (Set.member NameShared) (Map.lookup arrName sharedNames) /= Just True && arrName `notElem` declNames) $
|
||||||
do userArrName <- getRealName (A.Name undefined arrName)
|
do userArrName <- getRealName (A.Name undefined arrName)
|
||||||
arrType <- astTypeOf (A.Name undefined arrName)
|
arrType <- astTypeOf (A.Name undefined arrName)
|
||||||
arrLength <- case arrType of
|
arrLength <- case arrType of
|
||||||
|
|
|
@ -342,7 +342,7 @@ checkPlainVarUsage (m, p) = check p
|
||||||
-- A quick way to do this is to do a fold-union across all the maps, turning
|
-- A quick way to do this is to do a fold-union across all the maps, turning
|
||||||
-- the values into lists that can then be scanned for any problems.
|
-- the values into lists that can then be scanned for any problems.
|
||||||
check (ParItems ps)
|
check (ParItems ps)
|
||||||
= do sharedNames <- getCompState >>* csNameAttr >>* Map.filter (== NameShared)
|
= do sharedNames <- getCompState >>* csNameAttr >>* Map.filter (Set.member NameShared)
|
||||||
>>* Map.keysSet >>* (Set.map $ UsageCheckUtils.Var . A.Variable emptyMeta . A.Name emptyMeta)
|
>>* Map.keysSet >>* (Set.map $ UsageCheckUtils.Var . A.Variable emptyMeta . A.Name emptyMeta)
|
||||||
let decl = concatMap getDecl ps
|
let decl = concatMap getDecl ps
|
||||||
filt <- filterPlain
|
filt <- filterPlain
|
||||||
|
|
|
@ -85,7 +85,7 @@ instance Ord UnifyIndex where
|
||||||
-- | An entry in the map corresponding to a UnifyIndex
|
-- | An entry in the map corresponding to a UnifyIndex
|
||||||
type UnifyValue = TypeExp A.Type
|
type UnifyValue = TypeExp A.Type
|
||||||
|
|
||||||
data NameAttr = NameShared deriving (Typeable, Data, Eq, Show, Ord)
|
data NameAttr = NameShared | NameAliasesPermitted deriving (Typeable, Data, Eq, Show, Ord)
|
||||||
|
|
||||||
-- | State necessary for compilation.
|
-- | State necessary for compilation.
|
||||||
data CompState = CompState {
|
data CompState = CompState {
|
||||||
|
@ -116,7 +116,7 @@ data CompState = CompState {
|
||||||
csNames :: Map String A.NameDef,
|
csNames :: Map String A.NameDef,
|
||||||
csUnscopedNames :: Map String String,
|
csUnscopedNames :: Map String String,
|
||||||
csNameCounter :: Int,
|
csNameCounter :: Int,
|
||||||
csNameAttr :: Map String NameAttr,
|
csNameAttr :: Map String (Set.Set NameAttr),
|
||||||
|
|
||||||
-- Set by passes
|
-- Set by passes
|
||||||
csTypeContext :: [Maybe A.Type],
|
csTypeContext :: [Maybe A.Type],
|
||||||
|
|
|
@ -24,6 +24,7 @@ import Control.Monad.State (MonadState, modify, get, put)
|
||||||
import Data.List
|
import Data.List
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import qualified Data.Set as Set
|
||||||
import Text.ParserCombinators.Parsec
|
import Text.ParserCombinators.Parsec
|
||||||
import Text.Regex
|
import Text.Regex
|
||||||
|
|
||||||
|
@ -1284,27 +1285,41 @@ structuredTypeField
|
||||||
pragma :: OccParser ()
|
pragma :: OccParser ()
|
||||||
pragma = do Pragma p <- genToken isPragma
|
pragma = do Pragma p <- genToken isPragma
|
||||||
m <- getPosition >>* sourcePosToMeta
|
m <- getPosition >>* sourcePosToMeta
|
||||||
case matchRegex (mkRegex "^SHARED +(.*)") p of
|
case map (flip matchRegex p . mkRegex)
|
||||||
Just [varsRaw] ->
|
["^SHARED +(.*)", "^PERMITALIASES +(.*)"] of
|
||||||
let varsRawNoComment = if "--" `isInfixOf` varsRaw
|
[Just [varsRaw], _] ->
|
||||||
then chopTrailingSpaces $ chopComment [] varsRaw
|
|
||||||
else chopTrailingSpaces varsRaw
|
|
||||||
in
|
|
||||||
mapM_ (\var ->
|
mapM_ (\var ->
|
||||||
do st <- get
|
do st <- get
|
||||||
A.Name _ n <- case lookup var (csLocalNames st) of
|
A.Name _ n <- case lookup var (csLocalNames st) of
|
||||||
Nothing -> dieP m $ "name " ++ var ++ " not defined"
|
Nothing -> dieP m $ "name " ++ var ++ " not defined"
|
||||||
Just def -> return $ fst def
|
Just def -> return $ fst def
|
||||||
modify $ \st -> st {csNameAttr = Map.insert n NameShared (csNameAttr st)})
|
modify $ \st -> st {csNameAttr = Map.insertWith Set.union
|
||||||
(splitRegex (mkRegex ",") varsRawNoComment)
|
n (Set.singleton NameShared) (csNameAttr st)})
|
||||||
Nothing -> warnP m WarnUnknownPreprocessorDirective $
|
(processVarList varsRaw)
|
||||||
|
[Nothing, Just [varsRaw]] ->
|
||||||
|
mapM_ (\var ->
|
||||||
|
do st <- get
|
||||||
|
A.Name _ n <- case lookup var (csLocalNames st) of
|
||||||
|
Nothing -> dieP m $ "name " ++ var ++ " not defined"
|
||||||
|
Just def -> return $ fst def
|
||||||
|
modify $ \st -> st {csNameAttr = Map.insertWith Set.union
|
||||||
|
n (Set.singleton NameAliasesPermitted) (csNameAttr st)})
|
||||||
|
(processVarList varsRaw)
|
||||||
|
_ -> warnP m WarnUnknownPreprocessorDirective $
|
||||||
"Unknown PRAGMA: " ++ p
|
"Unknown PRAGMA: " ++ p
|
||||||
eol
|
eol
|
||||||
where
|
where
|
||||||
|
processVarList raw = map chopBoth $
|
||||||
|
splitRegex (mkRegex ",") $ if "--" `isInfixOf` raw
|
||||||
|
then chopComment [] raw
|
||||||
|
else raw
|
||||||
|
|
||||||
chopComment prev ('-':'-':_) = prev
|
chopComment prev ('-':'-':_) = prev
|
||||||
chopComment prev (x:xs) = chopComment (prev++[x]) xs
|
chopComment prev (x:xs) = chopComment (prev++[x]) xs
|
||||||
chopComment prev [] = prev
|
chopComment prev [] = prev
|
||||||
|
|
||||||
|
chopBoth = chopLeadingSpaces . chopTrailingSpaces
|
||||||
|
chopLeadingSpaces = dropWhile (`elem` " \t")
|
||||||
chopTrailingSpaces = reverse . dropWhile (`elem` " \t") . reverse
|
chopTrailingSpaces = reverse . dropWhile (`elem` " \t") . reverse
|
||||||
|
|
||||||
isPragma (Token _ p@(Pragma {})) = Just p
|
isPragma (Token _ p@(Pragma {})) = Just p
|
||||||
|
|
Loading…
Reference in New Issue
Block a user