never executed always true always false
    1 module GHC.Platform.Constants where
    2 
    3 import Prelude
    4 import Data.Char
    5 
    6 data PlatformConstants = PlatformConstants {
    7       pc_CONTROL_GROUP_CONST_291 :: {-# UNPACK #-} !Int,
    8       pc_STD_HDR_SIZE :: {-# UNPACK #-} !Int,
    9       pc_PROF_HDR_SIZE :: {-# UNPACK #-} !Int,
   10       pc_BLOCK_SIZE :: {-# UNPACK #-} !Int,
   11       pc_BLOCKS_PER_MBLOCK :: {-# UNPACK #-} !Int,
   12       pc_TICKY_BIN_COUNT :: {-# UNPACK #-} !Int,
   13       pc_OFFSET_StgRegTable_rR1 :: {-# UNPACK #-} !Int,
   14       pc_OFFSET_StgRegTable_rR2 :: {-# UNPACK #-} !Int,
   15       pc_OFFSET_StgRegTable_rR3 :: {-# UNPACK #-} !Int,
   16       pc_OFFSET_StgRegTable_rR4 :: {-# UNPACK #-} !Int,
   17       pc_OFFSET_StgRegTable_rR5 :: {-# UNPACK #-} !Int,
   18       pc_OFFSET_StgRegTable_rR6 :: {-# UNPACK #-} !Int,
   19       pc_OFFSET_StgRegTable_rR7 :: {-# UNPACK #-} !Int,
   20       pc_OFFSET_StgRegTable_rR8 :: {-# UNPACK #-} !Int,
   21       pc_OFFSET_StgRegTable_rR9 :: {-# UNPACK #-} !Int,
   22       pc_OFFSET_StgRegTable_rR10 :: {-# UNPACK #-} !Int,
   23       pc_OFFSET_StgRegTable_rF1 :: {-# UNPACK #-} !Int,
   24       pc_OFFSET_StgRegTable_rF2 :: {-# UNPACK #-} !Int,
   25       pc_OFFSET_StgRegTable_rF3 :: {-# UNPACK #-} !Int,
   26       pc_OFFSET_StgRegTable_rF4 :: {-# UNPACK #-} !Int,
   27       pc_OFFSET_StgRegTable_rF5 :: {-# UNPACK #-} !Int,
   28       pc_OFFSET_StgRegTable_rF6 :: {-# UNPACK #-} !Int,
   29       pc_OFFSET_StgRegTable_rD1 :: {-# UNPACK #-} !Int,
   30       pc_OFFSET_StgRegTable_rD2 :: {-# UNPACK #-} !Int,
   31       pc_OFFSET_StgRegTable_rD3 :: {-# UNPACK #-} !Int,
   32       pc_OFFSET_StgRegTable_rD4 :: {-# UNPACK #-} !Int,
   33       pc_OFFSET_StgRegTable_rD5 :: {-# UNPACK #-} !Int,
   34       pc_OFFSET_StgRegTable_rD6 :: {-# UNPACK #-} !Int,
   35       pc_OFFSET_StgRegTable_rXMM1 :: {-# UNPACK #-} !Int,
   36       pc_OFFSET_StgRegTable_rXMM2 :: {-# UNPACK #-} !Int,
   37       pc_OFFSET_StgRegTable_rXMM3 :: {-# UNPACK #-} !Int,
   38       pc_OFFSET_StgRegTable_rXMM4 :: {-# UNPACK #-} !Int,
   39       pc_OFFSET_StgRegTable_rXMM5 :: {-# UNPACK #-} !Int,
   40       pc_OFFSET_StgRegTable_rXMM6 :: {-# UNPACK #-} !Int,
   41       pc_OFFSET_StgRegTable_rYMM1 :: {-# UNPACK #-} !Int,
   42       pc_OFFSET_StgRegTable_rYMM2 :: {-# UNPACK #-} !Int,
   43       pc_OFFSET_StgRegTable_rYMM3 :: {-# UNPACK #-} !Int,
   44       pc_OFFSET_StgRegTable_rYMM4 :: {-# UNPACK #-} !Int,
   45       pc_OFFSET_StgRegTable_rYMM5 :: {-# UNPACK #-} !Int,
   46       pc_OFFSET_StgRegTable_rYMM6 :: {-# UNPACK #-} !Int,
   47       pc_OFFSET_StgRegTable_rZMM1 :: {-# UNPACK #-} !Int,
   48       pc_OFFSET_StgRegTable_rZMM2 :: {-# UNPACK #-} !Int,
   49       pc_OFFSET_StgRegTable_rZMM3 :: {-# UNPACK #-} !Int,
   50       pc_OFFSET_StgRegTable_rZMM4 :: {-# UNPACK #-} !Int,
   51       pc_OFFSET_StgRegTable_rZMM5 :: {-# UNPACK #-} !Int,
   52       pc_OFFSET_StgRegTable_rZMM6 :: {-# UNPACK #-} !Int,
   53       pc_OFFSET_StgRegTable_rL1 :: {-# UNPACK #-} !Int,
   54       pc_OFFSET_StgRegTable_rSp :: {-# UNPACK #-} !Int,
   55       pc_OFFSET_StgRegTable_rSpLim :: {-# UNPACK #-} !Int,
   56       pc_OFFSET_StgRegTable_rHp :: {-# UNPACK #-} !Int,
   57       pc_OFFSET_StgRegTable_rHpLim :: {-# UNPACK #-} !Int,
   58       pc_OFFSET_StgRegTable_rCCCS :: {-# UNPACK #-} !Int,
   59       pc_OFFSET_StgRegTable_rCurrentTSO :: {-# UNPACK #-} !Int,
   60       pc_OFFSET_StgRegTable_rCurrentNursery :: {-# UNPACK #-} !Int,
   61       pc_OFFSET_StgRegTable_rHpAlloc :: {-# UNPACK #-} !Int,
   62       pc_OFFSET_stgEagerBlackholeInfo :: {-# UNPACK #-} !Int,
   63       pc_OFFSET_stgGCEnter1 :: {-# UNPACK #-} !Int,
   64       pc_OFFSET_stgGCFun :: {-# UNPACK #-} !Int,
   65       pc_OFFSET_Capability_r :: {-# UNPACK #-} !Int,
   66       pc_OFFSET_bdescr_start :: {-# UNPACK #-} !Int,
   67       pc_OFFSET_bdescr_free :: {-# UNPACK #-} !Int,
   68       pc_OFFSET_bdescr_blocks :: {-# UNPACK #-} !Int,
   69       pc_OFFSET_bdescr_flags :: {-# UNPACK #-} !Int,
   70       pc_SIZEOF_CostCentreStack :: {-# UNPACK #-} !Int,
   71       pc_OFFSET_CostCentreStack_mem_alloc :: {-# UNPACK #-} !Int,
   72       pc_REP_CostCentreStack_mem_alloc :: {-# UNPACK #-} !Int,
   73       pc_OFFSET_CostCentreStack_scc_count :: {-# UNPACK #-} !Int,
   74       pc_REP_CostCentreStack_scc_count :: {-# UNPACK #-} !Int,
   75       pc_OFFSET_StgHeader_ccs :: {-# UNPACK #-} !Int,
   76       pc_OFFSET_StgHeader_ldvw :: {-# UNPACK #-} !Int,
   77       pc_SIZEOF_StgSMPThunkHeader :: {-# UNPACK #-} !Int,
   78       pc_OFFSET_StgEntCounter_allocs :: {-# UNPACK #-} !Int,
   79       pc_REP_StgEntCounter_allocs :: {-# UNPACK #-} !Int,
   80       pc_OFFSET_StgEntCounter_allocd :: {-# UNPACK #-} !Int,
   81       pc_REP_StgEntCounter_allocd :: {-# UNPACK #-} !Int,
   82       pc_OFFSET_StgEntCounter_registeredp :: {-# UNPACK #-} !Int,
   83       pc_OFFSET_StgEntCounter_link :: {-# UNPACK #-} !Int,
   84       pc_OFFSET_StgEntCounter_entry_count :: {-# UNPACK #-} !Int,
   85       pc_SIZEOF_StgUpdateFrame_NoHdr :: {-# UNPACK #-} !Int,
   86       pc_SIZEOF_StgMutArrPtrs_NoHdr :: {-# UNPACK #-} !Int,
   87       pc_OFFSET_StgMutArrPtrs_ptrs :: {-# UNPACK #-} !Int,
   88       pc_OFFSET_StgMutArrPtrs_size :: {-# UNPACK #-} !Int,
   89       pc_SIZEOF_StgSmallMutArrPtrs_NoHdr :: {-# UNPACK #-} !Int,
   90       pc_OFFSET_StgSmallMutArrPtrs_ptrs :: {-# UNPACK #-} !Int,
   91       pc_SIZEOF_StgArrBytes_NoHdr :: {-# UNPACK #-} !Int,
   92       pc_OFFSET_StgArrBytes_bytes :: {-# UNPACK #-} !Int,
   93       pc_OFFSET_StgTSO_alloc_limit :: {-# UNPACK #-} !Int,
   94       pc_OFFSET_StgTSO_cccs :: {-# UNPACK #-} !Int,
   95       pc_OFFSET_StgTSO_stackobj :: {-# UNPACK #-} !Int,
   96       pc_OFFSET_StgStack_sp :: {-# UNPACK #-} !Int,
   97       pc_OFFSET_StgStack_stack :: {-# UNPACK #-} !Int,
   98       pc_OFFSET_StgUpdateFrame_updatee :: {-# UNPACK #-} !Int,
   99       pc_OFFSET_StgFunInfoExtraFwd_arity :: {-# UNPACK #-} !Int,
  100       pc_REP_StgFunInfoExtraFwd_arity :: {-# UNPACK #-} !Int,
  101       pc_SIZEOF_StgFunInfoExtraRev :: {-# UNPACK #-} !Int,
  102       pc_OFFSET_StgFunInfoExtraRev_arity :: {-# UNPACK #-} !Int,
  103       pc_REP_StgFunInfoExtraRev_arity :: {-# UNPACK #-} !Int,
  104       pc_MAX_SPEC_SELECTEE_SIZE :: {-# UNPACK #-} !Int,
  105       pc_MAX_SPEC_AP_SIZE :: {-# UNPACK #-} !Int,
  106       pc_MIN_PAYLOAD_SIZE :: {-# UNPACK #-} !Int,
  107       pc_MIN_INTLIKE :: {-# UNPACK #-} !Int,
  108       pc_MAX_INTLIKE :: {-# UNPACK #-} !Int,
  109       pc_MIN_CHARLIKE :: {-# UNPACK #-} !Int,
  110       pc_MAX_CHARLIKE :: {-# UNPACK #-} !Int,
  111       pc_MUT_ARR_PTRS_CARD_BITS :: {-# UNPACK #-} !Int,
  112       pc_MAX_Vanilla_REG :: {-# UNPACK #-} !Int,
  113       pc_MAX_Float_REG :: {-# UNPACK #-} !Int,
  114       pc_MAX_Double_REG :: {-# UNPACK #-} !Int,
  115       pc_MAX_Long_REG :: {-# UNPACK #-} !Int,
  116       pc_MAX_XMM_REG :: {-# UNPACK #-} !Int,
  117       pc_MAX_Real_Vanilla_REG :: {-# UNPACK #-} !Int,
  118       pc_MAX_Real_Float_REG :: {-# UNPACK #-} !Int,
  119       pc_MAX_Real_Double_REG :: {-# UNPACK #-} !Int,
  120       pc_MAX_Real_XMM_REG :: {-# UNPACK #-} !Int,
  121       pc_MAX_Real_Long_REG :: {-# UNPACK #-} !Int,
  122       pc_RESERVED_C_STACK_BYTES :: {-# UNPACK #-} !Int,
  123       pc_RESERVED_STACK_WORDS :: {-# UNPACK #-} !Int,
  124       pc_AP_STACK_SPLIM :: {-# UNPACK #-} !Int,
  125       pc_WORD_SIZE :: {-# UNPACK #-} !Int,
  126       pc_CINT_SIZE :: {-# UNPACK #-} !Int,
  127       pc_CLONG_SIZE :: {-# UNPACK #-} !Int,
  128       pc_CLONG_LONG_SIZE :: {-# UNPACK #-} !Int,
  129       pc_BITMAP_BITS_SHIFT :: {-# UNPACK #-} !Int,
  130       pc_TAG_BITS :: {-# UNPACK #-} !Int,
  131       pc_LDV_SHIFT :: {-# UNPACK #-} !Int,
  132       pc_ILDV_CREATE_MASK :: !Integer,
  133       pc_ILDV_STATE_CREATE :: !Integer,
  134       pc_ILDV_STATE_USE :: !Integer
  135   } deriving (Show,Read,Eq)
  136 
  137 
  138 parseConstantsHeader :: FilePath -> IO PlatformConstants
  139 parseConstantsHeader fp = do
  140   s <- readFile fp
  141   let def = "#define HS_CONSTANTS \""
  142       find [] xs = xs
  143       find _  [] = error $ "GHC couldn't find the RTS constants ("++def++") in " ++ fp ++ ": the RTS package you are trying to use is perhaps for another GHC version" ++
  144                                "(e.g. you are using the wrong package database) or the package database is broken.\n"
  145       find (d:ds) (x:xs)
  146         | d == x    = find ds xs
  147         | otherwise = find def xs
  148 
  149       readVal' :: Bool -> Integer -> String -> [Integer]
  150       readVal' n     c (x:xs) = case x of
  151         '"' -> [if n then negate c else c]
  152         '-' -> readVal' True c xs
  153         ',' -> (if n then negate c else c) : readVal' False 0 xs
  154         _   -> readVal' n (c*10 + fromIntegral (ord x - ord '0')) xs
  155       readVal' n     c []     = [if n then negate c else c]
  156 
  157       readVal = readVal' False 0
  158 
  159   return $! case readVal (find def s) of
  160     [v0,v1,v2,v3,v4,v5,v6,v7,v8,v9,v10,v11,v12,v13,v14,v15
  161      ,v16,v17,v18,v19,v20,v21,v22,v23,v24,v25,v26,v27,v28,v29,v30,v31
  162      ,v32,v33,v34,v35,v36,v37,v38,v39,v40,v41,v42,v43,v44,v45,v46,v47
  163      ,v48,v49,v50,v51,v52,v53,v54,v55,v56,v57,v58,v59,v60,v61,v62,v63
  164      ,v64,v65,v66,v67,v68,v69,v70,v71,v72,v73,v74,v75,v76,v77,v78,v79
  165      ,v80,v81,v82,v83,v84,v85,v86,v87,v88,v89,v90,v91,v92,v93,v94,v95
  166      ,v96,v97,v98,v99,v100,v101,v102,v103,v104,v105,v106,v107,v108,v109,v110,v111
  167      ,v112,v113,v114,v115,v116,v117,v118,v119,v120,v121,v122,v123,v124,v125,v126,v127
  168      ] -> PlatformConstants
  169             { pc_CONTROL_GROUP_CONST_291 = fromIntegral v0
  170             , pc_STD_HDR_SIZE = fromIntegral v1
  171             , pc_PROF_HDR_SIZE = fromIntegral v2
  172             , pc_BLOCK_SIZE = fromIntegral v3
  173             , pc_BLOCKS_PER_MBLOCK = fromIntegral v4
  174             , pc_TICKY_BIN_COUNT = fromIntegral v5
  175             , pc_OFFSET_StgRegTable_rR1 = fromIntegral v6
  176             , pc_OFFSET_StgRegTable_rR2 = fromIntegral v7
  177             , pc_OFFSET_StgRegTable_rR3 = fromIntegral v8
  178             , pc_OFFSET_StgRegTable_rR4 = fromIntegral v9
  179             , pc_OFFSET_StgRegTable_rR5 = fromIntegral v10
  180             , pc_OFFSET_StgRegTable_rR6 = fromIntegral v11
  181             , pc_OFFSET_StgRegTable_rR7 = fromIntegral v12
  182             , pc_OFFSET_StgRegTable_rR8 = fromIntegral v13
  183             , pc_OFFSET_StgRegTable_rR9 = fromIntegral v14
  184             , pc_OFFSET_StgRegTable_rR10 = fromIntegral v15
  185             , pc_OFFSET_StgRegTable_rF1 = fromIntegral v16
  186             , pc_OFFSET_StgRegTable_rF2 = fromIntegral v17
  187             , pc_OFFSET_StgRegTable_rF3 = fromIntegral v18
  188             , pc_OFFSET_StgRegTable_rF4 = fromIntegral v19
  189             , pc_OFFSET_StgRegTable_rF5 = fromIntegral v20
  190             , pc_OFFSET_StgRegTable_rF6 = fromIntegral v21
  191             , pc_OFFSET_StgRegTable_rD1 = fromIntegral v22
  192             , pc_OFFSET_StgRegTable_rD2 = fromIntegral v23
  193             , pc_OFFSET_StgRegTable_rD3 = fromIntegral v24
  194             , pc_OFFSET_StgRegTable_rD4 = fromIntegral v25
  195             , pc_OFFSET_StgRegTable_rD5 = fromIntegral v26
  196             , pc_OFFSET_StgRegTable_rD6 = fromIntegral v27
  197             , pc_OFFSET_StgRegTable_rXMM1 = fromIntegral v28
  198             , pc_OFFSET_StgRegTable_rXMM2 = fromIntegral v29
  199             , pc_OFFSET_StgRegTable_rXMM3 = fromIntegral v30
  200             , pc_OFFSET_StgRegTable_rXMM4 = fromIntegral v31
  201             , pc_OFFSET_StgRegTable_rXMM5 = fromIntegral v32
  202             , pc_OFFSET_StgRegTable_rXMM6 = fromIntegral v33
  203             , pc_OFFSET_StgRegTable_rYMM1 = fromIntegral v34
  204             , pc_OFFSET_StgRegTable_rYMM2 = fromIntegral v35
  205             , pc_OFFSET_StgRegTable_rYMM3 = fromIntegral v36
  206             , pc_OFFSET_StgRegTable_rYMM4 = fromIntegral v37
  207             , pc_OFFSET_StgRegTable_rYMM5 = fromIntegral v38
  208             , pc_OFFSET_StgRegTable_rYMM6 = fromIntegral v39
  209             , pc_OFFSET_StgRegTable_rZMM1 = fromIntegral v40
  210             , pc_OFFSET_StgRegTable_rZMM2 = fromIntegral v41
  211             , pc_OFFSET_StgRegTable_rZMM3 = fromIntegral v42
  212             , pc_OFFSET_StgRegTable_rZMM4 = fromIntegral v43
  213             , pc_OFFSET_StgRegTable_rZMM5 = fromIntegral v44
  214             , pc_OFFSET_StgRegTable_rZMM6 = fromIntegral v45
  215             , pc_OFFSET_StgRegTable_rL1 = fromIntegral v46
  216             , pc_OFFSET_StgRegTable_rSp = fromIntegral v47
  217             , pc_OFFSET_StgRegTable_rSpLim = fromIntegral v48
  218             , pc_OFFSET_StgRegTable_rHp = fromIntegral v49
  219             , pc_OFFSET_StgRegTable_rHpLim = fromIntegral v50
  220             , pc_OFFSET_StgRegTable_rCCCS = fromIntegral v51
  221             , pc_OFFSET_StgRegTable_rCurrentTSO = fromIntegral v52
  222             , pc_OFFSET_StgRegTable_rCurrentNursery = fromIntegral v53
  223             , pc_OFFSET_StgRegTable_rHpAlloc = fromIntegral v54
  224             , pc_OFFSET_stgEagerBlackholeInfo = fromIntegral v55
  225             , pc_OFFSET_stgGCEnter1 = fromIntegral v56
  226             , pc_OFFSET_stgGCFun = fromIntegral v57
  227             , pc_OFFSET_Capability_r = fromIntegral v58
  228             , pc_OFFSET_bdescr_start = fromIntegral v59
  229             , pc_OFFSET_bdescr_free = fromIntegral v60
  230             , pc_OFFSET_bdescr_blocks = fromIntegral v61
  231             , pc_OFFSET_bdescr_flags = fromIntegral v62
  232             , pc_SIZEOF_CostCentreStack = fromIntegral v63
  233             , pc_OFFSET_CostCentreStack_mem_alloc = fromIntegral v64
  234             , pc_REP_CostCentreStack_mem_alloc = fromIntegral v65
  235             , pc_OFFSET_CostCentreStack_scc_count = fromIntegral v66
  236             , pc_REP_CostCentreStack_scc_count = fromIntegral v67
  237             , pc_OFFSET_StgHeader_ccs = fromIntegral v68
  238             , pc_OFFSET_StgHeader_ldvw = fromIntegral v69
  239             , pc_SIZEOF_StgSMPThunkHeader = fromIntegral v70
  240             , pc_OFFSET_StgEntCounter_allocs = fromIntegral v71
  241             , pc_REP_StgEntCounter_allocs = fromIntegral v72
  242             , pc_OFFSET_StgEntCounter_allocd = fromIntegral v73
  243             , pc_REP_StgEntCounter_allocd = fromIntegral v74
  244             , pc_OFFSET_StgEntCounter_registeredp = fromIntegral v75
  245             , pc_OFFSET_StgEntCounter_link = fromIntegral v76
  246             , pc_OFFSET_StgEntCounter_entry_count = fromIntegral v77
  247             , pc_SIZEOF_StgUpdateFrame_NoHdr = fromIntegral v78
  248             , pc_SIZEOF_StgMutArrPtrs_NoHdr = fromIntegral v79
  249             , pc_OFFSET_StgMutArrPtrs_ptrs = fromIntegral v80
  250             , pc_OFFSET_StgMutArrPtrs_size = fromIntegral v81
  251             , pc_SIZEOF_StgSmallMutArrPtrs_NoHdr = fromIntegral v82
  252             , pc_OFFSET_StgSmallMutArrPtrs_ptrs = fromIntegral v83
  253             , pc_SIZEOF_StgArrBytes_NoHdr = fromIntegral v84
  254             , pc_OFFSET_StgArrBytes_bytes = fromIntegral v85
  255             , pc_OFFSET_StgTSO_alloc_limit = fromIntegral v86
  256             , pc_OFFSET_StgTSO_cccs = fromIntegral v87
  257             , pc_OFFSET_StgTSO_stackobj = fromIntegral v88
  258             , pc_OFFSET_StgStack_sp = fromIntegral v89
  259             , pc_OFFSET_StgStack_stack = fromIntegral v90
  260             , pc_OFFSET_StgUpdateFrame_updatee = fromIntegral v91
  261             , pc_OFFSET_StgFunInfoExtraFwd_arity = fromIntegral v92
  262             , pc_REP_StgFunInfoExtraFwd_arity = fromIntegral v93
  263             , pc_SIZEOF_StgFunInfoExtraRev = fromIntegral v94
  264             , pc_OFFSET_StgFunInfoExtraRev_arity = fromIntegral v95
  265             , pc_REP_StgFunInfoExtraRev_arity = fromIntegral v96
  266             , pc_MAX_SPEC_SELECTEE_SIZE = fromIntegral v97
  267             , pc_MAX_SPEC_AP_SIZE = fromIntegral v98
  268             , pc_MIN_PAYLOAD_SIZE = fromIntegral v99
  269             , pc_MIN_INTLIKE = fromIntegral v100
  270             , pc_MAX_INTLIKE = fromIntegral v101
  271             , pc_MIN_CHARLIKE = fromIntegral v102
  272             , pc_MAX_CHARLIKE = fromIntegral v103
  273             , pc_MUT_ARR_PTRS_CARD_BITS = fromIntegral v104
  274             , pc_MAX_Vanilla_REG = fromIntegral v105
  275             , pc_MAX_Float_REG = fromIntegral v106
  276             , pc_MAX_Double_REG = fromIntegral v107
  277             , pc_MAX_Long_REG = fromIntegral v108
  278             , pc_MAX_XMM_REG = fromIntegral v109
  279             , pc_MAX_Real_Vanilla_REG = fromIntegral v110
  280             , pc_MAX_Real_Float_REG = fromIntegral v111
  281             , pc_MAX_Real_Double_REG = fromIntegral v112
  282             , pc_MAX_Real_XMM_REG = fromIntegral v113
  283             , pc_MAX_Real_Long_REG = fromIntegral v114
  284             , pc_RESERVED_C_STACK_BYTES = fromIntegral v115
  285             , pc_RESERVED_STACK_WORDS = fromIntegral v116
  286             , pc_AP_STACK_SPLIM = fromIntegral v117
  287             , pc_WORD_SIZE = fromIntegral v118
  288             , pc_CINT_SIZE = fromIntegral v119
  289             , pc_CLONG_SIZE = fromIntegral v120
  290             , pc_CLONG_LONG_SIZE = fromIntegral v121
  291             , pc_BITMAP_BITS_SHIFT = fromIntegral v122
  292             , pc_TAG_BITS = fromIntegral v123
  293             , pc_LDV_SHIFT = fromIntegral v124
  294             , pc_ILDV_CREATE_MASK = v125
  295             , pc_ILDV_STATE_CREATE = v126
  296             , pc_ILDV_STATE_USE = v127
  297             }
  298     _ -> error "Invalid platform constants"
  299