[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

api[nodejs] code

Reference:

Source code

NativeLibraryObject
 subclass: #NodeJS
 category: #NodeJS!
NodeJS comment: '
	Framework to run S8 systems on node.js execution engine.
	http://nodejs.org/docs/latest/api/index.html
	@2012 Alejandro Reimondo - [email protected]
'!

! Object methodsFor: #NodeJS-tools !
require: aName
	" Returns the native object/module bound at aName. "

	^# #require: aName! !

! NodeJS class methodsFor: #query !
isValid
	" Private - Returns true if the native interface is running. "

	| native |
	native := Smalltalk nativeObjectAt: #process ifAbsent: [].
	^native notNil! !

! NodeJS class methodsFor: #accessing !
platform
	" Private - Return the platform string (or nil if invalid). "

	^self isValid ifTrue: [ #{process} basicAt: #platform ]! !

! NodeJS class methodsFor: 'code generation' !
classToken
	" Private - Return the classToken to prepend/tag the receiver. "

	^#Node! !

! NodeJS class methodsFor: #modules !
requireModule: aName
	" Private - Return an instance of the receiver wrappping native object/module at aName. "

	^self @ (self require: aName)! !

"---------- Custom Code Generation Utilities-----------------"!

! NodeJS class methodsFor: #builders !
wrapFunctions: selectors
	" Private - Generate code to delegate selectors on instance handle. "

	self buildFunctions: (self buildFunctionsSpec: selectors withHandles: false)! !

! NodeJS class methodsFor: #builders !
wrapHandleFunctions: selectors
	" Private - Generate code to delegate selectors on instance handle. "

	self buildFunctions: (self buildFunctionsSpec: selectors withHandles: true)! !

! NodeJS class methodsFor: #builders !
buildFunctionsSpec: selectors withHandles: withHandles
	" Private - Return the builder spec for wrapped functions. "

	^selectors collect: [:each |
		self buildFunctionSpec: each withHandles: withHandles
	]! !

! NodeJS class methodsFor: #builders !
buildFunctionSpec: what withHandles: withHandles
	" Private - Return the builder spec for wrapped function what. "

	| type selector args |
	(what isString and: [(what includes: $:) not]) ifTrue: [ ^what ].
	what isArray ifTrue: [
		selector := what last.
		type := what first.
	] ifFalse: [
		selector := what.
		type := nil.
	].
	args :=  (1 to: (selector occurrencesOf: $:)) collect: [:i| #arg ,i asString ].
	args size = 1 ifTrue: [ args := #( #anObject ) ].
	withHandles ifTrue: [ args := args collect: [:each| Array with: each with: #handle ] ].
	^type isNil
		ifTrue: [ Array with: selector with: args ]
		ifFalse: [ Array with: selector with: args with: type ]! !

"---------- Build Interface -----------------"
NodeJS buildSubclasses: #(
	#Assert
	#Buffer
	#(#Buffer #(size)) #(#Buffer #(array)) #(#Buffer #(buffer))
	#(#Buffer #(string)) #(#Buffer #(string encoding))
	#Cluster #Worker
	#Console
	#(#Console #(stdout))
	#(#Console #(stdout stderr))
	#Crypto #Certificate
	#EventEmitter
	#TLS #TLSServer #TLSCleartextStream #TLSSecurePair
	#FileSystem #Stats #FSWatcher
	#Path #Net #DNS
	#HTTP #HTTPS
	#URL #QueryString
	#Readline #REPL
	#VM #Script
	#TTY
	#Util
	#Zlib #OS
).!
NodeEventEmitter buildSubclasses: #(
	#ChildProcess
	#Process #Stream
	#HTTPServer
	#HTTPServerRequest
	#HTTPClientRequest
).!
NodeStream buildSubclasses: #(
	#ReadStream #WriteStream #DuplexStream
	#Gzip #Gunzip #Deflate #Inflate
	#DeflateRaw #InflateRaw
	#Unzip
	#CryptoAlgorithm
).!
NodeDuplexStream buildSubclasses: #(
	#NetSocket #( #NetSocket #( #options ) )
	#Dgram
).!
NodeWriteStream buildSubclasses: #(
	#HTTPServerResponse
).!
NodeReadStream buildSubclasses: #(
	#HTTPClientResponse #IncomingMessage
).!
NodeNetSocket buildSubclasses: #(
	#NetServer
).!
NodeCryptoAlgorithm buildSubclasses: #(
	#Hash #Hmac
	#Cipher #Cipheriv
	#Decipher #Decipheriv
	#Sign #Verify
	#DiffieHellman #ECDH
).!
NodeNetServer buildSubclasses: #(
	#TLSServer
).!
NodeHTTP buildSubclasses: #(
	 #HTTPAgent #(#HTTPAgent #(options))
).!
NodeHTTPAgent buildSubclasses: #(
	#HTTPSAgent
).!

"---------- Build accessors -----------------"!
NodeAssert comment: 'This module is used so that Node.js can test itself.'!
NodeAssert buildFunctions: #(
	#assert:message: #ok:message: #ok:
	#deepEqual:expected:message: #deepEqual:expected:
	#doesNotThrow:error:message: #doesNotThrow:error: #doesNotThrow:
	#equal:expected:message: #equal:expected:
	#fail:expected:message:operator:
	#ifError:
	#notDeepEqual:expected:message: #notDeepEqual:expected:
	#notDeepStrictEqual:expected:message: #notDeepStrictEqual:expected:
	#notEqual:expected:message: #notEqual:expected:
	#notStrickEqual:expected:message: #notStrickEqual:expected:
	#strickEqual:expected:message: #strickEqual:expected:
	#throws:error:message: #throws:error: #throws:
).!

NodeBuffer comment: '
	Raw data is stored in instances of Buffer.
	A Buffer is similar to an array of integers but corresponds to a raw memory allocation outside the VM heap.
	A Buffer cannot be resized.'!
