{-# LANGUAGE CPP, DeriveDataTypeable #-} module Language.Java.Paragon.TypeCheck.Actors where --import Data.List (intersect) import Language.Java.Paragon.Syntax import Language.Java.Paragon.Pretty import Language.Java.Paragon.Interaction import Language.Java.Paragon.Monad.Uniq #ifdef BASE4 import Data.Data #else import Data.Generics (Data(..),Typeable(..)) #endif -- An actor id is either known and unique (Fresh), or -- it is an alias of some actor. If we know statically -- which actor(s) it can represent, we list that. -- Otherwise an empty list means it could be an alias -- of any other actor. data ActorId = Fresh Int String | Alias Int | ActorTPVar (Ident ()) deriving (Show, Eq, Ord, Data, Typeable) instance Pretty ActorId where pretty (Fresh k s) = text s <> text ('#':show k) pretty (Alias k) = text ('@':show k) pretty (ActorTPVar i) = pretty i infix 5 `unifies`, `unify` -- Precondition: No ActorTPVars unifies :: ActorId -> ActorId -> Bool -- If we have the exact (fresh) ids, we can tell exactly unifies (Fresh x _) (Fresh y _) = x == y unifies _ _ = True -- If either side is an alias, check if it could represent the fresh side. --unifies (Alias x xs) (Fresh y) = null xs || y `elem` xs --unifies (Fresh x) (Alias y ys) = null ys || x `elem` ys -- If both are aliases, check if they could represent the same fresh actor. --unifies (Alias x xs) (Alias y ys) = null xs || null ys || (not . null) (xs `intersect` ys) unify :: [ActorId] -> [ActorId] -> Bool unify xs ys = all (uncurry unifies) $ zip xs ys {- equals :: ActorId -> ActorId -> Bool equals (Fresh x) (Fresh y) = x == y equals (Alias x _) (Alias y _) = x == y equals _ _ = False reprs :: ActorId -> [Int] reprs (Fresh x) = [x] reprs (Alias x xs) = x:xs -} getId :: ActorId -> Int getId (Fresh x _) = x getId (Alias x ) = x getId _ = panic "getId" "Trying to get ActorId of ActorTPVar, which should have been instantiated" {- reprName :: ActorId -> Name reprName (Fresh _ n) = n reprName (Alias _ _ n) = n -} newAlias :: Uniq -> IO ActorId newAlias u = do uniq <- getUniq u return $ Alias uniq newFresh :: Uniq -> String -> IO ActorId newFresh u str = do uniq <- getUniq u return $ Fresh uniq str