{-#LANGUAGE CPP#-}
module Foreign.Storable.Generic.Plugin.Internal.Helpers where
import CoreSyn (Bind(..),Expr(..), CoreExpr, CoreBind, CoreProgram, Alt)
import Literal (Literal(..))
import Id (isLocalId, isGlobalId,Id)
import Var (Var(..))
#if MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
import Var (TyVarBinder(..), VarBndr(..))
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
import Var (TyVarBndr(..), TyVarBinder)
#endif
import Name (getOccName,mkOccName)
import OccName (OccName(..), occNameString)
import qualified Name as N (varName)
import SrcLoc (noSrcSpan)
import Unique (getUnique)
import HscMain (hscCompileCoreExpr)
import HscTypes (HscEnv,ModGuts(..))
import CoreMonad (CoreM,CoreToDo(..), getHscEnv)
import BasicTypes (CompilerPhase(..))
import Type (isAlgType, splitTyConApp_maybe)
import TyCon (algTyConRhs, visibleDataCons)
#if MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
import TyCoRep (Type(..), TyBinder(..), TyCoBinder(..))
#else
import TyCoRep (Type(..), TyBinder(..))
#endif
import TysWiredIn (intDataCon)
import DataCon (dataConWorkId,dataConOrigArgTys)
import MkCore (mkWildValBinder)
import Outputable (cat, ppr, SDoc, showSDocUnsafe)
import CoreMonad (putMsg, putMsgS)
import GHCi.RemoteTypes
import Unsafe.Coerce
import Data.List
import Data.Maybe
import Data.Either
import Control.Monad.IO.Class
import Var
getIdsBind :: CoreBind -> [Id]
getIdsBind (NonRec id _) = [id]
getIdsBind (Rec recs) = map fst recs
getExprsBind :: CoreBind -> [CoreExpr]
getExprsBind (NonRec _ e) = [e]
getExprsBind (Rec recs) = map snd recs
getIdsExprsBind :: CoreBind -> [(Id,CoreExpr)]
getIdsExprsBind (NonRec id expr) = [(id,expr)]
getIdsExprsBind (Rec recs) = recs
getIdsExpr :: CoreExpr -> [Id]
getIdsExpr (Var id) = [id]
getIdsExpr (App e1 e2) = concat [getIdsExpr e1, getIdsExpr e2]
getIdsExpr (Lam id e) = id : getIdsExpr e
getIdsExpr (Let bs e) = concat [getIdsExpr e, concatMap getIdsExpr (getExprsBind bs)]
getIdsExpr (Case e _ _ alts) = concat $ getIdsExpr e : map (\(_,_,e_c) -> getIdsExpr e_c) alts
getIdsExpr (Cast e _) = getIdsExpr e
getIdsExpr _ = []
cutOccName :: Int -> OccName -> OccName
cutOccName n occ_name = mkOccName (occNameSpace occ_name) name_string
where name_string = take n $ occNameString occ_name
eqType :: Type -> Type -> Bool
eqType (TyVarTy v1) (TyVarTy v2) = v1 == v2
eqType (AppTy t1a t1b) (AppTy t2a t2b) = t1a `eqType` t2a && t1b `eqType` t2b
eqType (TyConApp tc1 ts1) (TyConApp tc2 ts2) = tc1 == tc2 && (and $ zipWith eqType ts1 ts2)
#if MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
eqType (ForAllTy tb1 t1) (ForAllTy tb2 t2) = tb1 `eqTyVarBind` tb2 && t1 `eqType` t2
#else
eqType (ForAllTy tb1 t1) (ForAllTy tb2 t2) = tb1 `eqTyBind` tb2 && t1 `eqType` t2
#endif
eqType _ _ = False
eqTyBind :: TyBinder -> TyBinder -> Bool
#if MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
eqTyBind (Named tvb1) (Named tvb2) = tvb1 `eqTyVarBind` tvb2
#else
eqTyBind (Named t1 vis1) (Named t2 vis2) = t1 == t2 && vis1 == vis2
#endif
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
eqTyBind (Anon _ t1) (Anon _ t2) = t1 `eqType` t2
#else
eqTyBind (Anon t1) (Anon t2) = t1 `eqType` t2
#endif
eqTyBind _ _ = False
#if MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
eqTyVarBind :: TyVarBinder -> TyVarBinder -> Bool
eqTyVarBind (Bndr t1 arg1) (Bndr t2 arg2) = t1 == t2
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
eqTyVarBind :: TyVarBinder -> TyVarBinder -> Bool
eqTyVarBind (TvBndr t1 arg1) (TvBndr t2 arg2) = t1 == t2
#endif
elemType :: Type -> [Type] -> Bool
elemType t [] = False
elemType t (ot:ts) = (t `eqType` ot) || elemType t ts
#if MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
isProxy :: TyCoVarBinder -> Bool
isProxy (Bndr tycovar flag)
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
isProxy :: TyVarBinder -> Bool
isProxy (TvBndr tycovar flag)
#else
isProxy :: TyBinder -> Bool
isProxy (Anon t) = False
isProxy (Named tycovar flag)
#endif
| isTyCoVar tycovar
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
, FunTy _ bool star <- varType tycovar
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
, FunTy bool star <- varType tycovar
#else
, ForAllTy bool star <- varType tycovar
#endif
= True
| otherwise = False
removeProxy :: Type -> Type
removeProxy t
| ForAllTy fall t1 <- t
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
, FunTy _ ch t2 <- t1
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
, FunTy ch t2 <- t1
#else
, ForAllTy ch' t2 <- t
, Anon ch <- ch'
#endif
, AppTy pr bl <- ch
, TyConApp _ _ <- bl
, isProxy fall
= t2
| ForAllTy fall f2 <- t
, ForAllTy b t1 <- f2
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
, FunTy _ ch t2 <- t1
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
, FunTy ch t2 <- t1
#else
, ForAllTy ch' t2 <- t
, Anon ch <- ch'
#endif
, AppTy pr bl <- ch
, TyConApp _ _ <- bl
, isProxy fall
= ForAllTy b t2
| ForAllTy b f2 <- t
, ForAllTy fall t1 <- f2
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
, FunTy _ ch t2 <- t1
#elif MIN_VERSION_GLASGOW_HASKELL(8,2,1,0)
, FunTy ch t2 <- t1
#else
, ForAllTy ch' t2 <- t
, Anon ch <- ch'
#endif
, AppTy pr bl <- ch
, TyConApp _ _ <- bl
, isProxy fall
= ForAllTy b t2
| otherwise
= t