Skip to content

Commit

Permalink
WIP: moving
Browse files Browse the repository at this point in the history
  • Loading branch information
Ptival committed Oct 12, 2023
1 parent eeb4f45 commit 7c1bcbe
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 17 deletions.
22 changes: 11 additions & 11 deletions src/Reopt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -369,7 +369,7 @@ import Text.Printf (printf)

import Control.Monad.Extra (concatForM, concatMapM)
import Data.Macaw.CFG qualified as Macaw
import Debug.Trace (trace, traceM)
import Debug.Trace (trace)
import Reopt.ELFArchInfo (
InitDiscM,
ProcessPLTEntries,
Expand Down Expand Up @@ -2661,19 +2661,19 @@ reoptRecoveryLoop symAddrMap rOpts funPrefix sysp debugTypeMap firstDiscState =
(roTraceUnification rOpts)
(roTraceConstraintOrigins rOpts)

traceM "\nmcFunTypes:"
forM_ (Map.assocs (mcFunTypes moduleConstraints)) $ \a -> do
traceM $ show a
-- traceM "\nmcFunTypes:"
-- forM_ (Map.assocs (mcFunTypes moduleConstraints)) $ \a -> do
-- traceM $ show a

traceM "\nmcTypeMap:"
forM_ (Map.assocs (mcTypeMap moduleConstraints)) $ \a -> do
traceM $ show $ PP.pretty a
-- traceM "\nmcTypeMap:"
-- forM_ (Map.assocs (mcTypeMap moduleConstraints)) $ \a -> do
-- traceM $ show $ PP.pretty a

traceM "\nmcAssignTyVars:"
forM_ (Map.assocs (mcAssignTyVars moduleConstraints)) $ \a -> do
traceM $ show a
-- traceM "\nmcAssignTyVars:"
-- forM_ (Map.assocs (mcAssignTyVars moduleConstraints)) $ \a -> do
-- traceM $ show a

traceM "?"
-- traceM "?"

-- Search for new candidate function entry points
let allBlocks = concatMap fnBlocks (recoveredDefs recMod)
Expand Down
5 changes: 2 additions & 3 deletions src/Reopt/TypeInference/ConstraintGen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,6 @@ import Data.Parameterized (FoldableF, FoldableFC)
import Data.Parameterized.NatRepr (NatRepr, intValue, testEquality, widthVal)
import Data.Parameterized.Some (Some (Some), viewSome)
import Data.Parameterized.TraversableFC (toListFC)
import Debug.Trace (traceM)
import Reopt.CFG.FnRep (
FnArchConstraints,
FnArchStmt,
Expand Down Expand Up @@ -815,7 +814,7 @@ genCall ::
Maybe (Some FnReturnVar) ->
CGenM CGenBlockContext arch ()
genCall fn args m_ret = do
traceM $ "genCall: " <> show fn
-- traceM $ "genCall: " <> show fn
m_ftyp <- functionTypeTyVars fn

case m_ftyp of
Expand All @@ -828,7 +827,7 @@ genCall fn args m_ret = do
++ ")"
)
Just ftyp -> do
traceM $ "Found type: " <> show ftyp
-- traceM $ "Found type: " <> show ftyp
-- Arguments
zipWithM_ go args (fttvArgs ftyp)

Expand Down
2 changes: 1 addition & 1 deletion src/Reopt/TypeInference/HeaderTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ instance PP.Pretty AnnFunType where
[ PP.pretty (funRet fty)
, PP.space
, "("
, PP.hcat (PP.punctuate PP.comma (map PP.pretty (V.toList (funArgs fty))))
, PP.hcat (PP.punctuate (PP.comma <> PP.space) (map PP.pretty (V.toList (funArgs fty))))
, ")"
]

Expand Down
9 changes: 7 additions & 2 deletions src/Reopt/TypeInference/Solver/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,13 +135,18 @@ instance PP.Pretty ITy where
VarTy v -> PP.pretty v
ITy ty -> PP.pretty ty

-- | Prints `args` as "arg1, arg2, ..."
ppArgList :: PP.Pretty a => [a] -> PP.Doc ann
ppArgList args =
PP.hcat (PP.punctuate (PP.comma <> PP.space) (map PP.pretty args))

instance (PP.Pretty f, PP.Pretty rv) => PP.Pretty (TyF rv f) where
pretty = \case
NumTy sz -> "i" <> PP.pretty sz
PtrTy t -> "ptr " <> PP.pretty t
UnknownFunPtrTy -> "? (???)*"
PreFunPtrTy args ret -> PP.pretty ret <> " (" <> PP.hcat (PP.punctuate PP.comma (map PP.pretty args)) <> ", ...?)*"
FunPtrTy args ret -> PP.pretty ret <> " (" <> PP.hcat (PP.punctuate PP.comma (map PP.pretty args)) <> ")*"
PreFunPtrTy args ret -> PP.pretty ret <> " (" <> ppArgList args <> ", ...?)*"
FunPtrTy args ret -> PP.pretty ret <> " (" <> ppArgList args <> ")*"
ConflictTy n -> "![" <> PP.pretty n <> "]"
TupleTy ts -> PP.tupled (map PP.pretty ts)
VecTy n ty -> "< " <> PP.pretty n <> " x " <> PP.pretty ty <> " >"
Expand Down

0 comments on commit 7c1bcbe

Please sign in to comment.