# # # The Nim Compiler # (c) Copyright 2015 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. # # This module implements the transformator. It transforms the syntax tree # to ease the work of the code generators. Does some transformations: # # * inlines iterators # * inlines constants # * performs constant folding # * converts "continue" to "break"; disambiguates "break" # * introduces method dispatchers # * performs lambda lifting for closure support # * transforms 'defer' into a 'try finally' statement import options, ast, astalgo, trees, msgs, idents, renderer, types, semfold, magicsys, cgmeth, lowerings, injectdestructors, liftlocals, modulegraphs, lineinfos proc transformBody*(g: ModuleGraph, prc: PSym, cache = true; noDestructors = false): PNode import closureiters, lambdalifting type PTransNode* = distinct PNode PTransCon = ref TTransCon TTransCon{.final.} = object # part of TContext; stackable mapping: TIdNodeTable # mapping from symbols to nodes owner: PSym # current owner forStmt: PNode # current for stmt forLoopBody: PTransNode # transformed for loop body yieldStmts: int # we count the number of yield statements, # because we need to introduce new variables # if we encounter the 2nd yield statement next: PTransCon # for stacking TTransfContext = object of TPassContext module: PSym transCon: PTransCon # top of a TransCon stack inlining: int # > 0 if we are in inlining context (copy vars) nestedProcs: int # > 0 if we are in a nested proc contSyms, breakSyms: seq[PSym] # to transform 'continue' and 'break' deferDetected, tooEarly, needsDestroyPass, noDestructors: bool graph: ModuleGraph PTransf = ref TTransfContext proc newTransNode(a: PNode): PTransNode {.inline.} = result = PTransNode(shallowCopy(a)) proc newTransNode(kind: TNodeKind, info: TLineInfo, sons: int): PTransNode {.inline.} = var x = newNodeI(kind, info) newSeq(x.sons, sons) result = x.PTransNode proc newTransNode(kind: TNodeKind, n: PNode, sons: int): PTransNode {.inline.} = var x = newNodeIT(kind, n.info, n.typ) newSeq(x.sons, sons) x.typ = n.typ # x.flags = n.flags result = x.PTransNode proc add(a, b: PTransNode) {.inline.} = addSon(PNode(a), PNode(b)) proc len(a: PTransNode): int {.inline.} = sonsLen(a.PNode) proc `[]=`(a: PTransNode, i: int, x: PTransNode) {.inline.} = var n = PNode(a) n.sons[i] = PNode(x) proc `[]=`(a: PTransNode, i: BackwardsIndex, x: PTransNode) {.inline.} = `[]=`(a, a.len - i.int, x) proc `[]`(a: PTransNode, i: int): PTransNode {.inline.} = var n = PNode(a) result = n.sons[i].PTransNode proc `[]`(a: PTransNode, i: BackwardsIndex): PTransNode {.inline.} = `[]`(a, a.len - i.int) proc newTransCon(owner: PSym): PTransCon = assert owner != nil new(result) initIdNodeTable(result.mapping) result.owner = owner proc pushTransCon(c: PTransf, t: PTransCon) = t.next = c.transCon c.transCon = t proc popTransCon(c: PTransf) = if (c.transCon == nil): internalError(c.graph.config, "popTransCon") c.transCon = c.transCon.next proc getCurrOwner(c: PTransf): PSym = if c.transCon != nil: result = c.transCon.owner else: result = c.module proc newTemp(c: PTransf, typ: PType, info: TLineInfo): PNode = let r = newSym(skTemp, getIdent(c.graph.cache, genPrefix), getCurrOwner(c), info) r.typ = typ #skipTypes(typ, {tyGenericInst, tyAlias, tySink}) incl(r.flags, sfFromGeneric) let owner = getCurrOwner(c) if owner.isIterator and not c.tooEarly: result = freshVarForClosureIter(c.graph, r, owner) else: result = newSym
discard """
output: '''OK'''
"""
#bug #8468
import encodings, strutils
when defined(windows):
var utf16to8 = open(destEncoding = "utf-16", srcEncoding = "utf-8")
var s = "some string"
var c = utf16to8.convert(s)
var z = newStringOfCap(s.len * 2)
for x in s:
z.add x
z.add chr(0)
doAssert z == c
echo "OK"