NodeBuffer "iterators" buildGetters: #( entries keys values ).!
NodeBuffer buildGetters: #( #length ).!
NodeBuffer buildFunctions: #(
	#(#compare: #(#(aBuffer handle)))
	#(#copy:targetStart:sourceStart:sourceEnd: #(#(targetBuffer handle) targetStart sourceStart sourceEnd ))
	#(#copy:targetStart:sourceStart: #(#(targetBuffer handle) targetStart sourceStart))
	#(#copy:targetStart: #(#(targetBuffer handle) targetStart))
	#(#copy: #(#(targetBuffer handle)))
	#(#equals: #(#(aBuffer handle)))
	#(#fill:offset:end: #(value offset end))
	#(#fill:offset: #(value offset))
	#(#fill: #(value))
	#(#indexOf:byteOffset: #(value byteOffset))
	#(#indexOf: #(value))
	#(#readDoubleBE:noAssert: #(offset aBoolean)) #(#readDoubleBE: #(offset))
	#(#readDoubleLE:noAssert: #(offset aBoolean)) #(#readDoubleLE: #(offset))
	#(#readFloatBE:noAssert: #(offset aBoolean)) #(#readFloatBE: #(offset))
	#(#readFloatLE:noAssert: #(offset aBoolean)) #(#readFloatLE: #(offset))
	#(#readInt8:noAssert: #(offset aBoolean)) #(#readInt8: #(offset))
	#(#readInt16BE:noAssert: #(offset aBoolean)) #(#readInt16BE: #(offset))
	#(#readInt16LE:noAssert: #(offset aBoolean)) #(#readInt16LE: #(offset))
	#(#readInt32BE:noAssert: #(offset aBoolean)) #(#readInt32BE: #(offset))
	#(#readInt32LE:noAssert: #(offset aBoolean)) #(#readInt32LE: #(offset))
	#(#readIntBE:noAssert: #(offset aBoolean)) #(#readIntBE: #(offset))
	#(#readIntLE:noAssert: #(offset aBoolean)) #(#readIntLE: #(offset))
	#(#readUInt8:noAssert: #(offset aBoolean)) #(#readUInt8: #(offset))
	#(#readUInt16BE:noAssert: #(offset aBoolean)) #(#readUInt16BE: #(offset))
	#(#readUInt16LE:noAssert: #(offset aBoolean)) #(#readUInt16LE: #(offset))
	#(#readUInt32BE:noAssert: #(offset aBoolean)) #(#readUInt32BE: #(offset))
	#(#readUInt32LE:noAssert: #(offset aBoolean)) #(#readUInt32LE: #(offset))
	#(#readUIntBE:noAssert: #(offset aBoolean)) #(#readUIntBE: #(offset))
	#(#readUIntLE:noAssert: #(offset aBoolean)) #(#readUIntLE: #(offset))
	#(#slice:end: #(start end) #NodeBuffer)
	#(#slice: #(start) #NodeBuffer)
	#(#toString:start:end: #(encoding start end))
	#(#toString:start: #(encoding start))
	#(#toString: #(encoding))
	#toJSON
	#(#write:offset:length:encoding: #(string offset length encoding))
	#(#write:offset:length: #(string offset length))
	#(#write:offset: #(string offset))
	#(#write: #(string))
	#(#writeDoubleBE:offset:noAssert: #(value offset noAssert)) #(#writeDoubleBE:offset: #(value offset))
	#(#writeDoubleLE:offset:noAssert: #(value offset noAssert)) #(#writeDoubleLE:offset: #(value offset))
	#(#writeFloatBE:offset:noAssert: #(value offset noAssert)) #(#writeFloatBE:offset: #(value offset))
	#(#writeFloatLE:offset:noAssert: #(value offset noAssert)) #(#writeFloatLE:offset: #(value offset))
	#(#writeInt8:offset:noAssert: #(value offset noAssert)) #(#writeInt8:offset: #(value offset))
	#(#writeInt16BE:offset:noAssert: #(value offset noAssert)) #(#writeInt16BE:offset: #(value offset))
	#(#writeInt16LE:offset:noAssert: #(value offset noAssert)) #(#writeInt16LE:offset: #(value offset))
	#(#writeInt32BE:offset:noAssert: #(value offset noAssert)) #(#writeInt32BE:offset: #(value offset))
	#(#writeInt32LE:offset:noAssert: #(value offset noAssert)) #(#writeInt32LE:offset: #(value offset))
	#(#writeIntBE:offset:noAssert: #(value offset noAssert)) #(#writeIntBE:offset: #(value offset))
	#(#writeIntLE:offset:noAssert: #(value offset noAssert)) #(#writeIntLE:offset: #(value offset))
	#(#writeUInt8:offset:noAssert: #(value offset noAssert)) #(#writeUInt8:offset: #(value offset))
	#(#writeUInt16BE:offset:noAssert: #(value offset noAssert)) #(#writeUInt16BE:offset: #(value offset))
	#(#writeUInt16LE:offset:noAssert: #(value offset noAssert)) #(#writeUInt16LE:offset: #(value offset))
	#(#writeUInt32BE:offset:noAssert: #(value offset noAssert)) #(#writeUInt32BE:offset: #(value offset))
	#(#writeUInt32LE:offset:noAssert: #(value offset noAssert)) #(#writeUInt32LE:offset: #(value offset))
	#(#writeUIntBE:offset:noAssert: #(value offset noAssert)) #(#writeUIntBE:offset: #(value offset))
	#(#writeUIntLE:offset:noAssert: #(value offset noAssert)) #(#writeUIntLE:offset: #(value offset))
).!

! NodeBuffer methodsFor: #accessing !
at: index
	" Returns the octect at index. "

	^handle[index+1]! !

! NodeBuffer methodsFor: #accessing !
at: index put: value
	" Set the octect at index with value. "

	handle[index+1] := value.
	^value! !

! NodeBuffer methodsFor: #accessing !
size
	" Return the size of the receiver. "

	^self length! !

