diff --git a/compiler/GHC/Builtin/Types.hs b/compiler/GHC/Builtin/Types.hs index 7dceb6524e01c605646aac5f7eefff5e8b9f2fae..240b6eb7b35585e1df1d84909622287ecc223ed8 100644 --- a/compiler/GHC/Builtin/Types.hs +++ b/compiler/GHC/Builtin/Types.hs @@ -1636,10 +1636,11 @@ boxedRepDataCon = pcSpecialDataCon boxedRepDataConName where -- See Note [Getting from RuntimeRep to PrimRep] in RepType prim_rep_fun [lev] - = case tyConPromDataConInfo (tyConAppTyCon lev) of - Levity Lifted -> [LiftedRep] - Levity Unlifted -> [UnliftedRep] - _ -> pprPanic "boxedRepDataCon" (ppr lev) + = case tyConAppTyCon_maybe lev of + Just tc -> case tyConPromDataConInfo tc of + Levity l -> [BoxedRep (Just l)] + _ -> [BoxedRep Nothing] + Nothing -> [BoxedRep Nothing] prim_rep_fun args = pprPanic "boxedRepDataCon" (ppr args) diff --git a/compiler/GHC/Cmm/Utils.hs b/compiler/GHC/Cmm/Utils.hs index 0378eaa99ef8c5ffd9015cb1c8b04c19640b56b0..e0de7e7cc5ab37df7c242cc5604db1558ec64711 100644 --- a/compiler/GHC/Cmm/Utils.hs +++ b/compiler/GHC/Cmm/Utils.hs @@ -98,8 +98,7 @@ import GHC.Cmm.Dataflow.Collections primRepCmmType :: Platform -> PrimRep -> CmmType primRepCmmType platform = \case VoidRep -> panic "primRepCmmType:VoidRep" - LiftedRep -> gcWord platform - UnliftedRep -> gcWord platform + BoxedRep _ -> gcWord platform IntRep -> bWord platform WordRep -> bWord platform Int8Rep -> b8 @@ -142,8 +141,7 @@ typeCmmType platform ty = primRepCmmType platform (typePrimRep1 ty) primRepForeignHint :: PrimRep -> ForeignHint primRepForeignHint VoidRep = panic "primRepForeignHint:VoidRep" -primRepForeignHint LiftedRep = AddrHint -primRepForeignHint UnliftedRep = AddrHint +primRepForeignHint (BoxedRep _) = AddrHint primRepForeignHint IntRep = SignedHint primRepForeignHint Int8Rep = SignedHint primRepForeignHint Int16Rep = SignedHint diff --git a/compiler/GHC/Core/TyCon.hs b/compiler/GHC/Core/TyCon.hs index ccee17ab307d45e4b5c993a5b6ac9978e3c6425c..3aa17fe0b6aa2d25fde2296f8545099657cfd224 100644 --- a/compiler/GHC/Core/TyCon.hs +++ b/compiler/GHC/Core/TyCon.hs @@ -124,7 +124,7 @@ module GHC.Core.TyCon( tyConRepModOcc, -- * Primitive representations of Types - PrimRep(..), PrimElemRep(..), + PrimRep(..), PrimElemRep(..), Levity(..), primElemRepToPrimRep, isVoidRep, isGcPtrRep, primRepSizeB, @@ -1536,8 +1536,7 @@ See Note [RuntimeRep and PrimRep] in GHC.Types.RepType. -- "GHC.Types.RepType" and Note [VoidRep] in "GHC.Types.RepType". data PrimRep = VoidRep - | LiftedRep - | UnliftedRep -- ^ Unlifted pointer + | BoxedRep {-# UNPACK #-} !(Maybe Levity) -- ^ Boxed, heap value | Int8Rep -- ^ Signed, 8-bit value | Int16Rep -- ^ Signed, 16-bit value | Int32Rep -- ^ Signed, 32-bit value @@ -1548,7 +1547,7 @@ data PrimRep | Word32Rep -- ^ Unsigned, 32 bit value | Word64Rep -- ^ Unsigned, 64 bit value | WordRep -- ^ Unsigned, word-sized value - | AddrRep -- ^ A pointer, but /not/ to a Haskell value (use '(Un)liftedRep') + | AddrRep -- ^ A pointer, but /not/ to a Haskell value (use 'BoxedRep') | FloatRep | DoubleRep | VecRep Int PrimElemRep -- ^ A vector @@ -1575,42 +1574,47 @@ instance Outputable PrimElemRep where instance Binary PrimRep where put_ bh VoidRep = putByte bh 0 - put_ bh LiftedRep = putByte bh 1 - put_ bh UnliftedRep = putByte bh 2 - put_ bh Int8Rep = putByte bh 3 - put_ bh Int16Rep = putByte bh 4 - put_ bh Int32Rep = putByte bh 5 - put_ bh Int64Rep = putByte bh 6 - put_ bh IntRep = putByte bh 7 - put_ bh Word8Rep = putByte bh 8 - put_ bh Word16Rep = putByte bh 9 - put_ bh Word32Rep = putByte bh 10 - put_ bh Word64Rep = putByte bh 11 - put_ bh WordRep = putByte bh 12 - put_ bh AddrRep = putByte bh 13 - put_ bh FloatRep = putByte bh 14 - put_ bh DoubleRep = putByte bh 15 - put_ bh (VecRep n per) = putByte bh 16 *> put_ bh n *> put_ bh per + put_ bh (BoxedRep ml) = case ml of + -- cheaper storage of the levity than using + -- the Binary (Maybe Levity) instance + Nothing -> putByte bh 1 + Just Lifted -> putByte bh 2 + Just Unlifted -> putByte bh 3 + put_ bh Int8Rep = putByte bh 4 + put_ bh Int16Rep = putByte bh 5 + put_ bh Int32Rep = putByte bh 6 + put_ bh Int64Rep = putByte bh 7 + put_ bh IntRep = putByte bh 8 + put_ bh Word8Rep = putByte bh 9 + put_ bh Word16Rep = putByte bh 10 + put_ bh Word32Rep = putByte bh 11 + put_ bh Word64Rep = putByte bh 12 + put_ bh WordRep = putByte bh 13 + put_ bh AddrRep = putByte bh 14 + put_ bh FloatRep = putByte bh 15 + put_ bh DoubleRep = putByte bh 16 + put_ bh (VecRep n per) = putByte bh 17 *> put_ bh n *> put_ bh per get bh = do h <- getByte bh case h of 0 -> pure VoidRep - 1 -> pure LiftedRep - 2 -> pure UnliftedRep - 3 -> pure Int8Rep - 4 -> pure Int16Rep - 5 -> pure Int32Rep - 6 -> pure Int64Rep - 7 -> pure IntRep - 8 -> pure Word8Rep - 9 -> pure Word16Rep - 10 -> pure Word32Rep - 11 -> pure Word64Rep - 12 -> pure WordRep - 13 -> pure AddrRep - 14 -> pure FloatRep - 15 -> pure DoubleRep - 16 -> VecRep <$> get bh <*> get bh + 1 -> pure $ BoxedRep Nothing + 2 -> pure $ BoxedRep (Just Lifted) + 3 -> pure $ BoxedRep (Just Unlifted) + 4 -> pure Int8Rep + 5 -> pure Int16Rep + 6 -> pure Int32Rep + 7 -> pure Int64Rep + 8 -> pure IntRep + 9 -> pure Word8Rep + 10 -> pure Word16Rep + 11 -> pure Word32Rep + 12 -> pure Word64Rep + 13 -> pure WordRep + 14 -> pure AddrRep + 15 -> pure FloatRep + 16 -> pure DoubleRep + 17 -> VecRep <$> get bh <*> get bh _ -> pprPanic "Binary:PrimRep" (int (fromIntegral h)) instance Binary PrimElemRep where @@ -1622,9 +1626,8 @@ isVoidRep VoidRep = True isVoidRep _other = False isGcPtrRep :: PrimRep -> Bool -isGcPtrRep LiftedRep = True -isGcPtrRep UnliftedRep = True -isGcPtrRep _ = False +isGcPtrRep (BoxedRep _) = True +isGcPtrRep _ = False -- A PrimRep is compatible with another iff one can be coerced to the other. -- See Note [Bad unsafe coercion] in GHC.Core.Lint for when are two types coercible. @@ -1665,8 +1668,7 @@ primRepSizeB platform = \case FloatRep -> fLOAT_SIZE DoubleRep -> dOUBLE_SIZE AddrRep -> platformWordSizeInBytes platform - LiftedRep -> platformWordSizeInBytes platform - UnliftedRep -> platformWordSizeInBytes platform + BoxedRep _ -> platformWordSizeInBytes platform VoidRep -> 0 (VecRep len rep) -> len * primElemRepSizeB platform rep diff --git a/compiler/GHC/Stg/Syntax.hs b/compiler/GHC/Stg/Syntax.hs index 23ac20e9ee0f1fe2eadb645f0bdc33bfc5b89b94..49a3de1609693ce2bd95cdd33e58d7d75f340cd5 100644 --- a/compiler/GHC/Stg/Syntax.hs +++ b/compiler/GHC/Stg/Syntax.hs @@ -174,10 +174,9 @@ isDllConApp platform ext_dyn_refs this_mod con args -- -- The coercion argument here gets VoidRep isAddrRep :: PrimRep -> Bool -isAddrRep AddrRep = True -isAddrRep LiftedRep = True -isAddrRep UnliftedRep = True -isAddrRep _ = False +isAddrRep AddrRep = True +isAddrRep (BoxedRep _) = True -- FIXME: not true for JavaScript +isAddrRep _ = False -- | Type of an @StgArg@ -- diff --git a/compiler/GHC/StgToByteCode.hs b/compiler/GHC/StgToByteCode.hs index 94a0f457708026919eefa3d1eaa8155633bed72c..c85f66528ac5a8ab357f1f97a08f23c6d97fd681 100644 --- a/compiler/GHC/StgToByteCode.hs +++ b/compiler/GHC/StgToByteCode.hs @@ -1603,8 +1603,7 @@ primRepToFFIType platform r AddrRep -> FFIPointer FloatRep -> FFIFloat DoubleRep -> FFIDouble - LiftedRep -> FFIPointer - UnliftedRep -> FFIPointer + BoxedRep _ -> FFIPointer _ -> pprPanic "primRepToFFIType" (ppr r) where (signed_word, unsigned_word) = case platformWordSize platform of @@ -1629,9 +1628,8 @@ mkDummyLiteral platform pr AddrRep -> LitNullAddr DoubleRep -> LitDouble 0 FloatRep -> LitFloat 0 - LiftedRep -> LitNullAddr - UnliftedRep -> LitNullAddr - _ -> pprPanic "mkDummyLiteral" (ppr pr) + BoxedRep _ -> LitNullAddr + _ -> pprPanic "mkDummyLiteral" (ppr pr) -- Convert (eg) diff --git a/compiler/GHC/StgToCmm/ArgRep.hs b/compiler/GHC/StgToCmm/ArgRep.hs index 9db0ed7afcf44059ff0563ad15e11081862ad2c2..773195b6db43e6ed9e32515841e444930829f928 100644 --- a/compiler/GHC/StgToCmm/ArgRep.hs +++ b/compiler/GHC/StgToCmm/ArgRep.hs @@ -69,8 +69,7 @@ argRepString V64 = "V64" toArgRep :: Platform -> PrimRep -> ArgRep toArgRep platform rep = case rep of VoidRep -> V - LiftedRep -> P - UnliftedRep -> P + BoxedRep _ -> P IntRep -> N WordRep -> N Int8Rep -> N -- Gets widened to native word width for calls diff --git a/compiler/GHC/StgToCmm/Lit.hs b/compiler/GHC/StgToCmm/Lit.hs index ac45c7af33f752437cead20efa68375d26e7cfea..3615e65d489adc0b7371139c98bb70bbf36b9ae3 100644 --- a/compiler/GHC/StgToCmm/Lit.hs +++ b/compiler/GHC/StgToCmm/Lit.hs @@ -53,8 +53,7 @@ cgLit (LitString s) = cgLit (LitRubbish _ rep) = case expectOnly "cgLit" prim_reps of -- Note [Post-unarisation invariants] VoidRep -> panic "cgLit:VoidRep" -- ditto - LiftedRep -> idInfoToAmode <$> getCgIdInfo unitDataConId - UnliftedRep -> idInfoToAmode <$> getCgIdInfo unitDataConId + BoxedRep _ -> idInfoToAmode <$> getCgIdInfo unitDataConId AddrRep -> cgLit LitNullAddr VecRep n elem -> do platform <- getPlatform diff --git a/compiler/GHC/StgToJS/Apply.hs b/compiler/GHC/StgToJS/Apply.hs index bf8bed0ec6b52c7de49e374db190a79179eece56..60817a67b26cfaa312b79cdc08c255751fa34607 100644 --- a/compiler/GHC/StgToJS/Apply.hs +++ b/compiler/GHC/StgToJS/Apply.hs @@ -48,6 +48,7 @@ import GHC.Types.Literal import GHC.Types.Id import GHC.Types.Id.Info import GHC.Types.CostCentre +import GHC.Types.RepType (mightBeFunTy) import GHC.Stg.Syntax @@ -204,7 +205,7 @@ genApp ctx i args -- no args and Id can't be a function: just enter it | [] <- args , idFunRepArity i == 0 - , not (mightBeAFunction (idType i)) + , not (mightBeFunTy (idType i)) = do enter_id <- genIdArg i >>= \case diff --git a/compiler/GHC/StgToJS/Expr.hs b/compiler/GHC/StgToJS/Expr.hs index 6eaaaabb07d6bb9f9e27865f0ffacf3a93331041..f058e4581991ba9ab6b9ccca36388cfcd29e3b41 100644 --- a/compiler/GHC/StgToJS/Expr.hs +++ b/compiler/GHC/StgToJS/Expr.hs @@ -382,7 +382,6 @@ verifyRuntimeReps xs = do go _ _ = pprPanic "verifyRuntimeReps: inconsistent sizes" (ppr xs) ver j PtrV = v "h$verify_rep_heapobj" [j] ver j IntV = v "h$verify_rep_int" [j] - ver j RtsObjV = v "h$verify_rep_rtsobj" [j] ver j DoubleV = v "h$verify_rep_double" [j] ver j ArrV = v "h$verify_rep_arr" [j] ver _ _ = mempty diff --git a/compiler/GHC/StgToJS/Rts/Rts.hs b/compiler/GHC/StgToJS/Rts/Rts.hs index 8dd0272ae9df7e259fa5df70e8d948ff359bd045..f956eeda590b9bfa604e3c035922ef8927b78e23 100644 --- a/compiler/GHC/StgToJS/Rts/Rts.hs +++ b/compiler/GHC/StgToJS/Rts/Rts.hs @@ -340,7 +340,6 @@ rts' s = , TxtI "h$vt_double" ||= toJExpr IntV , TxtI "h$vt_long" ||= toJExpr LongV , TxtI "h$vt_addr" ||= toJExpr AddrV - , TxtI "h$vt_rtsobj" ||= toJExpr RtsObjV , TxtI "h$vt_obj" ||= toJExpr ObjV , TxtI "h$vt_arr" ||= toJExpr ArrV , jFun (TxtI "h$bh") (bhStats s True) diff --git a/compiler/GHC/StgToJS/Types.hs b/compiler/GHC/StgToJS/Types.hs index 00f04ff0ad85e704a9d96ea29deca449b396a938..908f1fc1bc0f5ba509ca0b856f289413d2efa04d 100644 --- a/compiler/GHC/StgToJS/Types.hs +++ b/compiler/GHC/StgToJS/Types.hs @@ -150,13 +150,13 @@ instance ToJExpr CIStatic where -- | Free variable types data VarType - = PtrV -- ^ pointer = reference to heap object (closure object) + = PtrV -- ^ pointer = reference to heap object (closure object), lifted or not. + -- Can also be some RTS object (e.g. TVar#, MVar#, MutVar#, Weak#) | VoidV -- ^ no fields | DoubleV -- ^ A Double: one field | IntV -- ^ An Int (32bit because JS): one field | LongV -- ^ A Long: two fields one for the upper 32bits, one for the lower (NB: JS is little endian) | AddrV -- ^ a pointer not to the heap: two fields, array + index - | RtsObjV -- ^ some RTS object from GHCJS (for example TVar#, MVar#, MutVar#, Weak#) | ObjV -- ^ some JS object, user supplied, be careful around these, can be anything | ArrV -- ^ boxed array deriving stock (Eq, Ord, Enum, Bounded, Show) diff --git a/compiler/GHC/StgToJS/Utils.hs b/compiler/GHC/StgToJS/Utils.hs index 77d9e4c85c7d7cb842db2aa28bb5354754775f9e..826eb3d16188805e73e88ebe4e663ef65142db12 100644 --- a/compiler/GHC/StgToJS/Utils.hs +++ b/compiler/GHC/StgToJS/Utils.hs @@ -38,7 +38,6 @@ module GHC.StgToJS.Utils , assocPrimReps , assocIdPrimReps , assocIdExprs - , mightBeAFunction , mkArityTag , toTypeList -- * Stg Utils @@ -147,11 +146,11 @@ assignCoerce1 _x _y = pprPanic "assignCoerce1" -- | Assign p2 to p1 with optional coercion assignCoerce :: TypedExpr -> TypedExpr -> JStat -- Coercion between StablePtr# and Addr# -assignCoerce (TypedExpr AddrRep [a_val, a_off]) (TypedExpr UnliftedRep [sptr]) = mconcat +assignCoerce (TypedExpr AddrRep [a_val, a_off]) (TypedExpr (BoxedRep (Just Unlifted)) [sptr]) = mconcat [ a_val |= var "h$stablePtrBuf" , a_off |= sptr ] -assignCoerce (TypedExpr UnliftedRep [sptr]) (TypedExpr AddrRep [_a_val, a_off]) = +assignCoerce (TypedExpr (BoxedRep (Just Unlifted)) [sptr]) (TypedExpr AddrRep [_a_val, a_off]) = sptr |= a_off assignCoerce p1 p2 = assignTypedExprs [p1] [p2] @@ -258,8 +257,7 @@ uTypeVt ut primRepVt :: HasDebugCallStack => PrimRep -> VarType primRepVt VoidRep = VoidV -primRepVt LiftedRep = PtrV -- fixme does ByteArray# ever map to this? -primRepVt UnliftedRep = RtsObjV +primRepVt (BoxedRep _) = PtrV -- fixme does ByteArray# ever map to this? primRepVt IntRep = IntV primRepVt Int8Rep = IntV primRepVt Int16Rep = IntV @@ -316,26 +314,26 @@ primTypeVt t = case tyConAppTyCon_maybe (unwrapType t) of | tc == word64PrimTyCon -> LongV | tc == addrPrimTyCon -> AddrV | tc == stablePtrPrimTyCon -> AddrV - | tc == stableNamePrimTyCon -> RtsObjV + | tc == stableNamePrimTyCon -> PtrV | tc == statePrimTyCon -> VoidV | tc == proxyPrimTyCon -> VoidV | tc == realWorldTyCon -> VoidV - | tc == threadIdPrimTyCon -> RtsObjV - | tc == weakPrimTyCon -> RtsObjV + | tc == threadIdPrimTyCon -> PtrV + | tc == weakPrimTyCon -> PtrV | tc == arrayPrimTyCon -> ArrV | tc == smallArrayPrimTyCon -> ArrV | tc == byteArrayPrimTyCon -> ObjV -- can contain any JS reference, used for JSVal | tc == mutableArrayPrimTyCon -> ArrV | tc == smallMutableArrayPrimTyCon -> ArrV | tc == mutableByteArrayPrimTyCon -> ObjV -- can contain any JS reference, used for JSVal - | tc == mutVarPrimTyCon -> RtsObjV - | tc == mVarPrimTyCon -> RtsObjV - | tc == tVarPrimTyCon -> RtsObjV - | tc == bcoPrimTyCon -> RtsObjV -- unsupported? - | tc == stackSnapshotPrimTyCon -> RtsObjV - | tc == ioPortPrimTyCon -> RtsObjV -- unsupported? + | tc == mutVarPrimTyCon -> PtrV + | tc == mVarPrimTyCon -> PtrV + | tc == tVarPrimTyCon -> PtrV + | tc == bcoPrimTyCon -> PtrV -- unsupported? + | tc == stackSnapshotPrimTyCon -> PtrV + | tc == ioPortPrimTyCon -> PtrV -- unsupported? | tc == anyTyCon -> PtrV - | tc == compactPrimTyCon -> ObjV -- unsupported? + | tc == compactPrimTyCon -> PtrV -- unsupported? | tc == eqPrimTyCon -> VoidV -- coercion token? | tc == eqReprPrimTyCon -> VoidV -- role | tc == unboxedUnitTyCon -> VoidV -- Void# @@ -392,17 +390,6 @@ assocIdPrimReps i = assocPrimReps (idPrimReps i) assocIdExprs :: Id -> [JExpr] -> [TypedExpr] assocIdExprs i es = fmap (uncurry TypedExpr) (assocIdPrimReps i es) --- | Return False only if we are *sure* it's a data type --- Look through newtypes etc as much as possible -mightBeAFunction :: HasDebugCallStack => Type -> Bool -mightBeAFunction ty - | [LiftedRep] <- typePrimRep ty - , Just tc <- tyConAppTyCon_maybe (unwrapType ty) - , isDataTyCon tc - = False - | otherwise - = True - mkArityTag :: Int -> Int -> Int mkArityTag arity registers = arity Bits..|. (registers `Bits.shiftL` 8) diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs index a7367b6755aaaeaec801b206555eb9429299ead6..e743276e0ee83c84d9bbc3d17ba176dee306cffe 100644 --- a/compiler/GHC/Types/Basic.hs +++ b/compiler/GHC/Types/Basic.hs @@ -20,6 +20,7 @@ types that {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE LambdaCase #-} module GHC.Types.Basic ( LeftOrRight(..), @@ -2001,12 +2002,20 @@ isKindLevel KindLevel = True data Levity = Lifted | Unlifted - deriving Eq + deriving (Data,Eq,Ord,Show) instance Outputable Levity where ppr Lifted = text "Lifted" ppr Unlifted = text "Unlifted" +instance Binary Levity where + put_ bh = \case + Lifted -> putByte bh 0 + Unlifted -> putByte bh 1 + get bh = getByte bh >>= \case + 0 -> pure Lifted + _ -> pure Unlifted + mightBeLifted :: Maybe Levity -> Bool mightBeLifted (Just Unlifted) = False mightBeLifted _ = True diff --git a/compiler/GHC/Types/RepType.hs b/compiler/GHC/Types/RepType.hs index 1e63922e1f52a74f9b8c2f1aacd9c00a8d1c2854..44111e0e4b841fdb25fb99589948045cca5cc9bc 100644 --- a/compiler/GHC/Types/RepType.hs +++ b/compiler/GHC/Types/RepType.hs @@ -315,8 +315,10 @@ typeSlotTy ty = case typePrimRep ty of primRepSlot :: PrimRep -> SlotTy primRepSlot VoidRep = pprPanic "primRepSlot" (text "No slot for VoidRep") -primRepSlot LiftedRep = PtrLiftedSlot -primRepSlot UnliftedRep = PtrUnliftedSlot +primRepSlot (BoxedRep mlev) = case mlev of + Nothing -> panic "primRepSlot: levity polymorphic BoxedRep" + Just Lifted -> PtrLiftedSlot + Just Unlifted -> PtrUnliftedSlot primRepSlot IntRep = WordSlot primRepSlot Int8Rep = WordSlot primRepSlot Int16Rep = WordSlot @@ -333,8 +335,8 @@ primRepSlot DoubleRep = DoubleSlot primRepSlot (VecRep n e) = VecSlot n e slotPrimRep :: SlotTy -> PrimRep -slotPrimRep PtrLiftedSlot = LiftedRep -slotPrimRep PtrUnliftedSlot = UnliftedRep +slotPrimRep PtrLiftedSlot = BoxedRep (Just Lifted) +slotPrimRep PtrUnliftedSlot = BoxedRep (Just Unlifted) slotPrimRep Word64Slot = Word64Rep slotPrimRep WordSlot = WordRep slotPrimRep DoubleSlot = DoubleRep @@ -635,8 +637,10 @@ runtimeRepPrimRep_maybe rr_ty primRepToRuntimeRep :: PrimRep -> RuntimeRepType primRepToRuntimeRep rep = case rep of VoidRep -> zeroBitRepTy - LiftedRep -> liftedRepTy - UnliftedRep -> unliftedRepTy + BoxedRep mlev -> case mlev of + Nothing -> panic "primRepToRuntimeRep: levity polymorphic BoxedRep" + Just Lifted -> liftedRepTy + Just Unlifted -> unliftedRepTy IntRep -> intRepDataConTy Int8Rep -> int8RepDataConTy Int16Rep -> int16RepDataConTy @@ -688,7 +692,7 @@ mightBeFunTy :: Type -> Bool -- AK: It would be nice to figure out and document the difference -- between this and isFunTy at some point. mightBeFunTy ty - | [LiftedRep] <- typePrimRep ty + | [BoxedRep _] <- typePrimRep ty , Just tc <- tyConAppTyCon_maybe (unwrapType ty) , isDataTyCon tc = False diff --git a/rts/js/rts.js b/rts/js/rts.js index c546c760468f7a1b6fb41b6ed4d12ba9d7029ffa..310be592388b8884b920939161fbd100301dce64 100644 --- a/rts/js/rts.js +++ b/rts/js/rts.js @@ -245,7 +245,7 @@ function h$printcl(i) { r += " "; switch(cl.i[i]) { case h$vt_ptr: - r += "[ Ptr :: " + d["d"+idx].f.n + "]"; + r += "[ Ptr :: " + d["d"+idx] + "]"; idx++; break; case h$vt_void: @@ -267,10 +267,6 @@ function h$printcl(i) { r += "(" + d["d"+idx].length + "," + d["d"+(idx+1)] + " :: ptr)"; idx+=2; break; - case h$vt_rtsobj: - r += "(" + d["d"+idx].toString() + " :: RTS object)"; - idx++; - break; default: r += "unknown field: " + cl.i[i]; } diff --git a/rts/js/verify.js b/rts/js/verify.js index a04a562b7f41b69a326b212c17aba83dfa9c67a1..e3522d7cc4f7fdfd62d0f2c43cc5ba493a4a05ab 100644 --- a/rts/js/verify.js +++ b/rts/js/verify.js @@ -113,7 +113,7 @@ function h$verify_rep_is_bytearray(o) { function h$verify_rep_heapobj(o) { // possibly an unlifted rts object // XXX: we should do a different check for these - if(h$verify_rep_is_rtsobj(o)) return; + if(h$verify_rep_is_rtsobj(o)) return h$verify_rep_rtsobj(o); // unboxed rep if(typeof o === 'number' || typeof o === 'boolean') return; // boxed rep diff --git a/testsuite/tests/primops/should_run/all.T b/testsuite/tests/primops/should_run/all.T index 09d74a5c6effe282e56421d4b4c4b03521fefd92..8e4afa0b538c7f562a8dfe98b811074a02c19bb8 100644 --- a/testsuite/tests/primops/should_run/all.T +++ b/testsuite/tests/primops/should_run/all.T @@ -8,7 +8,7 @@ test('T10481', exit_code(1), compile_and_run, ['']) test('T10678', [ collect_stats('bytes allocated',5), only_ways(['normal']), - js_broken(22360) + js_broken(22361) ], compile_and_run, ['-O']) test('T11296', normal, compile_and_run, ['']) diff --git a/testsuite/tests/rep-poly/T22291.hs b/testsuite/tests/rep-poly/T22291.hs new file mode 100644 index 0000000000000000000000000000000000000000..009cb1ed8ca1e2548ccccba5e7804b4d6c60a421 --- /dev/null +++ b/testsuite/tests/rep-poly/T22291.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE DataKinds #-} + +module T22291 where + +import GHC.Exts + +foo :: forall (lev :: Levity) (a :: TYPE (BoxedRep lev)). Addr# -> (# a #) +foo x = addrToAny# x diff --git a/testsuite/tests/rep-poly/T22291b.hs b/testsuite/tests/rep-poly/T22291b.hs new file mode 100644 index 0000000000000000000000000000000000000000..60d2f5e512bc697be14de4ca0766d8b9371bd9ab --- /dev/null +++ b/testsuite/tests/rep-poly/T22291b.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE DataKinds, MagicHash, UnboxedTuples #-} + +module T22291b where + +import GHC.Exts + +indexArray :: forall l (a :: TYPE (BoxedRep l)). Array# a -> Int# -> (# a #) +indexArray = indexArray# diff --git a/testsuite/tests/rep-poly/all.T b/testsuite/tests/rep-poly/all.T index 6d533feb45b0ffd4d3d3229dc9bc1b87f587ba48..1b8a73049ebde07154516a8c36ae331d39e3fa28 100644 --- a/testsuite/tests/rep-poly/all.T +++ b/testsuite/tests/rep-poly/all.T @@ -15,7 +15,7 @@ test('T18170b', [extra_files(['T18170c.hs']), expect_broken(19893)], multimod_co # T18170b isn't actually broken, but it causes a Core Lint error # even though the program is (correctly) rejected by the typechecker test('T18481', normal, compile, ['']) -test('T18481a', js_broken(22360), compile, ['']) +test('T18481a', normal, compile, ['']) test('T18534', normal, compile_fail, ['']) test('T19615', normal, compile_fail, ['']) test('T19709a', normal, compile_fail, ['']) @@ -29,8 +29,10 @@ test('T20423b', normal, compile_fail, ['']) test('T20426', normal, compile_fail, ['']) test('T21239', normal, compile, ['']) test('T21544', normal, compile, ['-Wno-deprecated-flags']) +test('T22291', normal, compile, ['']) +test('T22291b', normal, compile, ['']) -test('EtaExpandDataCon', js_broken(22360), compile, ['-O']) +test('EtaExpandDataCon', normal, compile, ['-O']) test('EtaExpandStupid1', normal, compile, ['-Wno-deprecated-flags']) test('EtaExpandStupid2', normal, compile_fail, ['-Wno-deprecated-flags']) test('LevPolyLet', normal, compile_fail, ['']) @@ -43,7 +45,7 @@ test('RepPolyBackpack1', normal, backpack_compile_fail, ['']) test('RepPolyBackpack2', req_c, backpack_run, ['']) test('RepPolyBackpack3', normal, backpack_compile_fail, ['']) test('RepPolyBackpack4', req_c, backpack_run, ['']) -test('RepPolyBackpack5', js_broken(22360), backpack_run, ['']) +test('RepPolyBackpack5', js_broken(22361), backpack_run, ['']) test('RepPolyBinder', normal, compile_fail, ['']) test('RepPolyCase1', normal, compile_fail, ['']) test('RepPolyClassMethod', normal, compile_fail, ['']) @@ -79,8 +81,8 @@ test('RepPolySum', normal, compile_fail, ['']) test('RepPolyTuple', normal, compile_fail, ['']) test('RepPolyTupleSection', normal, compile_fail, ['']) test('RepPolyUnboxedPatterns', normal, compile_fail, ['']) -test('RepPolyUnliftedDatatype', js_broken(22360), compile, ['']) -test('RepPolyUnliftedDatatype2', js_broken(22261), compile, ['-O']) +test('RepPolyUnliftedDatatype', normal, compile, ['']) +test('RepPolyUnliftedDatatype2', normal, compile, ['-O']) test('RepPolyUnliftedNewtype', normal, compile, ['-fno-warn-partial-type-signatures -fno-warn-deprecated-flags']) test('RepPolyWildcardPattern', normal, compile_fail, ['']) diff --git a/testsuite/tests/unlifted-datatypes/should_compile/all.T b/testsuite/tests/unlifted-datatypes/should_compile/all.T index 13835fe06bd9b449a0b11e5f737ab86d5d0a635d..d8c3eeb45736e89e2e721ea130051bb14b79a5ea 100644 --- a/testsuite/tests/unlifted-datatypes/should_compile/all.T +++ b/testsuite/tests/unlifted-datatypes/should_compile/all.T @@ -1,4 +1,4 @@ test('UnlDataMonoSigs', normal, compile, ['']) -test('UnlDataPolySigs', js_broken(22360), compile, ['']) +test('UnlDataPolySigs', normal, compile, ['']) test('UnlDataFams', normal, compile, ['']) -test('UnlDataUsersGuide', js_broken(22360), compile, ['']) +test('UnlDataUsersGuide', normal, compile, [''])