Module:Complex Number/Functions

From wiki
Revision as of 13:39, 3 December 2022 by 1>A2569875 (修正筆誤)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

local p = {} local math_lib local to_number function p._init(_math_lib, _to_number) local warp_funcs={"factorial","gamma","sec","csc","sech","csch","asec","acsc","asech","acsch","gd","cogd","arcgd", "LambertW","norm", "gcd","lcm","range","binomial",'minimum','maximum','average','min','max','avg','geoaverage','var','σ', 'selectlist','for','while','summation','product','if','iff','ifelse','ifelsef','diff','integral', '∫', 'limit', 'hide','exprs','lastexpr','equalexpr',--調整條目中定義不顯示的函數 'randomseed','time','nil','null','call', 'frameArg','object','string','symbols','passObject','typeof','length','array','assignMember', 'divisorsigma','findnext','findlast','divisor','primedivisor','eulerphi' } for i=1,#warp_funcs do if _math_lib[ warp_funcs[i] ] == nil then _math_lib[ warp_funcs[i] ] = p['_' .. warp_funcs[i] ] end end math_lib = _math_lib to_number = _to_number return _math_lib end function p._complex_number() return p._init(require("Module:Complex Number").cmath.init(), require("Module:Complex Number").cmath.init().toComplexNumber) end

local noop_func = function()end local function assertArg(val, index, func) assert (val ~= nil, string.format( "bad argument #%d to '%s' (number expected, got %s)", index, func, type(val))) end function p._binomial(cal_n,cal_k) local r_n=tonumber(tostring(cal_n)) local r_k=tonumber(tostring(cal_k)) if r_n and r_k then if r_n>0 and r_k>=0 then local f_n, f_k; _,f_n = math.modf(r_n);_,f_k = math.modf(r_k) if math.abs(f_n) < 1e-12 and math.abs(f_k) < 1e-12 then local result = 1 if r_n == 0 then return result end while r_k>0 do result = result * r_n / r_k r_n = r_n - 1 r_k = r_k - 1 end return result end end end local n=to_number(cal_n) local k=to_number(cal_k) assertArg(n, 1, 'binomial') assertArg(k, 2, 'binomial') return p._factorial(n) * math_lib.inverse( p._factorial(k) ) * math_lib.inverse( p._factorial(n-k) ) end

function p._factorial(cal_z)return p._gamma(to_number(cal_z) + 1)end function p._sec(cal_z)return math_lib.inverse( math_lib.cos( to_number(cal_z) ) )end function p._csc(cal_z)return math_lib.inverse( math_lib.sin( to_number(cal_z) ) )end function p._sech(cal_z)return math_lib.inverse( math_lib.cosh( to_number(cal_z) ) )end function p._csch(cal_z)return math_lib.inverse( math_lib.sinh( to_number(cal_z) ) )end function p._asec(cal_z)return math_lib.acos( math_lib.inverse( to_number(cal_z) ) )end function p._acsc(cal_z)return math_lib.asin( math_lib.inverse( to_number(cal_z) ) )end function p._asech(cal_z)return math_lib.acosh( math_lib.inverse( to_number(cal_z) ) )end function p._acsch(cal_z)return math_lib.asinh( math_lib.inverse( to_number(cal_z) ) )end function p._gd(cal_z)return math_lib.atan( math_lib.tanh( to_number(cal_z) * 0.5 ) ) * 2 end function p._arcgd(cal_z)return math_lib.atanh( math_lib.tan( to_number(cal_z) * 0.5 ) ) * 2 end function p._cogd(cal_z)local x = to_number(cal_z); return - math_lib.sgn( x ) * math_lib.log( math_lib.abs( math_lib.tanh( x * 0.5 ) ) ) end

function p._range(val,vmin,vmax) assertArg(val, 1, 'range') local min_inf, max_inf = tonumber("-inf"), tonumber("inf") local function get_vector(_val) local val = to_number(_val) if val == nil then return {} end return math_lib.tovector(val) end local v_val, v_min, v_max = math_lib.tovector(to_number(val)), get_vector(vmin), get_vector(vmax) for i=1,#v_val do local min_v, max_v = math.min(v_min[i]or min_inf, v_max[i]or max_inf), math.max(v_min[i]or min_inf, v_max[i]or max_inf) if v_val[i] < min_v or v_val[i] > max_v then return to_number(math_lib.nan) end end return to_number(val) end function p._calc_diff(_value, _left, _right, _expr) local value = to_number(_value) local left = to_number(_left) local right = to_number(_right) local left_val = _expr(value + left) local right_val = _expr(value + right) return (left_val - right_val) / (left - right) end function p._diff_abramowitz_stegun(_x, _h, _f) local x = to_number(_x) local h = to_number(_h)

   local _1 = to_number(1) local _2 = to_number(2) local _8 = to_number(8) local _12 = to_number(12)
   --if tonumber(math_lib.abs(math_lib.nonRealPart(x))) > 1e-8 then
   --	--數值微分#複變的方法 --(Martins, Sturdza et.al.)
   --	local _i = math_lib.i or _1
   --	return (math_lib.im(_f(x + _i * h))) / h
   --else
   	--數值微分#高階方法 --(Abramowitz & Stegun, Table 25.2)