! NodeBuffer methodsFor: #converting !
asUint32Array
	" Return an instance of Uint32Array copied from the receiver. "

{'	return Uint32Array(self);'}! !

! NodeBuffer class methodsFor: #constants !
encodings
	" Return the collection of known encodings. "

	^#( ascii utf8 utf16le ucs2 base64 binary hex )! !

! NodeBuffer class methodsFor: #tools !
byteLength: aString encoding: encoding
	" Private - Return the length (in bytes of aString). "

	^(self global: #Buffer) #byteLength: aString encoding: encoding! !

! NodeBuffer class methodsFor: #tools !
byteLength: aString
	" Return the length (in bytes of aString). "

	^(self global: #Buffer) #byteLength: aString! !

! NodeBuffer class methodsFor: #compare !
compare: buf1 with: buf2
	" Useful for sorting an Array of Buffers. "

	^(self global: #Buffer) #compare: buf1 handle with: buf2 handle! !

! NodeBuffer class methodsFor: #compare !
compareBlock
	" Return the comparation block for instances of the receiver.
	Useful for sorting an Array of Buffers. e.g.
		(Array	with: (NodeBuffer string: '1234')
			with: (NodeBuffer string: '0123')
			) sort: NodeBuffer compareBlock
	"

	^(self global: #Buffer) basicAt: #compare! !

! NodeBuffer class methodsFor: #instantiation !
concat: arrayOfBuffers totalLength: totalLength
	" Returns a buffer which is the result of concatenating all the buffers in the list together. "

	^self @ ((self global: #Buffer)
		#concat: arrayOfBuffers handles
		 totalLength: totalLength)! !

! NodeBuffer class methodsFor: #instantiation !
concat: arrayOfBuffers
	" Returns a buffer which is the result of concatenating all the buffers in the arrayOfBuffers. "

	^self @ ((self global: #Buffer) #concat: arrayOfBuffers handles)! !

! NodeBuffer class methodsFor: #query !
isBuffer: jsObject
	" Private - Returns true if jsObject is a handle to Buffer instance. "

	^(self global: #Buffer) #isBuffer: jsObject! !

! NodeBuffer class methodsFor: #query !
isEncoding: encoding
	" Returns true if the encoding is a valid encoding argument, or false otherwise. "

	^(self global: #Buffer) #isEncoding: encoding! !

NodeChildProcess comment: '
	Node.js provides a tri-directional popen facility through the child_process module.
	It is possible to stream data through a childs stdin, stdout, and stderr in a fully non-blocking way.
'!
NodeChildProcess buildGetters: #(
	#stdin #stdout #stderr #pid
).!
NodeChildProcess buildFunctions: #(
	#disconnect
	#(#kill: #(signal)) #kill
	#(#send:sendHandle:with: #(message sendHandle callback))
	#(#send:sendHandle: #(message sendHandle))
	#(#send: #(message))
	#(#send:handle:with: #(message aHandle callback))
	#(#send:handle: #(message aHandle))
	#(#exec:options:with: #(message #(options json) callback) #NodeChildProcess)
	#(#exec:with: #(message callback) #NodeChildProcess)
	#(#execFile:args:options:with: #(fileName args #(options json) callback) #NodeChildProcess)
	#(#execFile:args:with: #(fileName args callback) #NodeChildProcess)
	#(#execFile:options:with: #(fileName #(options json) callback) #NodeChildProcess)
	#(#execFile:with: #(fileName callback) #NodeChildProcess)
	#(#execFile: #(fileName) #NodeChildProcess)
	#(#fork:args:options: #(modulePath args #(options json)) #NodeChildProcess)
	#(#fork:args: #(modulePath args) #NodeChildProcess)
	#(#fork: #(modulePath) #NodeChildProcess)
	#(#spawn:args:options: #(command args #(options json)) #NodeChildProcess)
	#(#spawn:args: #(command args) #NodeChildProcess)
	#(#spawn: #(command) #NodeChildProcess)
	#(#execFileSync:args:options: #(fileName args #(options json)) #NodeBuffer)
	#(#execFileSync:args: #(fileName args) #NodeBuffer)
	#(#execFileSync: #(fileName) #NodeBuffer)
	#(#execSync:options: #(command #(options json)) #NodeBuffer)
	#(#execSync: #(command) #NodeBuffer)
	#(#spawnSync:args:options: #(command args #(options json)))
	#(#spawnSync:args: #(command args))
	#(#spawnSync:options: #(command #(options json)))
	#(#spawnSync: #(command))
).!

NodeCluster comment: '
	A single instance of Node.js runs in a single thread.
	To take advantage of multi-core systems the user will sometimes want to launch a cluster of Node.js processes to handle the load.
	The cluster module allows you to easily create child processes that all share server ports.
'!
NodeCluster buildBooleanGetters: #(
	#isMaster #isWorker
).!
NodeCluster buildGetters: #(
	settings workers
).!
NodeCluster buildTypedGetters: #(
	#(#worker #NodeWorker)
).!
NodeCluster buildAccessors: #(
	schedulingPolicy
).!
NodeCluster buildFunctions: #(
	#(#disconnect: #(callback)) #disconnect
	#(#fork: #(#(env json))) #fork
	#(#setupMaster: #(#(settings json))) #setupMaster
).!
! NodeCluster methodsFor: #accessing !
activeWorkers
	" Returns a pool with the active worker objects, keyed by id field.
	Makes it easy to loop through all the workers.
	It is only available in the master process. "

	^PoolDictionary @ self workers! !

NodeWorker comment: '
	A Worker object contains all public information and method about a worker.
'!
NodeWorker buildGetters: #(
	id
).!
NodeWorker buildBooleanGetters: #(
	suicide
).!
NodeWorker buildFunctions: #(
	disconnect
).!
NodeWorker buildFunctions: #(
	isConnected isDead
	#(#kill: #(signal)) #kill
	#(#process #() #NodeChildProcess)
	#(#send:sendHandle:with: #(message sendHandle callback))
	#(#send:sendHandle: #(message sendHandle))
	#(#send: #(message))
	#(#send:handle:with: #(message aHandle callback))
	#(#send:handle: #(message aHandle))
).!

