Navigation Menu

Skip to content
This repository has been archived by the owner on Feb 3, 2021. It is now read-only.

Commit

Permalink
brute force attempt to switch from Object to Mu
Browse files Browse the repository at this point in the history
  • Loading branch information
moritz committed Apr 10, 2012
1 parent 2512b2d commit 6e7c146
Show file tree
Hide file tree
Showing 8 changed files with 28 additions and 28 deletions.
2 changes: 1 addition & 1 deletion MetaObject/src/MO/Util/C3.hs
Expand Up @@ -114,7 +114,7 @@ main = do
data Object =
data Mu =
O | A | B | C | D | E | F | G | H | I | J | K | K1 | K2 | K3 | X | Y | Z
deriving (Eq, Show)
Expand Down
2 changes: 1 addition & 1 deletion Pugs/src/Pugs/AST/Internals.hs
Expand Up @@ -489,7 +489,7 @@ valType (VSubst _) = mkType "Subst"
valType (VMatch _) = mkType "Match"
valType (VType t) = t
valType (VObject o) = objType o
valType (VOpaque _) = mkType "Object"
valType (VOpaque _) = mkType "Mu"
valType (PerlSV _) = mkType "Scalar::Perl5"
valType (VV _) = mkType "Scalar::Perl5" -- (cast $ Val.valMeta v)

