Add expr_uses_binders predicate.
[matthijs/master-project/cλash.git] / cλash / CLasH / Utils / Core / CoreTools.hs
index e0a5c11187fc4c8b3f63f42192f859b11519a5da..05366fc2204add144909d94564375114118a86dc 100644 (file)
@@ -1,3 +1,4 @@
+{-# LANGUAGE PatternGuards #-}
 -- | This module provides a number of functions to find out things about Core
 -- programs. This module does not provide the actual plumbing to work with
 -- Core and Haskell (it uses HsTools for this), but only the functions that
@@ -19,6 +20,8 @@ import qualified HscTypes
 import qualified RdrName
 import qualified Name
 import qualified OccName
+import qualified Type
+import qualified TyCon
 import qualified TysWiredIn
 import qualified Bag
 import qualified DynFlags
@@ -45,7 +48,7 @@ eval_tfp_int env ty =
     -- Automatically import modules for any fully qualified identifiers
     setDynFlag DynFlags.Opt_ImplicitImportQualified
 
-    let from_int_t_name = mkRdrName "Types.Data.Num" "fromIntegerT"
+    let from_int_t_name = mkRdrName "Types.Data.Num.Ops" "fromIntegerT"
     let from_int_t = SrcLoc.noLoc $ HsExpr.HsVar from_int_t_name
     let undef = hsTypedUndef $ coreToHsType ty
     let app = SrcLoc.noLoc $ HsExpr.HsApp (from_int_t) (undef)
@@ -183,6 +186,10 @@ has_free_tyvars = not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars Var.isT
 has_free_vars :: CoreSyn.CoreExpr -> Bool
 has_free_vars = not . VarSet.isEmptyVarSet . CoreFVs.exprFreeVars
 
+-- Does the given expression use any of the given binders?
+expr_uses_binders :: [CoreSyn.CoreBndr] -> CoreSyn.CoreExpr -> Bool
+expr_uses_binders bndrs = not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))
+
 -- Turns a Var CoreExpr into the Id inside it. Will of course only work for
 -- simple Var CoreExprs, not complexer ones.
 exprToVar :: CoreSyn.CoreExpr -> Var.Id
@@ -211,3 +218,35 @@ getLiterals app@(CoreSyn.App _ _) = literals
   where
     (CoreSyn.Var f, args) = CoreSyn.collectArgs app
     literals = filter (is_lit) args
+
+reduceCoreListToHsList :: CoreSyn.CoreExpr -> [CoreSyn.CoreExpr]
+reduceCoreListToHsList app@(CoreSyn.App _ _) = out
+  where
+    (fun, args) = CoreSyn.collectArgs app
+    len = length args
+    out = case len of
+          3 -> ((args!!1) : (reduceCoreListToHsList (args!!2)))
+          otherwise -> []
+
+reduceCoreListToHsList _ = []
+
+-- | Is the given type a State type?
+isStateType :: Type.Type -> Bool
+-- Resolve any type synonyms remaining
+isStateType ty | Just ty' <- Type.tcView ty = isStateType ty'
+isStateType ty  = Maybe.isJust $ do
+  -- Split the type. Don't use normal splitAppTy, since that looks through
+  -- newtypes, and we want to see the State newtype.
+  (typef, _) <- Type.repSplitAppTy_maybe ty
+  -- See if the applied type is a type constructor
+  (tycon, _) <- Type.splitTyConApp_maybe typef
+  if TyCon.isNewTyCon tycon && Name.getOccString tycon == "State"
+    then
+      Just ()
+    else
+      Nothing
+
+-- | Does the given expression have a State type?
+hasStateType :: CoreSyn.CoreExpr -> Bool
+hasStateType (CoreSyn.Type _) = False
+hasStateType expr = (isStateType . CoreUtils.exprType) expr