NodeConsole comment: '
	The console object is a special instance of Console whose output is sent to stdout or stderr.
'!
NodeConsole buildFunctions: #(
	#(#assert:message: #(value message))
	#(#assert: #(value))
	#(#dir:options: #(obj #(options json)))
	#(#dir: #(obj))
	#(#error:with: #(data anObject))
	#(#info:with: #(data anObject)) #(#info: #(data))
	#(#log:with: #(data anObject)) #(#log: #(data))
	#(#time: #(label))
	#(#timeEnd: #(label))
	#(#trace: #(message))
	#(#warn:with: #(data anObject)) #(#warn: #(data))
).!

NodeCertificate comment: '
	Used for working with signed public key & challenges.
'!
NodeCertificate buildFunctions: #(
	#(#exportChallenge: #(spkac))
	#(#exportPublicKey: #(spkac))
	#(#verifySpkac: #(spkac))
).!
NodeCipher comment: '
	Cipher objects are streams that are both readable and writable.
	The written plain text data is used to produce the encrypted data on the readable side.
'!
NodeCipher buildFunctions: #(
	#final #(#final: #(encoding))
	#(#getAuthTag #() #NodeBuffer)
	#(#setAAD: #(#(buffer handle)))
	#(#setAutoPadding: #(padding)) #setAutoPadding
	#(#update:inputEncoding:outputEncoding: #(data inputEncoding outputEncoding))
	#(#update:inputEncoding: #(data inputEncoding))
	#(#update: #(data))
).!
NodeDecipher comment: '
	Decipher objects are streams that are both readable and writable.
	The written enciphered data is used to produce the plain-text data on the the readable side.
'!
NodeDecipher buildFunctions: #(
	#final #(#final: #(encoding))
	#(#getAuthTag #() #NodeBuffer)
	#(#setAAD: #(#(buffer handle)))
	#(#setAutoPadding: #(padding)) #setAutoPadding
	#(#update:inputEncoding: #(data inputEncoding))
	#(#update: #(data))
).!
NodeDiffieHellman comment: 'Diffie-Hellman key exchanges.'!
NodeDiffieHellman buildGetters: #(
	#verifyError
).!
NodeDiffieHellman buildFunctions: #(
	#generateKeys: #generateKeys
	#computeSecret:
	#computeSecret:inputEncoding:
	#computeSecret:inputEncoding:outputEncoding:
	#getPrime #getPrime:
	#getGenerator #getGenerator:
	#getPublicKey #getPublicKey:
	#getPrivateKey #getPrivateKey:
	#setPublicKey: #setPublicKey:encoding:
	#SetPrivateKey: #setPrivateKey:encoding:
).!
NodeECDH comment: 'EC Diffie-Hellman key exchanges.'!
NodeECDH buildFunctions: #(
	#generateKeys: #generateKeys
	#computeSecret:
	#computeSecret:inputEncoding:
	#computeSecret:inputEncoding:outputEncoding:
	#getPrime #getPrime:
	#getGenerator #getGenerator:
	#getPublicKey #getPublicKey:
	#getPrivateKey #getPrivateKey:
	#SetPrivateKey: #setPrivateKey:encoding:
).!
NodeHash comment: 'Hash digests of data.'!
NodeHash buildFunctions: #(
	#update: #update:inputEncoding:
	#digest #digest:
).!
NodeHmac comment: 'Cryptographic hmac content.'!
NodeHmac buildFunctions: #(
	#update: #digest #digest:
).!
NodeSign comment: 'Generate signatures.'!
NodeSign buildFunctions: #(
	#update: #sign: #sign:outputFormat:
).!
NodeVerify comment: 'Verify signatures.'!
NodeVerify buildFunctions: #(
	#update: #verify:signature:signatureFormat:
	#verify:signature: #verify:signature:format:
).!
NodeCrypto buildFunctions: #(
	#(#createCipher:password: #NodeCipher )
	#(#createCipheriv:key:iv: #NodeCipheriv )
	#(#createDecipher:password: #NodeDecipher )
	#(#createDecipheriv:key:iv: #NodeDecipher )
	#(#createDiffieHellman: #NodeDecipher )
	#(#createDiffieHellman:encoding: #NodeDecipher )
	#(#createECDH: #NodeECDH )
	#(#createHash: #NodeHash )
	#(#createHmac:key: #NodeHmac )
	#(#createSign: #NodeSign )
	#(#createVerify: #NodeVerify )
	getCiphers getCurves
	#getDiffieHellman:
	getHashes
	#pbkdf2:salt:iterations:keylen:digest:with:
	#pbkdf2:salt:iterations:keylen:with:
	#pbkdf2Sync:salt:iterations:keylen:digest:
	#pbkdf2Sync:salt:iterations:keylen:
	#randomBytes:with: #randomBytes:
	#setEngine:flags: #setEngine:
).!
NodeCrypto buildFunctions: #(
	#(#privateDecrypt:buffer: #(#(privateKey json) #(buffer handle)))
	#(#privateEncrypt:buffer: #(#(privateKey json) #(buffer handle)))
	#(#publicDecrypt:buffer: #(#(privateKey json) #(buffer handle)))
	#(#publicEncrypt:buffer: #(#(privateKey json) #(buffer handle)))
).!

NodeDNS comment: '
	Contains functions that belong to two different categories:
	1) Functions that use the underlying operating system facilities to perform name resolution, and that do not necessarily do any network communication. e.g. #lookup
	2) Functions that connect to an actual DNS server to perform name resolution, and that always use the network to perform DNS queries.
