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

api[libm] index

SwikiCodeRobot @> #apiLibmIndex

Prerequisites

"Check FFI is actually included in the image"
(Smalltalk includesKey: #S8FFI) ifFalse: [
    self print: '// Require S8FFI framework'.
    self abort
]

API implementation

FFILibrary subclass: #LibM category: #LibM!
LibM comment: '
	Wrapper to LIBM
	See https://sourceware.org/newlib/libm.html
'!

! LibM class methodsFor: #spec !
libraryName
	" Private - Returns the name of library file. "

	^NodeJS process platform = #win32
		ifTrue: [ #msvcrt ]
		ifFalse:[ #libm   ]! !

! LibM class methodsFor: #spec !
literalForFunctions: functions withArguments: args
	" Private - Returns the specification literal for functions. "

	^self literalForFunctions: functions withArguments: args return: nil! !

! LibM class methodsFor: #spec !
alternatives
	" Private - Returns the numeric alternatives. "

	^#( #('' double) #(f float) )! !

! LibM class methodsFor: #spec !
literalForFunctions: functions withArguments: args return: returnType
	" Private - Returns the specification literal for functions. "

	| result |
	result := Array new.
	self alternatives do: [:pair| | type |
		type := pair last.
		functions do: [:ffiName|
			result add: (Array with: ffiName ,pair first
				with: (Array
					with: (returnType isNil ifTrue: [type] ifFalse: [returnType])
					with: (args collect: [:arg|
						arg isString
						ifTrue: [ Array with: arg with: type ]
						ifFalse: [ arg ]
						])
				))
		]
	].
	^result ! !


! LibM class methodsFor: #spec !
specLiteral
	" Private - Returns the specification literal of library file. "

	^self mathLiteral
		,self complexLiteral! !

! LibM class methodsFor: #spec !
complexLiteral
	" Private - Returns the specification literal for Mathematical complex functions"

	^#(	"not implemented yet"
	)! !

! LibM class methodsFor: #spec !
mathLiteral
	" Private - Returns the specification literal for Mathematical functions"

	^(self literalForFunctions: #(
		acos acosh asin asinh
		atan atanh "j0 j1 y0 y1"
		cbrt copysign
		cosh erf erfc exp2 expm1
		fabs floor ceil
		"gamma" lgamma tgamma
		ilogb log log10 "log1" log2 logb
		nearbyint nextafter
		rint scalbn
		sin cos sinh sqrt
		tan tanh trunc
		) withArguments: #(x))
	,(self literalForFunctions: #(
		lrint lround 
		) withArguments: #(x) return: #int)
	,(self literalForFunctions: #(
		llrint llround
		) withArguments: #(x) return: #longlong)
	,(self literalForFunctions: #(
		atan2 fdim
		fmax fmin fmod
		hypot pow remainder
		) withArguments: #(x y))
	,(self literalForFunctions: #(
		fma
		) withArguments: #(x y z))
	,(self literalForFunctions: #( scalbn ) withArguments: #(x #(i int)))
	",(self literalForFunctions: #( jn yn ) withArguments: #(#(n int) y))"
	,(self literalForFunctions: #( frexp ) withArguments: #(x #(exp 'int*')))
	",(self literalForFunctions: #( infinity ) withArguments: #())"
	,(self literalForFunctions: #( ldexp ) withArguments: #(x #(exp int)))
	,(self literalForFunctions: #( nan ) withArguments: #(#(ignored 'char*')))
	,(self literalForFunctions: #( remquo ) withArguments: #(#(quo 'int*')))
	",#( #(matherr #(int #('void*' -struct exception *-))))" ! !

LibM buildFromLiteral!

References