# # # The Nim Compiler # (c) Copyright 2014 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. # ## This file implements the FFI part of the evaluator for Nim code. import ast, astalgo, ropes, types, options, tables, dynlib, libffi, msgs, os when defined(windows): const libcDll = "msvcrt.dll" else: const libcDll = "libc.so(.6|.5|)" type TDllCache = tables.TTable[string, TLibHandle] var gDllCache = initTable[string, TLibHandle]() when defined(windows): var gExeHandle = loadLib(os.getAppFilename()) else: var gExeHandle = loadLib() proc getDll(cache: var TDllCache; dll: string; info: TLineInfo): pointer = result = cache[dll] if result.isNil: var libs: seq[string] = @[] libCandidates(dll, libs) for c in libs: result = loadLib(c) if not result.isNil: break if result.isNil: globalError(info, "cannot load: " & dll) cache[dll] = result const nkPtrLit = nkIntLit # hopefully we can get rid of this hack soon var myerrno {.importc: "errno", header: "".}: cint ## error variable proc importcSymbol*(sym: PSym): PNode = let name = ropeToStr(sym.loc.r) # the AST does not support untyped pointers directly, so we use an nkIntLit # that contains the address instead: result = newNodeIT(nkPtrLit, sym.info, sym.typ) case name of "stdin": result.intVal = cast[TAddress](system.stdin) of "stdout": result.intVal = cast[TAddress](system.stdout) of "stderr": result.intVal = cast[TAddress](system.stderr) of "vmErrnoWrapper": result.intVal = cast[TAddress](myerrno) else: let lib = sym.annex if lib != nil and lib.path.kind notin {nkStrLit..nkTripleStrLit}: globalError(sym.info, "dynlib needs to be a string lit for the REPL") var theAddr: pointer if lib.isNil and not gExehandle.isNil: # first try this exe itself: theAddr = gExehandle.symAddr(name) # then try libc: if theAddr.isNil: let dllhandle = gDllCache.getDll(libcDll, sym.info) theAddr = dllhandle.symAddr(name) elif not lib.isNil: let dllhandle = gDllCache.getDll(if lib.kind == libHeader: libcDll else: lib.path.strVal, sym.info) theAddr = dllhandle.symAddr(name) if theAddr.isNil: globalError(sym.info, "cannot import: " & sym.name.s) result.intVal = cast[TAddress](theAddr) proc mapType(t: ast.PType): ptr libffi.TType = if t == nil: return addr libffi.type_void case t.kind of tyBool, tyEnum, tyChar, tyInt..tyInt64, tyUInt..tyUInt64, tySet: case t.getSize of 1: result = addr libffi.type_uint8 of 2: result = addr libffi.type_sint16 of 4: result = addr libffi.type_sint32 of 8: result = addr libffi.type_sint64 else: result = nil of tyFloat, tyFloat64: result = addr libffi.type_double of tyFloat32: result = addr libffi.type_float of tyVar, tyPointer, tyPtr, tyRef, tyCString, tySequence, tyString, tyExpr, tyStmt, tyTypeDesc, tyProc, tyArray, tyArrayConstr, tyStatic, tyNil: result = addr libffi.type_pointer of tyDistinct: result = mapType(t.sons[0]) else: result = nil # too risky: #of tyFloat128: result = addr libffi.type_longdouble proc mapCallConv(cc: TCallingConvention, info: TLineInfo): TABI = case cc of ccDefault: result = DEFAULT_ABI of ccStdCall: result = when defined(windows): STDCALL else: DEFAULT_ABI of ccCDecl: result = DEFAULT_ABI else: globalError(info, "cannot map calling convention to FFI") template rd(T,
import algorithm

doAssert product[int](newSeq[seq[int]]()) == newSeq[seq[int]](), "empty input"
doAssert product[int](@[newSeq[int](), @[], @[]]) == newSeq[seq[int]](), "bit more empty input"
doAssert product(@[@[1,2]]) == @[@[1,2]], "a simple case of one element"
doAssert product(@[@[1,2], @[3,4]]) == @[@[2,4],@[1,4],@[2,3],@[1,3]], "two elements"
doAssert product(@[@[1,2], @[3,4], @[5,6]]) == @[@[2,4,6],@[1,4,6],@[2,3,6],@[1,3,6], @[2,4,5],@[1,4,5],@[2,3,5],@[1,3,5]], "three elements"
doAssert product(@[@[1,2], @[]]) == newSeq[seq[int]](), "two elements, but one empty"
doAssert lowerBound([1,2,4], 3, system.cmp[int]) == 2
doAssert lowerBound([1,2,2,3], 4, system.cmp[int])