'!
NodeDNS buildFunctions: #(
	getServers
	#(#lookup:options:with: #(hostname #(options json) callback))
	#(#lookup:with: #(hostname callback))
	#(#lookupService:port:with: #(address port callback))
	#(#resolve:rrtype:with: #(hostname rrtype callback))
	#(#resolve:with: #(hostname callback))
	#(#resolve4:with: #(hostname callback))
	#(#resolve6:with: #(hostname callback))
	#(#resolveCname:with: #(hostname callback))
	#(#resolveMx:with: #(hostname callback))
	#(#resolveNs:with: #(hostname callback))
	#(#resolveSoa:with: #(hostname callback))
	#(#resolveSrv:with: #(hostname callback))
	#(#resolveTxt:with: #(hostname callback))
	#(#reverse:with: #(ip callback))
	#(#setServers: #(servers))
).!
NodeEventEmitter comment: '
	All Node.js objects which emit events are instances of NodeEventEmitter.
	By default EventEmitters will print a warning if more than 10 listeners are added for a particular event.
	This is a useful default which helps finding memory leaks.
'.!
NodeEventEmitter buildFunctions: #(
	#addListener:with: #addListener:doing:
	#listenerCount: #listeners:
	#on:do: #once:do:
	#removeListener:listener:
	#removeAllListeners #removeAllListeners:
	#setMaxListeners: getMaxListeners
	#emit: #emit:with: #emit:with:with:
	#emit:with:with:with: #emit:with:with:with:with:
).!

NodeFSWatcher comment: '
	Trigger change event when something changes in a watched directory or file.
'!
NodeFSWatcher buildFunctions: #(
	#close
).!
NodeFileSystem  comment: '
	File I/O is provided by simple wrappers around standard POSIX functions.
	The relative path to a filename can be used. Remember that this path will be relative to NodeProcess current cwd.
'!
NodeFileSystem buildFunctions: #(
	#access:mode:with: #access:with:
	#accessSync:mode: #accessSync:
	#(#appendFile:data:options:with: #(file #(data json) #(options json) callback))
	#(#appendFile:data:with: #(file #(data json) callback))
	#(#appendFileSync:data:options: #(file #(data json) #(options json)))
	#(#appendFileSync:data: #(file #(data json)))
	#chmod:mode:with: #chmod:mode: #chmodSync:mode:
	#chown:uid:gid:with: #chown:uid:gid: #chownSync:uid:gid:
	#close: #close:with: #closeSync:
	#(#createReadStream: #NodeReadStream )
	#(#createReadStream:options: #(path #(options json)) #NodeReadStream )
	#(#createWriteStream: #NodeWriteStream )
	#(#createWriteStream:options: #(path #(options json)) #NodeWriteStream )
	#fchmod:mode:with: #fchmod:mode: #fchmodSync:mode:
	#fchown:uid:gid:with: #fchown:uid:gid: #fchownSync:uid:gid:
	#(#fstat:with: #NodeStats ) #(#fstatSync: #NodeStats )
	#fsync:with: #fsyncSync:
	#ftruncate:len:with: #ftruncateSync:len:
	#futimes:atime:mtime:with: #futimesSync:atime:mtime:
	#lchmod:mode:with: #lchmodSync:mode:
	#lchown:uid:gid:with: #lchownSync:uid:gid:
	#link:dstpath:with: #linkSync:dstpath:
	#(#lstat:with: #NodeStats ) #(#lstatSync: #NodeStats )
	#mkdir:with: #mkdir:mode:with: #mkdirSync: #mkdirSync:mode:
	#open:flags:mode:with: #open:flags:with: #openSync:flags: #openSync:flags:mode:
	#read:buffer:offset:length:position:with: #readSync:buffer:offset:length:position:
	#readdir:with: #readdirSync:
	#(#readFile:options:with: #(file #(options json) callback))
	#readFile:with: #readFileSync:
	#(#readFileSync:options: #(file #(options json)))
	#readlink:with: #readlinkSync:
	#(#realpath:cache:with: #(path #(cache json) callback))
	#(#readSync:buffer:offset:length:position: #(fd #(buffer json) offset length position))
	#(#realpathSync:cache: #(path #(cache json))) #realpathSync:
	#rename:to:with: #renameSync:to:
	#rmdir:with: #rmdirSync:
	#(#stat:with: #NodeStats ) #(#statSync: #NodeStats )
	#symlink:path:type:with: #symlink:path:with: #symlinkSync:path:type: #symlinkSync:path:
	#truncate:len:with: #truncateSync:len:
	#unlink:with: #unlinkSync:
	#unwatchFile:listener: #unwatchFile:
	#utimes:atime:mtime:with: #utimesSync:atime:mtime:
	#(#watch:options:listener: #(filename #(options json) listener) #NodeFSWatcher )
	#(#watch:listener: #(filename listener) #NodeFSWatcher )
	#(#watch: #(filename) #NodeFSWatcher )
	#(#watchFile:options:listener: #(filename #(options json) listener))
	#(#watchFile:listener: #(filename listener))
	#(#write:buffer:offset:length:position:with: #(fd #(buffer json) offset length position callback))
	#(#write:buffer:offset:length:with: #(fd #(buffer json) offset length callback))
	#(#write:data:position:encoding:with: #(fd #(data json) position encoding callback))
	#(#write:data:position:with: #(fd #(data json) position callback))
	#(#write:data:with: #(fd #(data json) callback))
	#(#writeFile:data:options:with: #(file #(data json) #(options json) callback))
	#(#writeFile:data:with: #(file #(data json) callback))
	#(#writeFileSync:data:options: #(file #(data json) #(options json)))
	#(#writeFileSync:data: #(file #(data json)))
	#(#writeSync:buffer:offset:length:position: #(fd #(buffer json) offset length position))
	#(#writeSync:buffer:offset:length: #(fd #(buffer json) offset length))
	#(#writeSync:data:position:encoding: #(fd #(data json) position encoding))
	#(#writeSync:data:position: #(fd #(data json) position))
	#(#writeSync:data: #(fd #(data json)))
).!

