Skip to content

Commit

Permalink
Start moving other constants from (Haskell)Constants to platformConst…
Browse files Browse the repository at this point in the history
…ants
  • Loading branch information
Ian Lynagh committed Sep 14, 2012
1 parent f4d0e62 commit 9b0c4ed
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 12 deletions.
5 changes: 2 additions & 3 deletions compiler/codeGen/CgExpr.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@ module CgExpr ( cgExpr ) where
#include "HsVersions.h"
import Constants
import StgSyn
import CgMonad
Expand Down Expand Up @@ -352,7 +351,7 @@ mkRhsClosure dflags bndr cc bi
(StgApp selectee [{-no args-}]))])
| the_fv == scrutinee -- Scrutinee is the only free variable
&& maybeToBool maybe_offset -- Selectee is a component of the tuple
&& offset_into_int <= mAX_SPEC_SELECTEE_SIZE -- Offset is small enough
&& offset_into_int <= mAX_SPEC_SELECTEE_SIZE dflags -- Offset is small enough
= -- NOT TRUE: ASSERT(is_single_constructor)
-- The simplifier may have statically determined that the single alternative
-- is the only possible case and eliminated the others, even if there are
Expand Down Expand Up @@ -396,7 +395,7 @@ mkRhsClosure dflags bndr cc bi
| args `lengthIs` (arity-1)
&& all isFollowableArg (map idCgRep fvs)
&& isUpdatable upd_flag
&& arity <= mAX_SPEC_AP_SIZE
&& arity <= mAX_SPEC_AP_SIZE dflags
&& not (dopt Opt_SccProfilingOn dflags)
-- not when profiling: we don't want to
-- lose information about this particular
Expand Down
4 changes: 2 additions & 2 deletions compiler/codeGen/StgCmmBind.hs
Original file line number Diff line number Diff line change
Expand Up @@ -243,7 +243,7 @@ mkRhsClosure dflags bndr _cc _bi
(StgApp selectee [{-no args-}]))])
| the_fv == scrutinee -- Scrutinee is the only free variable
&& maybeToBool maybe_offset -- Selectee is a component of the tuple
&& offset_into_int <= mAX_SPEC_SELECTEE_SIZE -- Offset is small enough
&& offset_into_int <= mAX_SPEC_SELECTEE_SIZE dflags -- Offset is small enough
= -- NOT TRUE: ASSERT(is_single_constructor)
-- The simplifier may have statically determined that the single alternative
-- is the only possible case and eliminated the others, even if there are
Expand Down Expand Up @@ -272,7 +272,7 @@ mkRhsClosure dflags bndr _cc _bi
| args `lengthIs` (arity-1)
&& all (isGcPtrRep . idPrimRep . stripNV) fvs
&& isUpdatable upd_flag
&& arity <= mAX_SPEC_AP_SIZE
&& arity <= mAX_SPEC_AP_SIZE dflags
&& not (dopt Opt_SccProfilingOn dflags)
-- not when profiling: we don't want to
-- lose information about this particular
Expand Down
7 changes: 0 additions & 7 deletions includes/HaskellConstants.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,13 +34,6 @@ mAX_CONTEXT_REDUCTION_DEPTH :: Int
mAX_CONTEXT_REDUCTION_DEPTH = 200
-- Increase to 200; see Trac #5395

-- pre-compiled thunk types
mAX_SPEC_SELECTEE_SIZE :: Int
mAX_SPEC_SELECTEE_SIZE = MAX_SPEC_SELECTEE_SIZE

mAX_SPEC_AP_SIZE :: Int
mAX_SPEC_AP_SIZE = MAX_SPEC_AP_SIZE

-- closure sizes: these do NOT include the header (see below for header sizes)
mIN_PAYLOAD_SIZE ::Int
mIN_PAYLOAD_SIZE = MIN_PAYLOAD_SIZE
Expand Down
24 changes: 24 additions & 0 deletions includes/mkDerivedConstants.c
Original file line number Diff line number Diff line change
Expand Up @@ -293,6 +293,26 @@ enum Mode { Gen_Haskell_Type, Gen_Haskell_Value, Gen_Haskell_Wrappers, Gen_Haske

#define FUN_OFFSET(sym) (OFFSET(Capability,f.sym) - OFFSET(Capability,r))

void constantInt(char *name, intptr_t val) {
switch (mode) {
case Gen_Haskell_Type:
printf(" , pc_%s :: Int\n", name);
break;
case Gen_Haskell_Value:
printf(" , pc_%s = %" PRIdPTR "\n", name, val);
break;
case Gen_Haskell_Wrappers:
printf("%s :: DynFlags -> Int\n", name);
printf("%s dflags = pc_%s (sPlatformConstants (settings dflags))\n",
name, name);
break;
case Gen_Haskell_Exports:
printf(" %s,\n", name);
break;
case Gen_Header:
break;
}
}

int
main(int argc, char *argv[])
Expand Down Expand Up @@ -602,6 +622,10 @@ main(int argc, char *argv[])
}
#endif

// pre-compiled thunk types
constantInt("mAX_SPEC_SELECTEE_SIZE", MAX_SPEC_SELECTEE_SIZE);
constantInt("mAX_SPEC_AP_SIZE", MAX_SPEC_AP_SIZE);

switch (mode) {
case Gen_Haskell_Type:
printf(" } deriving (Read, Show)\n");
Expand Down

0 comments on commit 9b0c4ed

Please sign in to comment.