summary refs log tree commit diff stats
diff options
context:
space:
mode:
authorAraq <rumpf_a@web.de>2019-10-19 18:03:50 +0200
committerAndreas Rumpf <rumpf_a@web.de>2019-10-20 08:11:07 +0200
commited2fb36bc61bd5272734899783ede5e6f285da0e (patch)
tree00a45a08f74b73158d24400366ace8c6a8ff36e7
parent61ea85687c2950bb40c23a1a7cd2c13473bd9662 (diff)
downloadNim-ed2fb36bc61bd5272734899783ede5e6f285da0e.tar.gz
refactoring: use the new strings and seqs when optSeqDestructors is active
-rw-r--r--compiler/ccgexprs.nim40
-rw-r--r--compiler/ccgtypes.nim12
-rw-r--r--compiler/cgen.nim10
-rw-r--r--compiler/commands.nim1
-rw-r--r--compiler/lambdalifting.nim6
-rw-r--r--compiler/liftdestructors.nim6
-rw-r--r--compiler/semtypes.nim27
-rw-r--r--compiler/sigmatch.nim5
-rw-r--r--compiler/sizealignoffsetimpl.nim4
9 files changed, 45 insertions, 66 deletions
diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim
index 13656acad..cc4e8de42 100644
--- a/compiler/ccgexprs.nim
+++ b/compiler/ccgexprs.nim
@@ -79,7 +79,7 @@ proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
       # with the new semantics for 'nil' strings, we can map "" to nil and
       # save tons of allocations:
       if n.strVal.len == 0 and optNilSeqs notin p.options and
-          p.config.selectedGC != gcDestructors:
+          optSeqDestructors notin p.config.globalOptions:
         result = genNilStringLiteral(p.module, n.info)
       else:
         result = genStringLiteral(p.module, n)
@@ -250,7 +250,7 @@ proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   # tfShallow flag for the built-in string type too! So we check only
   # here for this flag, where it is reasonably safe to do so
   # (for objects, etc.):
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     linefmt(p, cpsStmts,
         "$1 = $2;$n",
         [rdLoc(dest), rdLoc(src)])
@@ -279,7 +279,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
   of tyRef:
     genRefAssign(p, dest, src)
   of tySequence:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       genGenericAsgn(p, dest, src, flags)
     elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode, dest):
       genRefAssign(p, dest, src)
@@ -288,7 +288,7 @@ proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
               [addrLoc(p.config, dest), rdLoc(src),
               genTypeInfo(p.module, dest.t, dest.lode.info)])
   of tyString:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       genGenericAsgn(p, dest, src, flags)
     elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode, dest):
       genRefAssign(p, dest, src)
@@ -934,7 +934,7 @@ proc genSeqElem(p: BProc, n, x, y: PNode, d: var TLoc) =
     a.r = ropecg(p.module, "(*$1)", [a.r])
 
   if lfPrepareForMutation in d.flags and ty.kind == tyString and
-      p.config.selectedGC == gcDestructors:
+      optSeqDestructors in p.config.globalOptions:
     linefmt(p, cpsStmts, "#nimPrepareStrMutationV2($1);$n", [byRefLoc(p, a)])
   putIntoDest(p, d, n,
               ropecg(p.module, "$1$3[$2]", [rdLoc(a), rdCharLoc(b), dataField(p)]), a.storage)
@@ -1060,7 +1060,7 @@ proc gcUsage(conf: ConfigRef; n: PNode) =
   if conf.selectedGC == gcNone: message(conf, n.info, warnGcMem, n.renderTree)
 
 proc strLoc(p: BProc; d: TLoc): Rope =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     result = byRefLoc(p, d)
   else:
     result = rdLoc(d)