NodeHTTPAgent buildAccessors: #(
	maxSockets maxFreeSockets
	sockets requests
).!
NodeHTTPAgent buildGetters: #(
	#freeSockets
).!
NodeHTTPAgent buildFunctions: #(
	#destroy
	#(#getName: #(#(options json)))
)!
NodeHTTPClientRequest buildFunctions: #(
	#abort
	#end:enconding:with: #end:enconding: #end: #end
	#flushHeaders
	#setNoDelay: #setNoDelay
	#setSocketKeepAlive:initialDelay: #setSocketKeepAlive:
	#setTimeout:with: #setTimeout:
	#write:encoding:with: #write:encoding: #write:
).!
NodeHTTPServer buildAccessors: #(
	timeout maxHeadersCount
).!
NodeHTTPServer buildFunctions: #(
	#(#close: #(callback)) #close
	#(#listen: #(#(serverOrSocket handle)))
	#(#listen:with: #(#(serverOrSocket handle) callback))
	#(#listen:hostname:backlog:with: #(port hostname backlog callback))
	#(#listen:hostname:backlog: #(port hostname backlog))
	#(#listen:hostname: #(port hostname))
	#(#setTimeout:with: #(msecs callback))
	#(#setTimeout: #(msecs))
).!
NodeHTTPServerResponse buildAccessors: #(
	statusCode finished
	headersSent sendDate statusMessage
).
NodeHTTPServerResponse buildFunctions: #(
	#(#addTrailers: #(#(headers json)))
	#end #end: #end:encoding: #end:encoding:with:
	#getHeader: #removeHeader:
	#setHeader:value:
	#setTimeout:with:
	#write:encoding:with: #write:encoding: #write:
	#writeContinue
	#writeHead:reasonPhrase:headers: #writeHead:reasonPhrase: #writeHead:
).!
NodeIncomingMessage buildAccessors: #(
	httpVersion method headers rawHeaders
	statusCode statusMessage
	trailers rawTrailers url
).!
NodeIncomingMessage buildTypedAccessors: #(
	#(headers #PoolDictionary)
	#(socket #JS)
).!
NodeIncomingMessage buildFunctions: #(
	#setTimeout:with: #setTimeout:
).!

NodeHTTPClientResponse buildAccessors: #(
	#statusCode #headers #trailers
).!
NodeHTTPClientResponse buildFunctions: #(
	#setEncoding: #setEncoding
	#pause #resume
).!
NodeHTTPServerRequest buildGetters: #(
	#method #url #headers #trailers
	#httpVersion #connection
).
NodeHTTPServerRequest buildFunctions: #(
	#setEncoding #setEncoding:
	#pause #resume
).!

NodeHTTP buildFunctions: #(
	#(#createServer: #NodeHTTPServer ) #(#createServer #NodeHTTPServer )
	#(#request:with: #(#(options json) callback) #NodeHTTPClientRequest )
	#get:with: #get:
).!