Expand Down
4 changes: 2 additions & 2 deletions Pugs/src/Pugs/Eval/Var.hs
Expand Up @@ -223,7 +223,7 @@ findSub _var _invs _args
-- has been reduced.)
return . Just $ mkPrim
{ subName = methName
, subParams = makeParams ["Object", "List", "Named"]
, subParams = makeParams ["Mu", "List", "Named"]
, subReturns = mkType "Any"
, subBody = Prim $ \(inv:named:pos:_) -> do
invVV <- fromVal inv :: Eval Val.Val
Expand Down Expand Up @@ -263,7 +263,7 @@ findSub _var _invs _args
attrs <- fmap (fmap (filter (/= pkg) . nub)) $ findAttrs pkg
if isNothing attrs || null (fromJust attrs) then fmap (err NoMatchingMulti) (findSub' var) else do
-- XXX - "reverse" below is a crude hack before we have C3 dispatch;
-- - this is such that "class X is Object is Moose" can dispatch with Moose first.
-- - this is such that "class X is Mu is Moose" can dispatch with Moose first.
(`fix` (reverse $ fromJust attrs)) $ \run pkgs -> do
if null pkgs then return (Left $ NoSuchMethod (cast pkg)) else do
subs <- findWithPkg (head pkgs) var
Expand Down
2 changes: 1 addition & 1 deletion Pugs/src/Pugs/Parser.hs
Expand Up @@ -290,7 +290,7 @@ rulePackageHead = do
"grammar" -> "Grammar"
_ -> fail "bug"
mixinRoles = nub ([ cls | ("does", cls) <- traits])
parentClasses = nub ("Object":[ cls | ("is", cls) <- traits, cls /= "also" ])
parentClasses = nub ("Mu":[ cls | ("is", cls) <- traits, cls /= "also" ])
case () of
_ | elem name parentClasses -> do
return (Left $ "Circular class inheritance detected for " ++ sym ++ " '" ++ name ++ "'")
Expand Down
34 changes: 17 additions & 17 deletions Pugs/src/Pugs/Prim.hs
Expand Up @@ -693,7 +693,7 @@ op1 "Pugs::Internals::emit_yaml" = \v -> do
glob <- filterPrim =<< asks envGlobal
yml <- io $ showYaml (filterUserDefinedPad glob, v)
return $ VStr yml
op1 "Object::HOW" = \v -> do
op1 "Mu::HOW" = \v -> do
typ <- evalValType v
evalExp $ _Var (':':'*':showType typ)
op1 "Class::name" = \v -> do
Expand Down Expand Up @@ -1313,7 +1313,7 @@ op3 "split" = op3Split
op3 "Str::split" = \x y z -> do
op3 "split" y x z
op3 "HOW::new" = \t n p -> do
cls <- op3 "Object::new" t n p
cls <- op3 "Mu::new" t n p
meta <- readRef =<< fromVal cls
fetch <- doHash meta hash_fetchVal

Expand All @@ -1337,7 +1337,7 @@ op3 "HOW::new" = \t n p -> do

return cls

op3 "Object::new" = \t n p -> do
op3 "Mu::new" = \t n p -> do
positionals <- fromVal p
typ <- fromVal t
named <- fromVal n
Expand All @@ -1358,7 +1358,7 @@ op3 "Object::new" = \t n p -> do
-- Register finalizers by keeping weakrefs somehow
setFinalization obj

op3 "Object::clone" = \t n _ -> do
op3 "Mu::clone" = \t n _ -> do
named <- fromVal n
(VObject o) <- fromVal t
attrs <- readIVar (IHash $ objAttrs o)
Expand Down Expand Up @@ -2066,10 +2066,10 @@ initSyms = seq (length syms) $ do
\\n Bool pre flush unsafe (IO)\
\\n Bool pre IO::close unsafe,export (IO:)\
\\n Bool pre Socket::close unsafe,export (Socket:)\
\\n Bool pre die safe (?Object)\
\\n Bool pre die safe (?Mu)\
\\n Bool pre warn safe (List)\
\\n Bool pre fail_ safe (?Object)\
\\n Bool pre fail safe (?Object)\
\\n Bool pre fail_ safe (?Mu)\
\\n Bool pre fail safe (?Mu)\
\\n Socket pre listen unsafe (Int)\
\\n Socket pre connect unsafe (Str, Int)\
\\n Any pre accept unsafe (Any)\
Expand Down Expand Up @@ -2198,8 +2198,8 @@ initSyms = seq (length syms) $ do
\\n Str pre chr safe (Int)\
\\n Int pre ord safe (Str)\
\\n Str pre oct safe (Str)\
\\n Object pre stat unsafe (Str)\
\\n Object pre lstat unsafe (Str)\
\\n Mu pre stat unsafe (Str)\
\\n Mu pre lstat unsafe (Str)\
\\n Int pre from safe (Match)\
\\n Int pre to safe (Match)\
\\n List pre matches safe (Match)\
Expand All @@ -2212,17 +2212,17 @@ initSyms = seq (length syms) $ do
\\n Int pre sign safe (Num)\
\\n Bool pre kill safe (Thread)\
\\n Int pre kill unsafe (Int, List)\
\\n Object pre Object::new safe,export (Object: Named)\
\\n Object pre BUILDALL safe (Object)\
\\n Object pre DESTROYALL safe (Object)\
\\n Mu pre Mu::new safe,export (Mu: Named)\
\\n Mu pre BUILDALL safe (Mu)\
\\n Mu pre DESTROYALL safe (Mu)\
\\n Code pre TEMP safe (rw!Any)\
\\n Object pre Object::clone safe (Object: Named)\
\\n Class pre Object::HOW safe,export (Object)\
\\n Object pre HOW::new safe (Object: Named)\
\\n Object pre HOW::does safe (Object: List)\
\\n Mu pre Mu::clone safe (Mu: Named)\
\\n Class pre Mu::HOW safe,export (Mu)\
\\n Mu pre HOW::new safe (Mu: Named)\
\\n Mu pre HOW::does safe (Mu: List)\
\\n Str pre Class::name safe (Class)\
\\n Hash pre Class::traits safe (Class)\
\\n Object pre WHICH safe (Any)\
\\n Mu pre WHICH safe (Any)\
\\n Int pre Rat::numerator safe (Rat:)\
\\n Int pre Rat::denominator safe (Rat:)\
\\n Bool pre Thread::yield safe (Thread)\
Expand Down
6 changes: 3 additions & 3 deletions Pugs/src/Pugs/Prim/Yaml.hs
Expand Up @@ -37,8 +37,8 @@ fromYaml MkNode{n_elem=EMap nodes, n_tag=tag} = do
return (key, val)
hv <- io $ (H.fromList H.hashString vals :: IO IHash)
return $ VRef (hashRef hv)
Just s | (pre, post) <- Str.splitAt 16 s -- 16 == length "tag:pugs:Object:"
, pre == packBuf "tag:pugs:Object:" -> do
Just s | (pre, post) <- Str.splitAt 16 s -- 16 == length "tag:pugs:Mu:"
, pre == packBuf "tag:pugs:Mu:" -> do
let typ = unpackBuf post
vals <- forM nodes $ \(keyNode, valNode) -> do
key <- fromVal =<< fromYaml keyNode
Expand Down Expand Up @@ -110,7 +110,7 @@ toYaml v@(VObject obj) = do
-- parens, which is, of course, wrong.
hash <- fromVal v :: Eval VHash
attrs <- toYaml $ VRef (hashRef hash)
return $ tagNode (Just $ packBuf $ "tag:pugs:Object:" ++ showType (objType obj)) attrs
return $ tagNode (Just $ packBuf $ "tag:pugs:Mu:" ++ showType (objType obj)) attrs
toYaml (VRule MkRulePGE{rxRule=rule, rxGlobal=global, rxStringify=stringify, rxAdverbs=adverbs}) = do
adverbs' <- toYaml adverbs
return . mkTagNode "tag:pugs:Rule" $ EMap
Expand Down
4 changes: 2 additions & 2 deletions Pugs/src/Pugs/Types.hs
Expand Up @@ -827,7 +827,7 @@ e.g.
will produce the list of types
@
Any, Void, Object, Scalar, Complex, Num
Any, Void, Mu, Scalar, Complex, Num
@
This function does /not/ expect to be given junctive types.
Expand Down Expand Up @@ -865,7 +865,7 @@ initTreeCount :: Int
initTreeCount = countTree initTree

rawTree :: Tree ID
rawTree = fmap cast $! Node "Object"
rawTree = fmap cast $! Node "Mu"
[ Node "Any"
[ Node "Item"
[ Node "List"
Expand Down
2 changes: 1 addition & 1 deletion Pugs/src/Pugs/Val.hs
Expand Up @@ -35,7 +35,7 @@ itemVal :: Val -> Eval Val
itemVal = return

valMeta :: Val -> PureStr
valMeta _ = cast "Object"
valMeta _ = cast "Mu"

valShow :: Val -> PureStr
valShow _ = cast "<opaque>"
Expand Down

0 comments on commit 6e7c146

Please sign in to comment.