diff options
author | Sylvain Henry <hsyl20@gmail.com> | 2018-11-22 11:31:16 -0500 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-11-22 12:11:15 -0500 |
commit | 13bb4bf44e6e690133be334bbf0c63fcae5db34a (patch) | |
tree | ee7a9a9f60ca936b16cc15a46c758d4dc51abfd7 /compiler/deSugar | |
parent | f5fbecc85967218fd8ba6512f10eea2daf2812ac (diff) | |
download | haskell-13bb4bf44e6e690133be334bbf0c63fcae5db34a.tar.gz |
Rename literal constructors
In a previous patch we replaced some built-in literal constructors
(MachInt, MachWord, etc.) with a single LitNumber constructor.
In this patch we replace the `Mach` prefix of the remaining constructors
with `Lit` for consistency (e.g., LitChar, LitLabel, etc.).
Sadly the name `LitString` was already taken for a kind of FastString
and it would become misleading to have both `LitStr` (literal
constructor renamed after `MachStr`) and `LitString` (FastString
variant). Hence this patch renames the FastString variant `PtrString`
(which is more accurate) and the literal string constructor now uses the
least surprising `LitString` name.
Both `Literal` and `LitString/PtrString` have recently seen breaking
changes so doing this kind of renaming now shouldn't harm much.
Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27, tdammers
Subscribers: tdammers, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4881
Diffstat (limited to 'compiler/deSugar')
-rw-r--r-- | compiler/deSugar/DsCCall.hs | 4 | ||||
-rw-r--r-- | compiler/deSugar/DsForeign.hs | 6 | ||||
-rw-r--r-- | compiler/deSugar/DsMonad.hs | 4 | ||||
-rw-r--r-- | compiler/deSugar/DsUtils.hs | 4 | ||||
-rw-r--r-- | compiler/deSugar/Match.hs | 4 | ||||
-rw-r--r-- | compiler/deSugar/MatchLit.hs | 38 |
6 files changed, 30 insertions, 30 deletions
diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs index 7a634ac1ff..7cab8e8e25 100644 --- a/compiler/deSugar/DsCCall.hs +++ b/compiler/deSugar/DsCCall.hs @@ -327,8 +327,8 @@ resultWrapper result_ty = do { dflags <- getDynFlags ; let marshal_bool e = mkWildCase e intPrimTy boolTy - [ (DEFAULT ,[],Var trueDataConId ) - , (LitAlt (mkMachInt dflags 0),[],Var falseDataConId)] + [ (DEFAULT ,[],Var trueDataConId ) + , (LitAlt (mkLitInt dflags 0),[],Var falseDataConId)] ; return (Just intPrimTy, marshal_bool) } -- Newtypes diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index 5856ff2445..2e20cc7f35 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -163,7 +163,7 @@ dsCImport id co (CLabel cid) cconv _ _ = do (resTy, foRhs) <- resultWrapper ty ASSERT(fromJust resTy `eqType` addrPrimTy) -- typechecker ensures this let - rhs = foRhs (Lit (MachLabel cid stdcall_info fod)) + rhs = foRhs (Lit (LitLabel cid stdcall_info fod)) rhs' = Cast rhs co stdcall_info = fun_type_arg_stdcall_info dflags cconv ty in @@ -442,8 +442,8 @@ dsFExportDynamic id co0 cconv = do -} adj_args = [ mkIntLitInt dflags (ccallConvToInt cconv) , Var stbl_value - , Lit (MachLabel fe_nm mb_sz_args IsFunction) - , Lit (mkMachString typestring) + , Lit (LitLabel fe_nm mb_sz_args IsFunction) + , Lit (mkLitString typestring) ] -- name of external entry point providing these services. -- (probably in the RTS.) diff --git a/compiler/deSugar/DsMonad.hs b/compiler/deSugar/DsMonad.hs index 921276e4d8..e93b2c30d6 100644 --- a/compiler/deSugar/DsMonad.hs +++ b/compiler/deSugar/DsMonad.hs @@ -82,7 +82,7 @@ import ErrUtils import FastString import Var (EvVar) import UniqFM ( lookupWithDefaultUFM ) -import Literal ( mkMachString ) +import Literal ( mkLitString ) import CostCentreState import Data.IORef @@ -609,5 +609,5 @@ pprRuntimeTrace str doc expr = do dflags <- getDynFlags let message :: CoreExpr message = App (Var unpackCStringId) $ - Lit $ mkMachString $ showSDoc dflags (hang (text str) 4 doc) + Lit $ mkLitString $ showSDoc dflags (hang (text str) 4 doc) return $ mkApps (Var traceId) [Type (exprType expr), message, expr] diff --git a/compiler/deSugar/DsUtils.hs b/compiler/deSugar/DsUtils.hs index 001b36151c..ca22387b59 100644 --- a/compiler/deSugar/DsUtils.hs +++ b/compiler/deSugar/DsUtils.hs @@ -403,8 +403,8 @@ mkErrorAppDs err_id ty msg = do dflags <- getDynFlags let full_msg = showSDoc dflags (hcat [ppr src_loc, vbar, msg]) - core_msg = Lit (mkMachString full_msg) - -- mkMachString returns a result of type String# + core_msg = Lit (mkLitString full_msg) + -- mkLitString returns a result of type String# return (mkApps (Var err_id) [Type (getRuntimeRep ty), Type ty, core_msg]) {- diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index e4a8bad525..f207d6039d 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -848,8 +848,8 @@ Previously we had, as PatGroup constructors But Literal is really supposed to represent an *unboxed* literal, like Int#. We were sticking the literal from, say, an overloaded numeric literal pattern -into a MachInt constructor. This didn't really make sense; and we now have -the invariant that value in a MachInt must be in the range of the target +into a LitInt constructor. This didn't really make sense; and we now have +the invariant that value in a LitInt must be in the range of the target machine's Int# type, and an overloaded literal could meaningfully be larger. Solution: For pattern grouping purposes, just store the literal directly in diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index ca7ef0af2f..b91f44de26 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -80,14 +80,14 @@ dsLit :: HsLit GhcRn -> DsM CoreExpr dsLit l = do dflags <- getDynFlags case l of - HsStringPrim _ s -> return (Lit (MachStr s)) - HsCharPrim _ c -> return (Lit (MachChar c)) - HsIntPrim _ i -> return (Lit (mkMachIntWrap dflags i)) - HsWordPrim _ w -> return (Lit (mkMachWordWrap dflags w)) - HsInt64Prim _ i -> return (Lit (mkMachInt64Wrap dflags i)) - HsWord64Prim _ w -> return (Lit (mkMachWord64Wrap dflags w)) - HsFloatPrim _ f -> return (Lit (MachFloat (fl_value f))) - HsDoublePrim _ d -> return (Lit (MachDouble (fl_value d))) + HsStringPrim _ s -> return (Lit (LitString s)) + HsCharPrim _ c -> return (Lit (LitChar c)) + HsIntPrim _ i -> return (Lit (mkLitIntWrap dflags i)) + HsWordPrim _ w -> return (Lit (mkLitWordWrap dflags w)) + HsInt64Prim _ i -> return (Lit (mkLitInt64Wrap dflags i)) + HsWord64Prim _ w -> return (Lit (mkLitWord64Wrap dflags w)) + HsFloatPrim _ f -> return (Lit (LitFloat (fl_value f))) + HsDoublePrim _ d -> return (Lit (LitDouble (fl_value d))) HsChar _ c -> return (mkCharExpr c) HsString _ str -> mkStringExprFS str HsInteger _ i _ -> mkIntegerExpr i @@ -375,9 +375,9 @@ matchLiterals (var:vars) ty sub_groups wrap_str_guard :: Id -> (Literal,MatchResult) -> DsM MatchResult -- Equality check for string literals - wrap_str_guard eq_str (MachStr s, mr) + wrap_str_guard eq_str (LitString s, mr) = do { -- We now have to convert back to FastString. Perhaps there - -- should be separate MachBytes and MachStr constructors? + -- should be separate LitBytes and LitString constructors? let s' = mkFastStringByteString s ; lit <- mkStringExprFS s' ; let pred = mkApps (Var eq_str) [Var var, lit] @@ -391,20 +391,20 @@ hsLitKey :: DynFlags -> HsLit GhcTc -> Literal -- Get the Core literal corresponding to a HsLit. -- It only works for primitive types and strings; -- others have been removed by tidy --- For HsString, it produces a MachStr, which really represents an _unboxed_ +-- For HsString, it produces a LitString, which really represents an _unboxed_ -- string literal; and we deal with it in matchLiterals above. Otherwise, it -- produces a primitive Literal of type matching the original HsLit. -- In the case of the fixed-width numeric types, we need to wrap here -- because Literal has an invariant that the literal is in range, while -- HsLit does not. -hsLitKey dflags (HsIntPrim _ i) = mkMachIntWrap dflags i -hsLitKey dflags (HsWordPrim _ w) = mkMachWordWrap dflags w -hsLitKey dflags (HsInt64Prim _ i) = mkMachInt64Wrap dflags i -hsLitKey dflags (HsWord64Prim _ w) = mkMachWord64Wrap dflags w -hsLitKey _ (HsCharPrim _ c) = mkMachChar c -hsLitKey _ (HsFloatPrim _ f) = mkMachFloat (fl_value f) -hsLitKey _ (HsDoublePrim _ d) = mkMachDouble (fl_value d) -hsLitKey _ (HsString _ s) = MachStr (fastStringToByteString s) +hsLitKey dflags (HsIntPrim _ i) = mkLitIntWrap dflags i +hsLitKey dflags (HsWordPrim _ w) = mkLitWordWrap dflags w +hsLitKey dflags (HsInt64Prim _ i) = mkLitInt64Wrap dflags i +hsLitKey dflags (HsWord64Prim _ w) = mkLitWord64Wrap dflags w +hsLitKey _ (HsCharPrim _ c) = mkLitChar c +hsLitKey _ (HsFloatPrim _ f) = mkLitFloat (fl_value f) +hsLitKey _ (HsDoublePrim _ d) = mkLitDouble (fl_value d) +hsLitKey _ (HsString _ s) = LitString (fastStringToByteString s) hsLitKey _ l = pprPanic "hsLitKey" (ppr l) {- |