NodeProcess buildGetters: #(
	#argv #execPath #env
	#version #installPrefix
	#pid #arch #platform
	config connected
	execArgv exitCode
	mainModule
).
NodeProcess buildTypedGetters: #(
	#(versions #Pooldictionary)
	#(release #Pooldictionary)
	#(stderr #NodeWriteStream)
	#(stdout #NodeWriteStream)
	#(stdin #NodeReadStream)
).
NodeProcess buildAccessors: #(
	#title
).
NodeProcess buildFunctions: #(
	abort
	#chdir: #cwd
	disconnect
	#exit #exit:
	#getgid #setgid:
	#getuid #setuid:
	hrtime
	#kill: #kill:signal:
	#(memoryUsage #() #PoolDictionary)
	#nextTick: #nextTick:with: #nextTick:with:with: #nextTick:with:with:with:
	#umask #umask:
	#uptime
).!
NodeUtil buildGetters: #(
	#argv #execPath #env
	#version #installPrefix
	#pid #arch #platform
).
NodeUtil buildAccessors: #(
	#title
).
NodeUtil buildFunctions: #(
	#debuglog: #log:
	#(#deprecate:string: #(aFunction string))
	#format:with: #format:with:with: #format:with:with:with: #format:with:with:with:with:
	#inherits:from:
	#(#inspect:options: #(object #(options json)))
).!
NodeStream buildGetters: #(
	#readable #writable
).
NodeStream buildFunctions: #(
	#setEncoding: #resume #destroy #destrySoon
).!
NodeReadStream buildFunctions: #(
	#pause resume
	#pipe: #(#pipe:options: #(destination #(options json)))
).!
NodeWriteStream buildGetters: #(
	bytesWritten
).!
NodeWriteStream buildFunctions: #(
	#write: #write:encoding: #write:encoding:fd:
	#end #end:encoding: #end:
).!
NodePath buildGetters: #(
	delimiter sep
)!
NodePath buildFunctions: #(
	#basename: #basename:ext:
	#normalize: #dirname: #extname:
	#(#format: #(#(parts json))) #parse:
	#isAbsolute: #normalize:
	#join:with: #join:with:with: #join:with:with:with: #join:with:with:with:with:
	#resolve:to: #resolve:with:to: #resolve:with:with:to: #resolve:with:with:with:to: #resolve:with:with:with:with:to:
	#relative:to:
	#exists: #exists:with: #existsSync:
).!
NodePath buildTypedGetters: #(
	#(win32 #NodePath) "Provide access to path methods in a win32 compatible way"
)!
NodeNet buildFunctions: #(
	#(#createServer #NodeNetServer)
	#(#createServer: #NodeNetServer)
	#(#createServer:listener: #NodeNetServer)
	#(#connect: #NodeSocket)
	#(#connect:with: #NodeSocket) #(#connect:with:with: #NodeSocket)
	#(#connect:with:with:with: #NodeSocket) #(#connect:with:with:with:with: #NodeSocket)
	#(#createConnection: #NodeSocket)
	#(#createConnection:with: #NodeSocket) #(#createConnection:with:with: #NodeSocket)
	#(#createConnection:with:with:with: #NodeSocket) #(#createConnection:with:with:with:with: #NodeSocket)
	#isIP: #isIPv4: #isIPv6:
).!
NodeNetServer buildAccessors: #( #maxConnections ).
NodeNetServer buildFunctions: #(
	#address #close #close:
	#getConnections:
	#listen: #listen:port: #listen:port:with:
	#(#listen:with: #(#(options json) callback))
	ref unref
).!
NodeNetSocket buildGetters: #(
	#bytesRead #bytesWritten
).
NodeNetSocket buildAccessors: #(
	#bufferSize #remoteAddress #remotePort
).
NodeNetSocket wrapFunctions: #(
	#connect: #connect:host: #connect:host:listener:
	#connect:listener:
	#setEncoding #setEncoding:
	#setSecure
	#write: #write:encoding: #write:encoding:with:
	#end #end: #end:encoding:
	#destroy #pause #resume
	#setTimeOut: #setTimeOut:with:
	#setNoDelay #setNoDelay:
	#setKeepAlive: #setKeepAlive:initialDelay:
).!
NodeDgram wrapFunctions: #(
	#send:offset:length:port:address: #send:offset:length:port:address:with:
	#bind: #bind:address:
	#close #address
	#setBroadcast:
	#setTTL: #setMulticastTTL: #setMulticastLoopback:
	#addMembership:multicastInterface: #addMembership:
	#dropMembership:multicastInterface: #dropMembership:
).!
NodeTLS wrapFunctions: #(
	#( #NodeTSLServer #createServer:secureConnectionListener: )
	#( #NodeTSLServer #createServer: )
	#( #NodeTSLCleartextStream #connect:host:options:secureConnectListener: )
	#( #NodeTSLCleartextStream #connect:host:options: )
	#( #NodeTSLCleartextStream #connect:host: )
	#( #NodeTSLCleartextStream #connect: )
	#( #NodeTLSSecurePair #createSecurePair:isServer:requestCert:rejectUnauthorized: )
	#( #NodeTLSSecurePair #createSecurePair:isServer:requestCert: )
	#( #NodeTLSSecurePair #createSecurePair:isServer: )
	#( #NodeTLSSecurePair #createSecurePair: )
	#( #NodeTLSSecurePair #createSecurePair )
).!
NodeTLSSecurePair buildGetters: #(
	#clearText #encrypted
).!
NodeTLSServer buildGetters: #(
	#maxConnections #connections
).
NodeTLSServer wrapFunctions: #(
	#listen:host:with: #listen:host: #listen:
	#close #address
	#addContext:credentials:
).
NodeTLSCleartextStream buildGetters: #(
	#authorized #authorizationError
	#remoteAddress #remotePort
).
NodeTLSCleartextStream wrapFunctions: #(
	#getPeerCertificate #address
).!
NodeHTTPS wrapFunctions: #(
	#( #NodeHTTPSServer #createServer: ) #( #NodeHTTPSServer #createServer:requestListener: )
	#( #NodeHTTPClientRequest #request:with: )
	#get:with:
).!
NodeURL wrapFunctions: #(
	#( #NodeURL #parse: )
	#( #NodeURL #parse:query: )
	#( #NodeURL #parse:query:slashesDenoteHost: )
	#format:
	#resolve:to:
).!
NodeQueryString buildAccessors: #(
	#escape #unescape
).
NodeQueryString wrapFunctions: #(
	#stringify:sep:eq: #stringify:sep: #stringify:
	#parse:sep:eq: #parse:sep: #parse:
).!
NodeReadline wrapFunctions: #(
	#( #NodeReadline #createInterface:output:completer: )
	#setPrompt:length:
	#prompt #close #pause #resume #write
	#question:with:
).!
NodeREPL wrapFunctions: #(
	#start #start:
	#start:stream:
	#start:stream:eval:
	#start:stream:eval:useGlobal:
	#start:stream:eval:useGlobal:ignoreUndefined:
).!
NodeVM wrapFunctions: #(
	#runInThisContext:filename: #runInThisContext:
	#runInNewContext:
	#runInNewContext:sandbox:
	#runInNewContext:sandbox:filename:
	#runInContext:context:filename:
	#runInContext:context:
	#createContext: #createContext
	#( #NodeScript #createScript:filename: )
	#( #NodeScript #createScript: )
).!
NodeScript wrapFunctions: #(
	#runInThisContext
	#runInNewContext:
	#runInNewContext
).!
NodeTTY wrapFunctions: #(
	#isatty: #setRawMode:
	#setWindowSize:row:color:
	#getWindowSize:
).!
NodeZlib wrapFunctions: #(
	#( #Gzip #createGzip: ) #( #Gzip #createGzip )
	#( #Gunzip #createGunzip: ) #( #Gunzip #createGunzip )
	#( #Deflate #createDeflate: ) #( #Deflate #createDeflate )
	#( #Inflate #createInflate: ) #( #Inflate #createInflate )
	#( #DeflateRaw #createDeflateRaw: ) #( #DeflateRaw #createDeflateRaw )
	#( #InflateRaw #createInflateRaw: ) #( #InflateRaw #createInflateRaw )
	#( #Unzip #createUnzip: ) #( #Unzip #createUnzip )
	#deflate:with:
	#deflateRaw:with:
	#gzip:with:
	#gunzip:with:
	#inflate:with:
	#inflateRaw:with:
	#unzip:with:
).!
NodeOS wrapFunctions: #(
	#hostname #type #platform #arch #release
	#uptime #loadavg #totalmem #freemem
	#cpus #networkInterfaces
).!

"---------- Library embedding ------------"!
! NodeJS class methodsFor: 'private' !
globalName
	" Private - Return the names of the required properties/features to execute the receiver. "

	^#global! !