@@ -1141,7 +1141,7 @@ proc genStrAppend(p: BProc, e: PNode, d: var TLoc) =
         add(lens, " + ")
       add(appends, ropecg(p.module, "#appendString($1, $2);$n",
                         [strLoc(p, dest), rdLoc(a)]))
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     linefmt(p, cpsStmts, "#prepareAdd($1, $2$3);$n",
             [byRefLoc(p, dest), lens, L])
   else:
@@ -1288,7 +1288,7 @@ proc genNewSeq(p: BProc, e: PNode) =
   var a, b: TLoc
   initLocExpr(p, e.sons[1], a)
   initLocExpr(p, e.sons[2], b)
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     let seqtype = skipTypes(e.sons[1].typ, abstractVarRange)
     linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3));$n",
       [a.rdLoc, b.rdLoc, getTypeDesc(p.module, seqtype.lastSon),
@@ -1303,7 +1303,7 @@ proc genNewSeqOfCap(p: BProc; e: PNode; d: var TLoc) =
   let seqtype = skipTypes(e.typ, abstractVarRange)
   var a: TLoc
   initLocExpr(p, e.sons[1], a)
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     if d.k == locNone: getTemp(p, e.typ, d, needsInit=false)
     linefmt(p, cpsStmts, "$1.len = 0; $1.p = ($4*) #newSeqPayload($2, sizeof($3));$n",
       [d.rdLoc, a.rdLoc, getTypeDesc(p.module, seqtype.lastSon),
@@ -1403,7 +1403,7 @@ proc genSeqConstr(p: BProc, n: PNode, d: var TLoc) =
     getTemp(p, n.typ, d)
 
   let l = intLiteral(len(n))
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     let seqtype = n.typ
     linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3));$n",
       [rdLoc dest[], l, getTypeDesc(p.module, seqtype.lastSon),
@@ -1434,7 +1434,7 @@ proc genArrToSeq(p: BProc, n: PNode, d: var TLoc) =
     getTemp(p, n.typ, d)
   # generate call to newSeq before adding the elements per hand:
   let L = toInt(lengthOrd(p.config, n.sons[1].typ))
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     let seqtype = n.typ
     linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3));$n",
       [rdLoc d, L, getTypeDesc(p.module, seqtype.lastSon),
@@ -1654,7 +1654,7 @@ proc makeAddr(n: PNode): PNode =
     result.typ = makePtrType(n.typ)
 
 proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     e.sons[1] = makeAddr(e[1])
     genCall(p, e, d)
     return
@@ -1683,7 +1683,7 @@ proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
   gcUsage(p.config, e)
 
 proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     binaryStmtAddr(p, e, d, "setLengthStrV2")
   else:
     var a, b, call: TLoc
@@ -1897,7 +1897,7 @@ proc genSomeCast(p: BProc, e: PNode, d: var TLoc) =
     if srcTyp.kind in {tyPtr, tyPointer} and etyp.kind in IntegralTypes:
       putIntoDest(p, d, e, "(($1) (ptrdiff_t) ($2))" %
           [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.storage)
-    elif p.config.selectedGC == gcDestructors and etyp.kind in {tySequence, tyString}:
+    elif optSeqDestructors in p.config.globalOptions and etyp.kind in {tySequence, tyString}:
       putIntoDest(p, d, e, "(*($1*) (&$2))" %
           [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.storage)
     else:
@@ -2025,7 +2025,7 @@ proc genMove(p: BProc; n: PNode; d: var TLoc) =
     resetLoc(p, a)
 
 proc genDestroy(p: BProc; n: PNode) =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     let arg = n[1].skipAddr
     let t = arg.typ.skipTypes(abstractInst)
     case t.kind
@@ -2120,7 +2120,7 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
 
   of mConStrStr: genStrConcat(p, e, d)
   of mAppendStrCh:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       binaryStmtAddr(p, e, d, "nimAddCharV1")
     else:
       var dest, b, call: TLoc
@@ -2131,7 +2131,7 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
       genAssignment(p, dest, call, {})
   of mAppendStrStr: genStrAppend(p, e, d)
   of mAppendSeqElem:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       e.sons[1] = makeAddr(e[1])
       genCall(p, e, d)
     else:
@@ -2713,7 +2713,7 @@ proc getDefaultValue(p: BProc; typ: PType; info: TLineInfo): Rope =
      tyTyped, tyTypeDesc, tyStatic, tyRef, tyNil:
     result = rope"NIM_NIL"
   of tyString, tySequence:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       result = rope"{0, NIM_NIL}"
     else:
       result = rope"NIM_NIL"
@@ -2855,7 +2855,7 @@ proc genConstExpr(p: BProc, n: PNode): Rope =
   of nkBracket, nkPar, nkTupleConstr, nkClosure:
     var t = skipTypes(n.typ, abstractInstOwned)
     if t.kind == tySequence:
-      if p.config.selectedGC == gcDestructors:
+      if optSeqDestructors in p.config.globalOptions:
         result = genConstSeqV2(p, n, n.typ)
       else:
         result = genConstSeq(p, n, n.typ)
@@ -2879,7 +2879,7 @@ proc genConstExpr(p: BProc, n: PNode): Rope =
   of nkObjConstr:
     result = genConstObjConstr(p, n)
   of nkStrLit..nkTripleStrLit:
-    if p.config.selectedGC == gcDestructors:
+    if optSeqDestructors in p.config.globalOptions:
       result = genStringLiteralV2Const(p.module, n)
     else:
       var d: TLoc
diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim
index 3e06da146..de1f0e497 100644
--- a/compiler/ccgtypes.nim
+++ b/compiler/ccgtypes.nim
@@ -356,7 +356,7 @@ proc addForwardStructFormat(m: BModule, structOrUnion: Rope, typename: Rope) =
     m.s[cfsForwardTypes].addf "typedef $1 $2 $2;$n", [structOrUnion, typename]
 
 proc seqStar(m: BModule): string =
-  if m.config.selectedGC == gcDestructors: result = ""
+  if optSeqDestructors in m.config.globalOptions: result = ""
   else: result = "*"
 
 proc getTypeForward(m: BModule, typ: PType; sig: SigHash): Rope =
@@ -390,7 +390,7 @@ proc getTypeDescWeak(m: BModule; t: PType; check: var IntSet): Rope =
       pushType(m, t)
   of tySequence:
     let sig = hashType(t)
-    if m.config.selectedGC == gcDestructors:
+    if optSeqDestructors in m.config.globalOptions:
       if skipTypes(etB.sons[0], typedescInst).kind == tyEmpty:
         internalError(m.config, "cannot map the empty seq type to a C type")
 
@@ -710,7 +710,7 @@ proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope =
         result = name & star
         m.typeCache[sig] = result
     of tySequence:
-      if m.config.selectedGC == gcDestructors:
+      if optSeqDestructors in m.config.globalOptions:
         result = getTypeDescWeak(m, et, check) & star
         m.typeCache[sig] = result
       else:
@@ -770,7 +770,7 @@ proc getTypeDescAux(m: BModule, origTyp: PType, check: var IntSet): Rope =
             "void* ClE_0;$n} $1;$n",
              [result, rettype, desc])
   of tySequence:
-    if m.config.selectedGC == gcDestructors:
+    if optSeqDestructors in m.config.globalOptions:
       result = getTypeDescWeak(m, t, check)
     else:
       # we cannot use getTypeForward here because then t would be associated
@@ -926,7 +926,7 @@ proc finishTypeDescriptions(m: BModule) =
   var check = initIntSet()
   while i < len(m.typeStack):
     let t = m.typeStack[i]
-    if m.config.selectedGC == gcDestructors and t.skipTypes(abstractInst).kind == tySequence:
+    if optSeqDestructors in m.config.globalOptions and t.skipTypes(abstractInst).kind == tySequence:
       seqV2ContentType(m, t, check)
     else:
       discard getTypeDescAux(m, t, check)
@@ -1351,7 +1351,7 @@ proc genTypeInfo(m: BModule, t: PType; info: TLineInfo): Rope =
       genTupleInfo(m, x, x, result, info)
   of tySequence:
     genTypeInfoAux(m, t, t, result, info)
-    if m.config.selectedGC != gcDestructors:
+    if optSeqDestructors notin m.config.globalOptions:
       if m.config.selectedGC >= gcMarkAndSweep:
         let markerProc = genTraverseProc(m, origType, sig)
         addf(m.s[cfsTypeInit3], "$1.marker = $2;$n", [tiNameForHcr(m, result), markerProc])
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index 0c03c7171..5809a4049 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -293,13 +293,13 @@ proc lenField(p: BProc): Rope =
   result = rope(if p.module.compileToCpp: "len" else: "Sup.len")
 
 proc lenExpr(p: BProc; a: TLoc): Rope =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     result = rdLoc(a) & ".len"
   else:
     result = "($1 ? $1->$2 : 0)" % [rdLoc(a), lenField(p)]
 
 proc dataField(p: BProc): Rope =
-  if p.config.selectedGC == gcDestructors:
+  if optSeqDestructors in p.config.globalOptions:
     result = rope".p->data"
   else:
     result = rope"->data"
@@ -377,10 +377,10 @@ proc isComplexValueType(t: PType): bool {.inline.} =
     (t.kind == tyProc and t.callConv == ccClosure)
 
 proc resetLoc(p: BProc, loc: var TLoc) =
-  let containsGcRef = p.config.selectedGC != gcDestructors and containsGarbageCollectedRef(loc.t)
+  let containsGcRef = optSeqDestructors notin p.config.globalOptions and containsGarbageCollectedRef(loc.t)
   let typ = skipTypes(loc.t, abstractVarRange)
   if isImportedCppType(typ): return
-  if p.config.selectedGC == gcDestructors and typ.kind in {tyString, tySequence}:
+  if optSeqDestructors in p.config.globalOptions and typ.kind in {tyString, tySequence}:
     assert rdLoc(loc) != nil
     linefmt(p, cpsStmts, "$1.len = 0; $1.p = NIM_NIL;$n", [rdLoc(loc)])
   elif not isComplexValueType(typ):
@@ -411,7 +411,7 @@ proc resetLoc(p: BProc, loc: var TLoc) =
 
 proc constructLoc(p: BProc, loc: TLoc, isTemp = false) =
   let typ = loc.t
-  if p.config.selectedGC == gcDestructors and skipTypes(typ, abstractInst).kind in {tyString, tySequence}:
+  if optSeqDestructors in p.config.globalOptions and skipTypes(typ, abstractInst).kind in {tyString, tySequence}:
     linefmt(p, cpsStmts, "$1.len = 0; $1.p = NIM_NIL;$n", [rdLoc(loc)])
   elif not isComplexValueType(typ):
     linefmt(p, cpsStmts, "$1 = ($2)0;$n", [rdLoc(loc),
diff --git a/compiler/commands.nim b/compiler/commands.nim
index 0ca99e2ce..05626a9c3 100644
--- a/compiler/commands.nim
+++ b/compiler/commands.nim
@@ -452,6 +452,7 @@ proc processSwitch*(switch, arg: string, pass: TCmdLinePass, info: TLineInfo;
       of "destructors":
         conf.selectedGC = gcDestructors
         defineSymbol(conf.symbols, "gcdestructors")
+        incl conf.globalOptions, optSeqDestructors
       of "go":
         conf.selectedGC = gcGo
         defineSymbol(conf.symbols, "gogc")
diff --git a/compiler/lambdalifting.nim b/compiler/lambdalifting.nim
index 612cc3b17..2ea5f5263 100644
--- a/compiler/lambdalifting.nim
+++ b/compiler/lambdalifting.nim
@@ -342,9 +342,9 @@ proc createUpField(c: var DetectionPass; dest, dep: PSym; info: TLineInfo) =
   let obj = refObj.skipTypes({tyOwned, tyRef})
   # The assumption here is that gcDestructors means we cannot deal
   # with cycles properly, so it's better to produce a weak ref (=ptr) here.
-  # This seems to be generally correct but since it's a bit risky it's only
-  # enabled for gcDestructors.
-  let fieldType = if false: # c.graph.config.selectedGC == gcDestructors:
+  # This seems to be generally correct but since it's a bit risky it's disabled
+  # for now.
+  let fieldType = if false: # optSeqDestructors in c.graph.config.globalOptions:
                     c.getEnvTypeForOwnerUp(dep, info) #getHiddenParam(dep).typ
                   else:
                     c.getEnvTypeForOwner(dep, info)
diff --git a/compiler/liftdestructors.nim b/compiler/liftdestructors.nim
index 69a4a55ee..ffdf3e16e 100644
--- a/compiler/liftdestructors.nim
+++ b/compiler/liftdestructors.nim
@@ -129,7 +129,7 @@ proc newDeepCopyCall(op: PSym; x, y: PNode): PNode =
   result = newAsgnStmt(x, newOpCall(op, y))
 
 proc useNoGc(c: TLiftCtx; t: PType): bool {.inline.} =
-  result = c.g.config.selectedGC == gcDestructors and
+  result = optSeqDestructors in c.g.config.globalOptions and
     ({tfHasGCedMem, tfHasOwned} * t.flags != {} or t.isGCedMem)
 
 proc instantiateGeneric(c: var TLiftCtx; op: PSym; t, typeInst: PType): PSym =
@@ -142,7 +142,7 @@ proc instantiateGeneric(c: var TLiftCtx; op: PSym; t, typeInst: PType): PSym =
 
 proc considerAsgnOrSink(c: var TLiftCtx; t: PType; body, x, y: PNode;
                         field: var PSym): bool =
-  if c.g.config.selectedGC == gcDestructors:
+  if optSeqDestructors in c.g.config.globalOptions:
     let op = field
     if field != nil and sfOverriden in field.flags:
       if sfError in op.flags:
@@ -488,7 +488,7 @@ proc fillBody(c: var TLiftCtx; t: PType; body, x, y: PNode) =
   of tySequence:
     if useNoGc(c, t):
       useSeqOrStrOp(c, t, body, x, y)
-    elif c.g.config.selectedGC == gcDestructors:
+    elif optSeqDestructors in c.g.config.globalOptions:
       # note that tfHasAsgn is propagated so we need the check on
       # 'selectedGC' here to determine if we have the new runtime.
       discard considerUserDefinedOp(c, t, body, x, y)
diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim
index 7e42a120c..3fdeb144d 100644
--- a/compiler/semtypes.nim
+++ b/compiler/semtypes.nim
@@ -1668,26 +1668,9 @@ proc semTypeNode(c: PContext, n: PNode, prev: PType): PType =
     of mSet: result = semSet(c, n, prev)
     of mOrdinal: result = semOrdinal(c, n, prev)
     of mSeq:
-      if false: # c.config.selectedGC == gcDestructors and optNimV2 notin c.config.globalOptions:
-        let s = c.graph.sysTypes[tySequence]
-        assert s != nil
-        assert prev == nil
-        result = copyType(s, s.owner, keepId=false)
-        # Remove the 'T' parameter from tySequence:
-        result.sons.setLen 0
-        result.n = nil
-        result.flags = {tfHasAsgn}
-        semContainerArg(c, n, "seq", result)
-        if result.len > 0:
-          var base = result[0]
-          if base.kind in {tyGenericInst, tyAlias, tySink}: base = lastSon(base)
-          if not containsGenericType(base):
-            # base.kind != tyGenericParam:
-            c.typesWithOps.add((result, result))
-      else:
-        result = semContainer(c, n, tySequence, "seq", prev)
-        if c.config.selectedGC == gcDestructors:
-          incl result.flags, tfHasAsgn
+      result = semContainer(c, n, tySequence, "seq", prev)
+      if optSeqDestructors in c.config.globalOptions:
+        incl result.flags, tfHasAsgn
     of mOpt: result = semContainer(c, n, tyOpt, "opt", prev)
     of mVarargs: result = semVarargs(c, n, prev)
     of mTypeDesc, mType, mTypeOf:
@@ -1862,7 +1845,7 @@ proc processMagicType(c: PContext, m: PSym) =
   of mString:
     setMagicType(c.config, m, tyString, szUncomputedSize)
     rawAddSon(m.typ, getSysType(c.graph, m.info, tyChar))
-    if c.config.selectedGC == gcDestructors:
+    if optSeqDestructors in c.config.globalOptions:
       incl m.typ.flags, tfHasAsgn
   of mCstring:
     setMagicIntegral(c.config, m, tyCString, c.config.target.ptrSize)
@@ -1903,7 +1886,7 @@ proc processMagicType(c: PContext, m: PSym) =
     setMagicIntegral(c.config, m, tyUncheckedArray, szUncomputedSize)
   of mSeq:
     setMagicType(c.config, m, tySequence, szUncomputedSize)
-    if c.config.selectedGC == gcDestructors:
+    if optSeqDestructors in c.config.globalOptions:
       incl m.typ.flags, tfHasAsgn
     assert c.graph.sysTypes[tySequence] == nil
     c.graph.sysTypes[tySequence] = m.typ
diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim
index 10141e645..a5e588bab 100644
--- a/compiler/sigmatch.nim
+++ b/compiler/sigmatch.nim
@@ -2590,11 +2590,6 @@ proc instTypeBoundOp*(c: PContext; dc: PSym; t: PType; info: TLineInfo;
     if f.kind in {tyRef, tyPtr}: f = f.lastSon
   else:
     if f.kind == tyVar: f = f.lastSon
-  #if c.config.selectedGC == gcDestructors and f.kind == tySequence:
-  # use the canonical type to access the =sink and =destroy etc.
-  #  f = c.graph.sysTypes[tySequence]
-  #echo "YUP_---------Formal ", typeToString(f, preferDesc), " real ", typeToString(t, preferDesc), " ", f.id, " ", t.id
-
   if typeRel(m, f, t) == isNone:
     localError(c.config, info, "cannot instantiate: '" & dc.name.s & "'")
   else:
diff --git a/compiler/sizealignoffsetimpl.nim b/compiler/sizealignoffsetimpl.nim
index 1692aaf64..f57969712 100644
--- a/compiler/sizealignoffsetimpl.nim
+++ b/compiler/sizealignoffsetimpl.nim
@@ -231,7 +231,7 @@ proc computeSizeAlign(conf: ConfigRef; typ: PType) =
     typ.size = conf.target.ptrSize
     typ.align = int16(conf.target.ptrSize)
   of tyString:
-    if conf.selectedGC == gcDestructors:
+    if optSeqDestructors in conf.globalOptions:
       typ.size = conf.target.ptrSize * 2
     else:
       typ.size = conf.target.ptrSize
@@ -245,7 +245,7 @@ proc computeSizeAlign(conf: ConfigRef; typ: PType) =
       typ.paddingAtEnd = szIllegalRecursion
       return
     typ.align = int16(conf.target.ptrSize)
-    if typ.kind == tySequence and conf.selectedGC == gcDestructors:
+    if typ.kind == tySequence and optSeqDestructors in conf.globalOptions:
       typ.size = conf.target.ptrSize * 2
     else:
       typ.size = conf.target.ptrSize