return (- _f(x + _2*h) + _8*_f(x + h) - _8*_f(x - h) + _f(x - _2*h)) / (_12 * h) --end end

function p._calc_from(_value, _left, _right, _expr) local value = to_number(_value) local left = to_number(_left) local left_val = _expr(value + left) return left_val - p._calc_diff(_value, _left, _right, _expr) * left end function p._get_sample_number(_value) local num = math_lib.re(math_lib.abs(to_number(_value))) return (tonumber(num)~=nil) and ((num < 1e-8) and 1 or num) or 1 end function p._diff(_expr, _value) local func_type = type(noop_func) local value_str = tostring(_value) if value_str == 'nan' or value_str == '-nan' or value_str == 'nil'then error("計算失敗:無效的數值 ") return _expr end if value_str == 'inf' or value_str == '-inf'then error("計算失敗:不支援無窮微分 ") return _expr end local small_scale_pow = math_lib.floor(math_lib.log(p._get_sample_number(_value)) / math_lib.log(to_number(10)))-5 local small_scale = math_lib.pow(10,small_scale_pow) if type(_expr) == func_type then return p._diff_abramowitz_stegun(_value, small_scale, _expr) else return 0 end end

function p._integral(_a,_b,func,step) local a = to_number(_a) local b = to_number(_b) local begin_str = tostring(_a) local stop_str = tostring(_b) if begin_str == 'nan' or begin_str == '-nan' or begin_str == 'nil' or stop_str == 'nan' or stop_str == '-nan' or stop_str == 'nil'then error("計算失敗:無效的迴圈 ") return func end if begin_str == 'inf' or begin_str == '-inf' or stop_str == 'inf' or stop_str == '-inf'then error("計算失敗:不支援無窮求積 ") return func end local n = tonumber(step) or 2000 local f = (type(func)==type(noop_func))and func or (function()return to_number(func) or 0 end) local h = (b-a)/n local x0, xn = a, b local _2, _7, _12, _14, _32, _45 = to_number(2), to_number(7), to_number(12), to_number(14), to_number(32), to_number(45) local i0, i1, i2 = 1, 2, 4 local sumfxi0, sumfxi1, sumfxi2 = to_number(0), to_number(0), to_number(0) for i=1,n do -- Boole's rule if i0 > n-1 and i1 > n-2 and i2 > n-4 then break end local xi0, xi1, xi2 = a + i0 * h, a + i1 * h, a + i2 * h if i0 <= n-1 then sumfxi0 = sumfxi0 + f(xi0) end if i1 <= n-2 then sumfxi1 = sumfxi1 + f(xi1) end if i1 <= n-4 then sumfxi2 = sumfxi2 + f(xi2) end i0 = i0 + 2 i1 = i1 + 4 i2 = i2 + 4 end return (_2 * h / _45) * (_7 * (f(x0) + f(xn)) + _32 * sumfxi0 + _12 * sumfxi1 + _14 * sumfxi2) end p['_∫'] = p._integral

function p._limit(_value, _way, _expr) local way = to_number(_way) local func_type = type(noop_func) local value_str = tostring(_value) if value_str == 'nan' or value_str == '-nan' or value_str == 'nil' then error("計算失敗:無效的數值 ") return _expr end if value_str == 'inf' or value_str == '-inf'then error("計算失敗:不支援無窮極限 ") return _expr end local small_scale_pow = tonumber(math_lib.re(math_lib.floor(math_lib.log(p._get_sample_number(_value)) / math_lib.log(to_number(10))))-6) local small_scale = math.pow(10,small_scale_pow) local small_scale_a = small_scale / 10 local small_scale_c = small_scale * 10

if type(_expr) == func_type then if math_lib.re(math_lib.abs(way)) < 1e-10 then local left = p._calc_from(_value, -small_scale, -small_scale_a, _expr) local right = p._calc_from(_value, small_scale_a, small_scale, _expr) if math_lib.re(math_lib.abs(left - right)) < small_scale_c then return (left + right) / 2 else return math_lib.nan end else return (math_lib.re(way) > 0) and p._calc_from(_value, small_scale_a, small_scale, _expr) or p._calc_from(_value, -small_scale, -small_scale_a, _expr) end else return _expr end end p._nil = "nil" p._null = "nil"