! NodeJS class methodsFor: 'private' !
topGlobal
	" Private - Return the object to access the global during detection stage. "

	^nil! !

! NodeJS class methodsFor: 'source code' !
sourceCode
	" Private - Return the source code of the library.
	The library is granted by our execution engine, so we don't need installation sources.
	"

	^''.! !

"------------- Custom implementation -----------------------"!
! NodeJS class methodsFor: #accessing!
global
	" Return the global namespace object.
	In browsers, the top-level scope is the global scope. That means that in browsers if you're in the global scope var something will define a global variable.
	In Node this is different. The top-level scope is not the global scope; var something inside a Node module will be local to that module.
	"

	^Smalltalk nativeObjectAt: #global ifAbsent: [ self error: '#global missing.' ]! !

! NodeJS class methodsFor: #accessing!
process
	" Return the current (global) process object. "

	^NodeProcess current! !

! NodeProcess class methodsFor: #accessing!
current
	" Return the current (global) process object. "

	^self @ #{process}! !

! NodeJS class methodsFor: #accessing!
console
	" Return the current (global) instance. "

	^NodeConsole current! !

! NodeConsole class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self @ #{console}! !

! NodeJS class methodsFor: #accessing!
resolve: what
	" Use the internal (require) machinery to look up the location of a module, but rather than loading the module, just return the resolved filename. "

{'	return require.resolve(what); '}! !

! NodeJS class methodsFor: #accessing!
cache
	" Modules are cached in this object when they are required.
	By deleting a key value from this object, the next require will reload the module.
	"

	^#{require}#cache! !

! NodeJS class methodsFor: #accessing!
module
	" Return a reference to the current module.
	In particular module.exports is the same as the exports object.
	"

	^#{module}! !

! NodeJS class methodsFor: #accessing!
exports
	" Return an object which is shared between all instances of the current module and made accessible through #require:.
	Exports is the same as the module.exports object.
	"

	^#{exports}! !

! NodeProcess methodsFor: #accessing!
stdout
	^NodeWriteStream @ handle#stdout! !

! NodeProcess methodsFor: #accessing!
stderr
	^NodeWriteStream @ handle#stderr! !

! NodeProcess methodsFor: #accessing!
stdin
	^NodeReadStream @ handle#stdin! !

! NodeCrypto class methodsFor: #accessing!
crypto
	" Return the current (global) instance. "

	^NodeFileSystem current! !

! NodeCrypto class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #crypto! !

! NodeJS class methodsFor: #accessing!
fs
	" Return the current (global) instance. "

	^NodeFileSystem current! !

! NodeFileSystem class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #fs! !

! NodeJS class methodsFor: #accessing!
path
	" Return the current (global) instance. "

	^NodePath current! !

! NodePath class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #path! !

! NodeJS class methodsFor: #accessing!
net
	" Return the current (global) instance. "

	^NodeNet current! !

! NodeNet class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #net! !

! NodeDgram class methodsFor: 'instance creation' !
socket: type with: callback
	" Return an instance of the receiver. "

	| support |
	support := self requireModule: #dgram.
	^self @ (support #createSocket: type with: callback)! !

! NodeDgram class methodsFor: 'instance creation' !
socket: type
	" Return an instance of the receiver. "

	| support |
	support := self requireModule: #dgram.
	^self @ (support #createSocket: type)! !

! NodeJS class methodsFor: #accessing!
dns
	" Return the current (global) instance. "

	^NodeDNS current! !

! NodeDNS class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #dns! !

! NodeJS class methodsFor: #accessing!
http
	" Return the current (global) instance. "

	^NodeHTTP current! !

! NodeHTTP class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #http! !

! NodeHTTP methodsFor: #accessing!
globalAgent

	^NodeHTTPAgent @ handle#globalAgent! !

! NodeJS class methodsFor: #accessing!
https
	" Return the current (global) instance. "

	^NodeHTTPS current! !

! NodeHTTPS class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #https! !

! NodeHTTP methodsFor: #accessing!
globalAgent

	^NodeHTTPAgent @ handle#globalAgent! !

! NodeJS class methodsFor: #accessing!
tls
	" Return the current (global) instance. "

	^NodeTLS current! !

! NodeTLS class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #tls! !

! NodeHTTPS methodsFor: #accessing!
globalAgent

	^NodeHTTPSAgent @ handle#globalAgent! !

! NodeJS class methodsFor: #accessing!
url
	" Return the current (global) instance. "

	^NodeURL current! !

! NodeURL class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #url! !

! NodeJS class methodsFor: #accessing!
rl
	" Return the current (global) instance. "

	^NodeReadline current! !

! NodeJS class methodsFor: #accessing!
readline
	" Return the current (global) instance. "

	^NodeReadline current! !

! NodeReadline class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #readline! !

! NodeJS class methodsFor: #accessing!
repl
	" Return the current (global) instance. "

	^NodeREPL current! !

! NodeREPL class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #repl! !

! NodeJS class methodsFor: #accessing!
vm
	" Return the current (global) instance. "

	^NodeVM current! !

! NodeVM class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #vm! !

! NodeJS class methodsFor: #accessing!
child
	" Return the current (global) instance. "

	^NodeChildProcess current! !

! NodeChildProcess class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #child_process! !

! NodeJS class methodsFor: #accessing!
assert
	" Return the current (global) instance. "

	^NodeAssert current! !

! NodeAssert class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #assert! !

! NodeJS class methodsFor: #accessing!
tty
	" Return the current (global) instance. "

	^NodeTTY current! !

! NodeTTY class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #tty! !

! NodeJS class methodsFor: #accessing!
zlib
	" Return the current (global) instance. "

	^NodeZlib current! !

! NodeZlib class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #zlib! !

! NodeJS class methodsFor: #accessing!
os
	" Return the current (global) instance. "

	^NodeOS current! !

! NodeOS class methodsFor: #accessing!
current
	" Return the current (global) instance. "

	^self requireModule: #os! !