流程控制擴充 ----------------------

function p._if(_expr, _true_expr, _false_expr) return p._ifelse_func(false, _expr, _true_expr, _false_expr) end function p._iff(_expr, _true_expr, _false_expr) return p._ifelse_func(true, _expr, _true_expr, _false_expr) end function p._ifelse(...) return p._ifelse_func(false, ...) end function p._ifelsef(...) return p._ifelse_func(true, ...) end function p._ifelse_func(is_func, ...) local func = noop_func local exprlist = {...} local last_else = #exprlist % 2 == 1 local max_num = (last_else and (#exprlist - 1) or #exprlist) / 2 for i=1,max_num do local _expr = exprlist[i * 2 - 1] local expr = (type(_expr) == type(func)) and _expr() or _expr local expr_true = exprlist[i * 2] local _chk_flag = math_lib.abs(to_number(expr)) > 1e-14; if _chk_flag then return (type(expr_true) == type(func) and is_func) and expr_true() or expr_true end end if last_else then local expr_false = exprlist[#exprlist] return (type(expr_false) == type(func) and is_func) and expr_false() or expr_false end local _expr = exprlist[1] return (type(_expr) == type(func)) and _expr() or _expr end local function check_while(_ifexpr) local result = (type(_ifexpr) == type(noop_func)) and _ifexpr() or _ifexpr if result == true then return true end if not result then return false end return math_lib.abs(to_number(result)) > 1e-14 end function p._while(_ifexpr, _expr) local result while check_while(_ifexpr) do result = (type(_expr) == type(noop_func)) and _expr() or _expr if type(result) == type({}) and result['return'] then break end end return result end function p._for(_start,_end,_step,_expr) local _begin = to_number(_start); local _stop = to_number(_end); local _do_step = to_number(_step); local check_loop = (_stop - _begin) / _do_step local begin_str = tostring(_begin) local stop_str = tostring(_stop) if math_lib.re(math_lib.abs(_do_step))<=1e-14 or math_lib.re(check_loop) < 0 or begin_str == 'nan' or begin_str == '-nan' or begin_str == 'nil' or begin_str == 'inf' or begin_str == '-inf' or stop_str == 'nan' or stop_str == '-nan' or stop_str == 'nil' or stop_str == 'inf' or stop_str == '-inf'then error("計算失敗:無效的迴圈 ") return _expr end if type(_expr) == type(noop_func) then local it = _begin local init = to_number(0) while math_lib.re(it) <= math_lib.re(_stop) do init = _expr(to_number(it),to_number(init)) if type(init) == type({}) and init['return'] then break end it = it + _do_step end return init else return _expr end end function p._summation(_start,_end,_expr) local _begin = to_number(_start); local _stop = to_number(_end); local _do_step = to_number(1); local check_loop = (_stop - _begin) / _do_step local begin_str = tostring(_begin) local stop_str = tostring(_stop) if math_lib.re(math_lib.abs(_do_step))<=1e-14 or math_lib.re(check_loop) < 0 or begin_str == 'nan' or begin_str == '-nan' or begin_str == 'nil' or stop_str == 'nan' or stop_str == '-nan' or stop_str == 'nil'then error("計算失敗:無效的迴圈 ") return _expr end if begin_str == 'inf' or begin_str == '-inf' or stop_str == 'inf' or stop_str == '-inf'then error("計算失敗:不支援無窮求和 ") return _expr end local func_type = type(noop_func) local it = _begin local init = to_number(0)--空和 while math_lib.re(it) <= math_lib.re(_stop) do init = init + ((type(_expr) == func_type) and _expr(to_number(it)) or to_number(_expr))--累加 it = it + _do_step end return init end

function p._product(_start,_end,_expr) local _begin = to_number(_start); local _stop = to_number(_end); local _do_step = to_number(1); local check_loop = (_stop - _begin) / _do_step local begin_str = tostring(_begin) local stop_str = tostring(_stop) if math_lib.re(math_lib.abs(_do_step))<=1e-14 or math_lib.re(check_loop) < 0 or begin_str == 'nan' or begin_str == '-nan' or begin_str == 'nil' or stop_str == 'nan' or stop_str == '-nan' or stop_str == 'nil'then error("計算失敗:無效的迴圈 ") return _expr end if begin_str == 'inf' or begin_str == '-inf' or stop_str == 'inf' or stop_str == '-inf'then error("計算失敗:不支援無窮求積 ") return _expr end local func_type = type(noop_func) local it = _begin local init = to_number(1)--空積 while math_lib.re(it) <= math_lib.re(_stop) do init = init * ((type(_expr) == func_type) and _expr(to_number(it)) or to_number(_expr))--累乘 it = it + _do_step end return init end


工具函數擴充 ----------------------

function p._randomseed(_seed) local seed = tonumber(tostring(_seed)) or (os.time() * os.clock()) math.randomseed(math.floor(seed)) return to_number(seed) end function p._time() return to_number(os.time()) end function p._call(func, ...) if type(func) == type(noop_func) then return func(...)end return func end

function p._hide(...) local input_args = {...} return to_number(input_args[#input_args]) end p._exprs = p._hide p._lastexpr = p._hide p._equalexpr = p._hide


統計函數 ----------------------

function p._selectlist(x,...) local input_args = {...} local y = input_args[1] local z = input_args[2] local id_x = tonumber(tostring(x)) or 0 if type(y) == type("string") then return mw.ustring.sub(y,id_x,id_x) end if type(y)==type({}) and #y >= id_x and id_x>0 then if id_x <= 0 then id_x = id_x + #y + 1 end return y[id_x] or tonumber('nan') elseif type(z)==type({}) and #z >= id_x then local id_y = tonumber(tostring(y)) or 0 if id_x <= 0 then id_x = id_x + #z + 1 end if type(z[id_x])==type({}) and #(z[id_x]) >= id_y and id_y>0 then if id_y <= 0 then id_y = id_y + #(z[id_x]) + 1 end return (z[id_x][id_y]) or tonumber('nan') end end id_x = tonumber(tostring(x)) or 0 if id_x <= 0 then id_x = id_x + #input_args + 1 end return input_args[id_x] or tonumber('nan') end function p._minimum(...) return p.minmax('min', ...) end function p._maximum(...) return p.minmax('max', ...) end function p._average(...) return p.minmax('avg', ...) end function p._geoaverage(...) return p.minmax('gavg', ...) end function p._var(...) return p.minmax('var', ...) end p._min = p._minimum p._max = p._maximum p._avg = p._average p['_σ'] = function(...) return p.minmax('σ',...) end local function flatten(inarray,outarray) outarray = outarray or {} if type(inarray) ~= type({}) then outarray[#outarray + 1] = inarray elseif inarray.numberType then outarray[#outarray + 1] = inarray elseif type(inarray.args) == type({}) then local midarray = inarray.args for k,v in pairs(midarray) do local i = tonumber(k) if i then outarray = flatten(midarray[i],outarray)end end if type(inarray.getParent) == type(noop_func) then midarray = (inarray:getParent() or {}).args or {} for k,v in pairs(midarray) do local i = tonumber(k) if i then outarray = flatten(midarray[i],outarray)end end end elseif #inarray > 0 then for i=1,#inarray do outarray = flatten(inarray[i],outarray)end end return outarray end function p.minmax(calc_mode,...) local mode = calc_mode local tonumber_lib = to_number or tonumber local lib_math = math_lib or math local args, tester = flatten({ ... }), {tonumber("nan")} if type(calc_mode) == type({}) then mode = (calc_mode.args or calc_mode).mode or mode; args = flatten({args, calc_mode}) end local sum, prod, count, sumsq, sig = tonumber_lib(0), tonumber_lib(1), 0, tonumber_lib(0), (mode =='var'or mode=='σ') local mode_map = {} local non_nan for i=1,#args do local got_number, calc_number = tonumber(tostring(args[i])) or tonumber("nan"), tonumber_lib(args[i]) if calc_number then sum, prod, count = calc_number + sum, calc_number * prod, count + 1 end if sig == true then local x_2 = calc_number * calc_number if lib_math.dot then x_2 = lib_math.dot(calc_number, lib_math.conjugate(calc_number)) end sumsq = sumsq + x_2 end mode_map[args[i]] = (mode_map[args[i]]or 0) + 1 if tostring(got_number):lower()~="nan" and type(non_nan) == type(nil) then tester[1], non_nan = got_number, got_number else tester[#tester + 1] = got_number end end local modes={min=math.min,max=math.max,sum=function()return sum end,prod=function()return prod end,count=function()return count end, avg=function()return sum*tonumber_lib(1/count) end, gavg=function()return lib_math.pow(prod,tonumber_lib(1/count)) end, var=function()return sumsq*tonumber_lib(1/count)-sum*sum*tonumber_lib(1/(count*count)) end, ['σ']=function()return lib_math.sqrt(sumsq*tonumber_lib(1/count)-sum*sum*tonumber_lib(1/(count*count))) end, mode=function() local max_count, mode_data = 0, for mkey, mval in pairs(mode_map) do if mval > max_count then max_count = mval mode_data = mkey end end return mode_data end, gcd=function(...)if not to_number or not math_lib then p._complex_number()end return p._gcd(...)end, lcm=function(...)if not to_number or not math_lib then p._complex_number()end return p._lcm(...)end, } if tostring(tester[1]):lower()=="nan" and mode:sub(1,1)=='m' then local error_msg = for i=1,#args do if error_msg~=then error_msg = error_msg .. '、 ' end error_msg = error_msg .. tostring(args[i]) end error("給定的數字 " .. error_msg .." 無法比較大小") end if type(modes[mode]) ~= type(tonumber) then error("未知的統計方式 '" .. mode .."' ") end return modes[mode](unpack(tester)) end

local function fold(func, ...) -- Use a function on all supplied arguments, and return the result. The function must accept two numbers as parameters, -- and must return a number as an output. This number is then supplied as input to the next function call. local vals = {...} local count = #vals -- The number of valid arguments if count == 0 then return -- Exit if we have no valid args, otherwise removing the first arg would cause an error. nil, 0 end local ret = table.remove(vals, 1) for _, val in ipairs(vals) do ret = func(ret, val) end return ret, count end

--[[ Fold arguments by selectively choosing values (func should return when to choose the current "dominant" value). ]] local function binary_fold(func, ...) local value = fold((function(a, b) if func(a, b) then return a else return b end end), ...) return value end


伽瑪函數 ----------------------

local Reciprocal_gamma_coeff = {1,0.577215664901532860607,-0.655878071520253881077,-0.0420026350340952355290,0.166538611382291489502,-0.0421977345555443367482,-0.00962197152787697356211,0.00721894324666309954240,-0.00116516759185906511211,-0.000215241674114950972816,0.000128050282388116186153,-0.0000201348547807882386557,-1.25049348214267065735e-6,1.13302723198169588237e-6,-2.05633841697760710345e-7,6.11609510448141581786e-9,5.00200764446922293006e-9,-1.18127457048702014459e-9,1.04342671169110051049e-10,7.78226343990507125405e-12,-3.69680561864220570819e-12,5.10037028745447597902e-13,-2.05832605356650678322e-14,-5.34812253942301798237e-15,1.22677862823826079016e-15,-1.18125930169745876951e-16,1.18669225475160033258e-18,1.41238065531803178156e-18,-2.29874568443537020659e-19,1.71440632192733743338e-20} --https://oeis.org/A001163https://oeis.org/A001164 local stirling_series_coeff = {1,0.0833333333333333333333333,0.00347222222222222222222222,-0.00268132716049382716049383,-0.000229472093621399176954733,0.000784039221720066627474035,0.0000697281375836585777429399,-0.000592166437353693882864836,-0.0000517179090826059219337058,0.000839498720672087279993358,0.0000720489541602001055908572,-0.00191443849856547752650090,-0.000162516262783915816898635,0.00640336283380806979482364,0.000540164767892604515180468,-0.0295278809456991205054407,-0.00248174360026499773091566,0.179540117061234856107699,0.0150561130400264244123842,-1.39180109326533748139915,-0.116546276599463200850734} function p._gamma_high_imag(cal_z) local z = to_number(cal_z) if z ~= nil and math_lib.abs(math_lib.nonRealPart(z)) > 2 then local inv_z = math_lib.inverse(z) return math_lib.sqrt((math_lib.pi * 2) * inv_z) * math_lib.pow(z * math_lib.exp(-1) * math_lib.sqrt( (z * math_lib.sinh(inv_z) ) + math_lib.inverse(to_number(810) * z * z * z * z * z * z) ),z) end return nil end function p._gamma_morethen_lua_int(cal_z) local z = to_number(cal_z) - to_number(1) local lua_int_term = 18.1169 --FindRoot[ Factorial[ x ] == 2 ^ 53, {x, 20} ] if math_lib.abs(z) > (lua_int_term - 1) or (math_lib.re(z) < 0 and math_lib.abs(math_lib.nonRealPart(z)) > 1 ) then local sum = 1 for i = 1, #stirling_series_coeff - 1 do local a, n = to_number(z), tonumber(i) local y, k, f = to_number(1), n, to_number(a) while k ~= 0 do if k % 2 == 1 then y = y * f end k = math.floor(k / 2); f = f * f end sum = sum + stirling_series_coeff[i + 1] * math_lib.inverse(y) end return math_lib.sqrt( (2 * math.pi) * z ) * math_lib.pow( z * math.exp(-1), z ) * sum end return nil end function p._gamma_abs_less1(cal_z) local z = to_number(cal_z) if (math.abs(math_lib.re(z)) <=1.001) then if math_lib.abs(math_lib.nonRealPart(z)) < 1e-14 and ( (math.abs(math_lib.re(z) - 1) < 1e-14) or (math.abs(math_lib.re(z) - 2) < 1e-14) ) then return to_number(1)end return math_lib.inverse(p._recigamma_abs_less1(z)) end return nil end function p._recigamma_abs_less1(z) local result = to_number(0) for i=1,#Reciprocal_gamma_coeff do result = result + Reciprocal_gamma_coeff[i] * math_lib.pow(z,i) end return result end function p._gamma(cal_z) local z = to_number(cal_z) if math_lib.abs(math_lib.nonRealPart(z)) < 1e-14 and ((math_lib.re(z) < 0 or math.abs(math_lib.re(z)) < 1e-14) and math.abs(math.floor(math_lib.re(z)) - math_lib.re(z)) < 1e-14 ) then return tonumber("nan") end local pre_result = p._gamma_morethen_lua_int(z) or p._gamma_high_imag(z) or p._gamma_abs_less1(z) if pre_result then return pre_result end local real_check = math_lib.re(z) local loop_count = math.floor(real_check) local start_number, zero_flag = z - loop_count, false if math_lib.abs(start_number) <= 1e-14 then start_number = to_number(1);zero_flag = true end local result = math_lib.inverse(p._recigamma_abs_less1(start_number)) if math_lib.abs(math_lib.nonRealPart(z)) < 1e-14 and ((math_lib.re(z) > 1e-14 )and math.abs(math.floor(math_lib.re(z)) - math_lib.re(z)) < 1e-14 ) then result = to_number(1) end local j = to_number(start_number) for i=1,math.abs(loop_count) do if loop_count > 0 then result = result * j else result = result * math_lib.inverse(j-1) end if zero_flag==true and loop_count > 0 then zero_flag=false else if loop_count > 0 then j = j + 1 else j = j - 1 end end end if math_lib.abs(math_lib.nonRealPart(z)) < 1e-14 and ((math_lib.re(z) > 1e-14 )and math.abs(math.floor(math_lib.re(z)) - math_lib.re(z)) < 1e-14 ) then return math_lib.floor(result) end return result end


最大公因數與最小公倍數 ----------------------

local function findGcd(a, b) local r, oldr = to_number(b), to_number(a) while math_lib.abs(r) > 1e-6 do local mod_val = oldr % r oldr, r = to_number(r), mod_val end if math_lib.abs(math_lib.nonRealPart(oldr)) < 1e-14 and (math_lib.re(oldr) < 0 ) then oldr = -oldr end return oldr end

function p._gcd(...) local result, count = fold(findGcd, ...) return result end

function p._lcm(...) local function findLcm(_a, _b) local a, b = to_number(_b), to_number(_a) return math_lib.abs(a * b) / findGcd(a, b) end local result, count = fold(findLcm, ...) return result end


字串與物件擴充 (提供Module:Complex Number/Calculate使用) ----------------------

function p._symbols(name) return({ comma = ',', space = ' ', colon = ':', dot = '.', squot = "'", dquot = '"', semicolon = ';', underline = '_', lcbracket = '{', rcbracket = '}', lsbracket = '[', rsbracket = ']', lpbracket = '(', rpbracket = ')', plus = '+', minus = '-', mul = '*', div = '/', ['pow'] = '^', equal = '=', lt = '<', gt = '>', money = '$', percent = '%', ['and'] = '&', exclamation = '!', at = '@', hashtag = '#', to = '~', slash ='\\' })[name] end

function p._frameArg(str) local frame = mw.getCurrentFrame() local working_frame = frame:getParent() or frame local argname = tonumber(tostring(str)) or tostring(str) return working_frame.args[argname] or frame.args[argname] end

function p._string(str,...) local result = tostring(str) local str_list = {...} for i = 1,#str_list do result = result .. .. tostring(str_list[i]) end return result end

function p._passObject(obj) return obj end

function p._assignMember(obj, member, value) local input_obj = obj if type(obj) == type("string") then input_obj = _G[obj] end if type(obj) == type(0) or type(input_obj) == type(0) then error("無法傳值給數字", 2) end if type(obj) == type(noop_func) or type(input_obj) == type(noop_func) then error("無法傳值給函數", 2) end if input_obj == nil then error("無法傳值給空值", 2) end input_obj[member] = value return value end

function p._object(obj,...) local input_obj = obj if type(obj) == type("string") then input_obj = _G[obj] end if type(obj) == type(0) then return obj end if type(obj) == type(noop_func) then return obj end if input_obj == nil then return nil end local members = {...} if #members > 0 then local it_obj = input_obj for i = 1,#members do if type(it_obj) ~= type({}) then return nil end it_obj = (it_obj or {})[members[i]] if it_obj == nil then return nil end end return it_obj end return input_obj end

function p._typeof(obj) if type(obj) == type({}) then if obj.numberType then return type(0) end local is_array = true for index, data in pairs(obj) do if not tonumber(index) and index ~= 'metatable' then is_array = false break end end if is_array then return 'array' end end return type(obj) end

function p._array(...) return {...} end

function p._length(obj) if type(obj) == type({}) then if obj.numberType then return 1 end local max_index = 0 for key, data in pairs(obj) do local index = tonumber(key) if (index or 0) > max_index then max_index = index end end return max_index elseif type(obj) == type("string") then return mw.ustring.len(obj) else return 1 end end


數論相關 ----------------------

function p._findnext(func, x) local it = to_number(x) + 1 if type(func) ~= type(noop_func) then if math_lib.abs(to_number(func)) < 1e-14 then return to_number("inf") else return it end end local checker = func(it) while math_lib.abs(to_number(checker)) < 1e-14 do it = it + 1 checker = func(it) end return it end

function p._findlast(func, x) local it = to_number(x) - 1 if type(func) ~= type(noop_func) then if math_lib.abs(to_number(func)) < 1e-14 then return to_number("-inf") else return it end end local checker = func(it) while math_lib.abs(to_number(checker)) < 1e-14 do it = it - 1 checker = func(it) end return it end local function key_sort(t) if type(t) ~= type({"table"}) then return {t} end local key_list = {} for k,v in pairs(t) do key_list[#key_list + 1] = k end table.sort(key_list) return key_list end local function get_divisor(n, combination) local is_complex = math_lib.abs(math_lib.nonRealPart(n)) > 1e-14 local factors = {} if math_lib.abs(math_lib.floor(n)-n) < 1e-14 then local lib_factor = require('Module:Factorization') factors = (lib_factor[is_complex and "_gaussianFactorization" or "_factorization"])( is_complex and n or tonumber(tostring(n)) ) else return combination and Template:N or {} end if not combination then return factors end local gened=require('Module:Combination').getCombinationGenerator() gened:init(factors,0) return gened:findSubset() end

function p._primedivisor(_n, _x) local n = to_number(_n) if math_lib.abs(n) < 1e-14 then return 0 end

local is_complex = math_lib.abs(math_lib.nonRealPart(n)) > 1e-14 if not is_complex then n = math_lib.abs(n) end local primedivisors = key_sort(get_divisor(n, false)) return primedivisors[math_lib.abs(to_number(_x or #primedivisors))] or 0 end

function p._eulerphi(_n, _x) local n = to_number(_n) if math_lib.abs(n) < 1e-14 then return 0 end

local is_complex = math_lib.abs(math_lib.nonRealPart(n)) > 1e-14 if not is_complex and math_lib.re(n) < 1e-14 then return 0 end local primedivisors = get_divisor(n, false) local result = 1 for p,k in pairs(primedivisors) do local p_r = to_number(p) local k_r = to_number(k) result = result * math_lib.pow(p_r, k_r-1) * (p_r-1) end return result end

function p._divisor(_n, _x) local n = to_number(_n) local function _index(total) return (total <= 2) and total or (total - 1) end if math_lib.abs(n) < 1e-14 then return 0 end

local is_complex = math_lib.abs(math_lib.nonRealPart(n)) > 1e-14 if not is_complex then n = math_lib.abs(n) end local combination = get_divisor(n, true) local divisors = {} for i=1,#combination do local divisor = to_number(1) for j=1,#(combination[i]) do divisor = divisor * to_number(combination[i][j]) end divisors[#divisors+1] = divisor end table.sort(divisors, function(a,b) return math_lib.abs(a) < math_lib.abs(b) end) return divisors[math_lib.abs(to_number(_x or _index(#divisors)))] or 0 end

function p._divisorsigma(_x, _n) local x = to_number(1), n if _n == nil then n = to_number(_x) else x = to_number(_x) n = to_number(_n) end if math_lib.abs(n) < 1e-14 then return 0 end

local is_complex = math_lib.abs(math_lib.nonRealPart(n)) > 1e-14 if not is_complex then n = math_lib.abs(n) end local combination = get_divisor(n, true) local sum = to_number(0) for i=1,#combination do local divisor = to_number(1) for j=1,#(combination[i]) do divisor = divisor * to_number(combination[i][j]) end sum = sum + math_lib.pow(divisor, x) end return sum end


朗伯W函數 ----------------------

local function zexpz(z) return math_lib.exp(z) * z end --The derivative of z * exp(z) = exp(z) + z * exp(z) local function zexpz_d(z) return math_lib.exp(z) + math_lib.exp(z) * z end --The second derivative of z * exp(z) = 2. * exp(z) + z * exp(z) local function zexpz_dd(z)return math_lib.exp(z) * 2 + math_lib.exp(z) * z end --Determine the initial point for the root finding local function LWInitPoint(_z, k) local z = to_number(_z) local two_pi_k_I = math_lib.i * 2 * math_lib.pi * k local ip = math_lib.log(z) + two_pi_k_I - math_lib.log(math_lib.log(z) + two_pi_k_I) --initial point coming from the general asymptotic approximation local p = math_lib.sqrt((math_lib.e * z + 1) * 2) --used when we are close to the branch cut around zero and when k=0,-1

if math_lib.abs(-(-math_lib.exp(-1)) + z) <= 1 then --we are close to the branch cut, the initial point must be chosen carefully if k == 0 then ip = -math_lib[1] + p - 1/3 * math_lib.pow(p, 2) + 11/72 * math_lib.pow(p, 3) end if k == 1 and math_lib.im(z) < 0 then ip = -math_lib[1] - p - 1/3 * math_lib.pow(p, 2) - 11/72 * math_lib.pow(p, 3) end if k == -1 and math_lib.im(z) > 0 then ip = -math_lib[1] - p - 1/3 * math_lib.pow(p, 2) - 11/72 * math_lib.pow(p, 3) end end

if k == 0 and math_lib.abs(z - 0.5) <= 0.5 then ip = ((z * 7.061302897 + 0.1237166) * 0.35173371) / ((z * 2 + 1) * 0.827184 + 2) end-- (1,1) Pade approximant for W(0,a)

if k == -1 and math_lib.abs(z - 0.5) <= 0.5 then ip = -(((math_lib.i * 4.22096 + 2.2591588985) * ((-math_lib.i * 33.767687754 - 14.073271) * z - (-math_lib.i * 19.071643 + 12.7127) * (z*2 + 1))) / (-(-math_lib.i*10.629721 + 17.23103) * (z*2 + 1) + 2)) end -- (1,1) Pade approximant for W(-1,a)

return ip; end

function p._LambertW(_z, _k) local z = to_number(_z) local k = to_number(_k) or to_number(0) local _2 = math_lib[1] * 2 if math_lib.abs(math_lib.nonRealPart(k)) > 1e-14 then error("朗伯W函数的k只能是實數") end k = math_lib.re(k) --For some particular z and k W(z,k) has simple value: if math_lib.abs(z) == 0 then return (k == 0) and 0 or to_number(-math.huge) end if z == -math_lib.exp(-1) and (k == 0 or k == -1) then return -math_lib[1] end if z == math_lib.exp(1) and k == 0 then return math_lib[1]+0 end

--Halley method begins local w, wprev = LWInitPoint(z, k), LWInitPoint(z, k) --intermediate values in the Halley method local maxiter = 30 --max number of iterations. This eliminates improbable infinite loops local iter = 0 --iteration counter local prec = 1e-30; --difference threshold between the last two iteration results (or the iter number of iterations is taken)

wprev = w w = w - _2 *((zexpz(w) - z) * zexpz_d(w)) / (_2*math_lib.pow(zexpz_d(w),2) - (zexpz(w) - z)*zexpz_dd(w)) iter = iter + 1 while ((math_lib.abs(w - wprev) > prec) and iter < maxiter) do wprev = w w = w - _2 *((zexpz(w) - z) * zexpz_d(w)) / (_2*math_lib.pow(zexpz_d(w),2) - (zexpz(w) - z)*zexpz_dd(w)) iter = iter + 1 end return w end


範數 ----------------------

function p._norm(_z, _p) local p_value = to_number(_p or 2) local check_inf = tostring(_p):match("[Ii][Nn][Ff]") local abs_p, re_p = math_lib.abs(p_value), math_lib.re(p_value) local value_list = {} if type(_z) == type(0) or type(_z) == type("string") or (type(_z) == type({}) and _z.numberType) then local z = to_number(_z) if type(math_lib.dot) == type(noop_func) then if type(math_lib.elements) == type({}) and #(math_lib.elements) > 0 then for i=1,#(math_lib.elements) do value_list[#value_list + 1] = math_lib.dot(z, math_lib.elements[i]) end else return math_lib.abs(z) end else return math_lib.abs(z) end elseif type(_z) == type({}) and #_z > 0 then for i=1,#_z do value_list[#value_list + 1] = to_number(_z[i]) or to_number(0) end end if #value_list > 0 then local norm_sum, norm_max, norm_min, non_zero_count = 0, -1, tonumber("inf"), 0 for i=1,#value_list do local abs_value = math_lib.abs(value_list[i]) if abs_value > norm_max then norm_max = abs_value end if abs_value < norm_min then norm_min = abs_value end if abs_value ~= 0 then norm_sum = math_lib.pow(abs_value, p_value) + norm_sum end if abs_value > 1e-14 then non_zero_count = non_zero_count + 1 end end return check_inf and (re_p > 0 and norm_max or norm_min) or (abs_p >= 1 and math_lib.pow(norm_sum, math_lib.inverse(p_value)) or (abs_p ~= 0 and norm_sum or non_zero_count)) end error("無效的范數") end

return p