module fvn_fnlib !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! This module is a generic interface for fn library ! http://www.netlib.org/fn !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Elementary Functions !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Argument interface carg real(4) function carg(z) complex(4) :: z end function carg real(8) function zarg(z) complex(8) :: z end function zarg end interface carg ! Cubic root interface cbrt real(4) function cbrt(x) real(4) :: x end function cbrt real(8) function dcbrt(x) real(8) :: x end function dcbrt complex(4) function ccbrt(z) complex(4) :: z end function ccbrt complex(8) function zcbrt(z) complex(8) :: z end function zcbrt end interface cbrt ! (exp(x) -1)/x interface exprl real(4) function exprel(x) real(4) :: x end function exprel real(8) function dexprl(x) real(8) :: x end function dexprl complex(4) function cexprl(z) complex(4) :: z end function cexprl complex(8) function zexprl(z) complex(8) :: z end function zexprl end interface exprl ! log10 extension to complex arguments interface log10 complex(4) function clog10(z) complex(4) :: z end function clog10 complex(8) function zlog10(z) complex(8) :: z end function zlog10 end interface log10 ! ln(x+1) interface alnrel real(4) function alnrel(x) real(4) :: x end function alnrel real(8) function dlnrel(x) real(8) :: x end function dlnrel complex(4) function clnrel(z) complex(4) :: z end function clnrel complex(8) function zlnrel(z) complex(8) :: z end function zlnrel end interface alnrel !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Elementary Functions !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Trigonometry !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Extension de la tangente aux arguments complexes interface tan complex(4) function ctan(z) complex(4) :: z end function ctan complex(8) function ztan(z) complex(8) :: z end function ztan end interface tan ! Cotangente interface cot real(4) function cot(x) real(4) :: x end function cot real(8) function dcot(x) real(8) :: x end function dcot complex(4) function ccot(z) complex(4) :: z end function ccot complex(8) function zcot(z) complex(8) :: z end function zcot end interface cot ! Sinus in degree interface sindg real(4) function sindg(x) real(4) :: x end function sindg real(8) function dsindg(x) real(8) :: x end function dsindg end interface sindg ! Cosinus in degree interface cosdg real(4) function cosdg(x) real(4) :: x end function cosdg real(8) function dcosdg(x) real(8) :: x end function dcosdg end interface cosdg ! Extension de l'arcsinus aux arguments complexes interface asin complex(4) function casin(z) complex(4) :: z end function casin complex(8) function zasin(z) complex(8) :: z end function zasin end interface asin ! Extension de l'arccosinus aux arguments complexes interface acos complex(4) function cacos(z) complex(4) :: z end function cacos complex(8) function zacos(z) complex(8) :: z end function zacos end interface acos ! Extension de l'arctangente aux arguments complexes interface atan complex(4) function catan(z) complex(4) :: z end function catan complex(8) function zatan(z) complex(8) :: z end function zatan end interface atan ! Extension de atan2 aux arguments complexes interface atan2 complex(4) function catan2(csn,ccs) complex(4) :: csn,ccs end function catan2 complex(8) function zatan2(csn,ccs) complex(8) :: csn,ccs end function zatan2 end interface atan2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Hyperbolic Trigonometry !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Extension du Sinus hyperbolique aux arguments complexes interface sinh complex(4) function csinh(z) complex(4) :: z end function csinh complex(8) function zsinh(z) complex(8) :: z end function zsinh end interface sinh ! Extension du Cosinus hyperbolique aux arguments complexes interface cosh complex(4) function ccosh(z) complex(4) :: z end function ccosh complex(8) function zcosh(z) complex(8) :: z end function zcosh end interface cosh ! Extension de la tangente hyperbolique aux arguments complexes interface tanh complex(4) function ctanh(z) complex(4) :: z end function ctanh complex(8) function ztanh(z) complex(8) :: z end function ztanh end interface tanh ! Arc sinus hyperbolique interface asinh real(4) function asinh(x) real(4) :: x end function asinh real(8) function dasinh(x) real(8) :: x end function dasinh complex(4) function casinh(z) complex(4) :: z end function casinh complex(8) function zasinh(z) complex(8) :: z end function zasinh end interface asinh ! Arc cosinus hyperbolique interface acosh real(4) function acosh(x) real(4) :: x end function acosh real(8) function dacosh(x) real(8) :: x end function dacosh complex(4) function cacosh(z) complex(4) :: z end function cacosh complex(8) function zacosh(z) complex(8) :: z end function zacosh end interface acosh ! Arc tangente hyperbolique interface atanh real(4) function atanh(x) real(4) :: x end function atanh real(8) function datanh(x) real(8) :: x end function datanh complex(4) function catanh(z) complex(4) :: z end function catanh complex(8) function zatanh(z) complex(8) :: z end function zatanh end interface atanh !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Trigonometry !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Exponential integral and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Exponential integral ei(x) interface ei real(4) function ei(x) real(4) :: x end function ei real(8) function dei(x) real(8) :: x end function dei end interface ei ! Exponential integral e1(x) interface e1 real(4) function e1(x) real(4) :: x end function e1 real(8) function de1(x) real(8) :: x end function de1 end interface e1 !!!!!!!!!!!!!!! ! MISSING ENE !!!!!!!!!!!!!!! ! Logarithm integral interface ali real(4) function ali(x) real(4) :: x end function ali real(8) function dli(x) real(8) :: x end function dli end interface ali ! Sine integral interface si real(4) function si(x) real(4) :: x end function si real(8) function dsi(x) real(8) :: x end function dsi end interface si ! Cosine integral interface ci real(4) function ci(x) real(4) :: x end function ci real(8) function dci(x) real(8) :: x end function dci end interface ci ! Cosine integral alternate definition interface cin real(4) function cin(x) real(4) :: x end function cin real(8) function dcin(x) real(8) :: x end function dcin end interface cin ! Hyperbolic sine integral interface shi real(4) function shi(x) real(4) :: x end function shi real(8) function dshi(x) real(8) :: x end function dshi end interface shi ! Hyperbolic cosine integral interface chi real(4) function chi(x) real(4) :: x end function chi real(8) function dchi(x) real(8) :: x end function dchi end interface chi ! Hyperbolic cosine integral alternate definition interface cinh real(4) function cinh(x) real(4) :: x end function cinh real(8) function dcinh(x) real(8) :: x end function dcinh end interface cinh !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Exponential integral and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Gamma family !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! No generic interface for fac and binom but we still ! define their prototypes ! Factorial interface real(4) function fac(n) integer(4) :: n end function fac real(8) function dfac(n) integer(4) :: n end function dfac ! Binomial coefficient real(4) function binom(n,m) integer(4) :: n,m end function binom real(8) function dbinom(n,m) integer(4) :: n,m end function dbinom end interface ! Gamma function interface gamma real(4) function gamma(x) real(4) :: x end function gamma real(8) function dgamma(x) real(8) :: x end function dgamma complex(4) function cgamma(z) complex(4) :: z end function cgamma complex(8) function zgamma(z) complex(8) :: z end function zgamma end interface gamma ! Reciprocal of gamma function interface gamr real(4) function gamr(x) real(4) :: x end function gamr real(8) function dgamr(x) real(8) :: x end function dgamr complex(4) function cgamr(z) complex(4) :: z end function cgamr complex(8) function zgamr(z) complex(8) :: z end function zgamr end interface gamr ! natural log of abs(gamma) interface alngam real(4) function alngam(x) real(4) :: x end function alngam real(8) function dlngam(x) real(8) :: x end function dlngam complex(4) function clngam(z) complex(4) :: z end function clngam complex(8) function zlngam(z) complex(8) :: z end function zlngam end interface alngam ! log abs gamma and sign interface algams subroutine algams(x,algam,sgngam) real(4) :: x end subroutine algams subroutine dlgams(x,algam,sgngam) real(8) :: x end subroutine dlgams end interface algams ! Incomplete gamma function interface gami real(4) function gami(a,x) real(4) :: a,x end function gami real(8) function dgami(a,x) real(8) :: a,x end function dgami end interface gami ! Complementary incomplete gamma function interface gamic real(4) function gamic(a,x) real(4) :: a,x end function gamic real(8) function dgamic(a,x) real(8) :: a,x end function dgamic end interface gamic ! Tricomi's incomplete gamma function interface gamit real(4) function gamit(a,x) real(4) :: a,x end function gamit real(8) function dgamit(a,x) real(8) :: a,x end function dgamit end interface gamit ! Psi function interface psi real(4) function psi(x) real(4) :: x end function psi real(8) function dpsi(x) real(8) :: x end function dpsi complex(4) function cpsi(z) complex(4) :: z end function cpsi complex(8) function zpsi(z) complex(8) :: z end function zpsi end interface psi ! Pochhammer interface poch real(4) function poch(a,x) real(4) :: a,x end function poch real(8) function dpoch(a,x) real(8) :: a,x end function dpoch end interface poch ! Pochhammer first order interface poch1 real(4) function poch1(a,x) real(4) :: a,x end function poch1 real(8) function dpoch1(a,x) real(8) :: a,x end function dpoch1 end interface poch1 ! Beta function interface beta real(4) function beta(a,b) real(4) :: a,b end function beta real(8) function dbeta(a,b) real(8) :: a,b end function dbeta complex(4) function cbeta(a,b) complex(4) :: a,b end function cbeta complex(8) function zbeta(a,b) complex(8) :: a,b end function zbeta end interface beta ! natural log of beta interface albeta real(4) function albeta(a,b) real(4) :: a,b end function albeta real(8) function dlbeta(a,b) real(8) :: a,b end function dlbeta complex(4) function clbeta(a,b) complex(4) :: a,b end function clbeta complex(8) function zlbeta(a,b) complex(8) :: a,b end function zlbeta end interface albeta ! Incomplete beta function interface betai real(4) function betai(x,pin,qin) real(4) :: x,pin,qin end function betai real(8) function dbetai(x,pin,qin) real(8) :: x,pin,qin end function dbetai end interface betai !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Gamma family !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Error function and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Error function interface erf real(4) function erf(x) real(4) :: x end function erf real(8) function derf(x) real(8) :: x end function derf end interface erf ! Complementary error function interface erfc real(4) function erfc(x) real(4) :: x end function erfc real(8) function derfc(x) real(8) :: x end function derfc end interface erfc !!!!!!!!!!! ! MISSING ERFCE ! MISSING CERFI ! MISSING ERFI ! MISSING ERFCI !!!!!!!!!!!!!! ! Dawson's function interface daws real(4) function daws(x) real(4) :: x end function daws real(8) function ddaws(x) real(8) :: x end function ddaws end interface daws !!!!!!!!!!!!!!!!! ! MISSING FRESC ! MISSING FRESS !!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Error function and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Bessel functions and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !J0(x) interface bsj0 real(4) function besj0(x) real(4) :: x end function besj0 real(8) function dbesj0(x) real(8) :: x end function dbesj0 end interface bsj0 !J1(x) interface bsj1 real(4) function besj1(x) real(4) :: x end function besj1 real(8) function dbesj1(x) real(8) :: x end function dbesj1 end interface bsj1 !Y0(x) interface bsy0 real(4) function besy0(x) real(4) :: x end function besy0 real(8) function dbesy0(x) real(8) x end function dbesy0 end interface bsy0 !Y1(x) interface bsy1 real(4) function besy1(x) real(4) :: x end function besy1 real(8) function dbesy1(x) real(8) x end function dbesy1 end interface bsy1 !I0(x) interface bsi0 real(4) function besi0(x) real(4) :: x end function besi0 real(8) function dbesi0(x) real(8) x end function dbesi0 end interface bsi0 !I1(x) interface bsi1 real(4) function besi1(x) real(4) :: x end function besi1 real(8) function dbesi1(x) real(8) x end function dbesi1 end interface bsi1 !K0(x) interface bsk0 real(4) function besk0(x) real(4) :: x end function besk0 real(8) function dbesk0(x) real(8) x end function dbesk0 end interface bsk0 !K1(x) interface bsk1 real(4) function besk1(x) real(4) :: x end function besk1 real(8) function dbesk1(x) real(8) x end function dbesk1 end interface bsk1 ! Exponentially scaled I0 interface bsi0e real(4) function besi0e(x) real(4) :: x end function besi0e real(8) function dbsi0e(x) real(8) :: x end function dbsi0e end interface bsi0e ! Exponentially scaled I1 interface bsi1e real(4) function besi1e(x) real(4) :: x end function besi1e real(8) function dbsi1e(x) real(8) :: x end function dbsi1e end interface bsi1e ! Exponentially scaled K0 interface bsk0e real(4) function besk0e(x) real(4) :: x end function besk0e real(8) function dbsk0e(x) real(8) :: x end function dbsk0e end interface bsk0e ! Exponentially scaled K1 interface bsk1e real(4) function besk1e(x) real(4) :: x end function besk1e real(8) function dbsk1e(x) real(8) :: x end function dbsk1e end interface bsk1e ! nth order J interface bsjn real(4) function besjn(n,x,factor,big) integer(4) :: n real(4) :: x integer(4), optional :: factor real(4), optional :: big end function besjn real(8) function dbesjn(n,x,factor,big) integer(4) :: n real(8) :: x integer(4), optional :: factor real(8), optional :: big end function dbesjn end interface bsjn ! nth order Y interface bsyn real(4) function besyn(n,x) integer(4) :: n real(4) :: x end function besyn real(8) function dbesyn(n,x) integer(4) :: n real(8) :: x end function dbesyn end interface bsyn ! nth order I interface bsin real(4) function besin(n,x,factor,big) integer(4) :: n real(4) :: x integer(4), optional :: factor real(4), optional :: big end function besin real(8) function dbesin(n,x,factor,big) integer(4) :: n real(8) :: x integer(4), optional :: factor real(8), optional :: big end function dbesin end interface bsin ! nth order K interface bskn real(4) function beskn(n,x) integer(4) :: n real(4) :: x end function beskn real(8) function dbeskn(n,x) integer(4) :: n real(8) :: x end function dbeskn end interface bskn !!!!!!!!!!!!!!!!!!!!! ! MISSING BSJNS ! MISSING BSINS ! MISSING BSJS ! MISSING BSYS ! MISSING BSIS ! MISSING BSIES !!!!!!!!!!!!!!!!!!!!! ! K nu + k interface bsks subroutine besks(xnu,x,nin,bk) real(4) :: xnu,x integer :: nin real(4), dimension(nin) :: bk end subroutine besks subroutine dbesks(xnu,x,nin,bk) real(8) :: xnu,x integer :: nin real(8), dimension(nin) :: bk end subroutine dbesks end interface bsks ! Exponentially scaled K nu + k interface bskes subroutine beskes(xnu,x,nin,bke) real(4) :: xnu,x integer :: nin real(4),dimension(nin) :: bke end subroutine beskes subroutine dbskes(xnu,x,nin,bke) real(8) :: xnu,x integer :: nin real(8),dimension(nin) :: bke end subroutine dbskes end interface bskes !!!!!!!!!!!!!!!!!! ! MISSING CBJS ! MISSING CBYS ! MISSING CBIS !!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Bessel functions and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Airy functions and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !ai(x) interface ai real(4) function ai(x) real(4) :: x end function ai real(8) function dai(x) real(8) :: x end function dai end interface ai !bi(x) interface bi real(4) function bi(x) real(4) :: x end function bi real(8) function dbi(x) real(8) :: x end function dbi end interface bi !ai'(x) interface aid real(4) function aid(x) real(4) :: x end function aid real(8) function daid(x) real(8) :: x end function daid end interface aid !bi'(x) interface bid real(4) function bid(x) real(4) :: x end function bid real(8) function dbid(x) real(8) :: x end function dbid end interface bid ! Exponentially scaled Ai interface aie real(4) function aie(x) real(4) :: x end function aie real(8) function daie(x) real(8) :: x end function daie end interface aie ! Exponentially scaled Bi interface bie real(4) function bie(x) real(4) :: x end function bie real(8) function dbie(x) real(8) :: x end function dbie end interface bie ! Exponentially scaled Ai'(x) interface aide real(4) function aide(x) real(4) :: x end function aide real(8) function daide(x) real(8) :: x end function daide end interface aide ! Exponentially scaled Bi'(x) interface bide real(4) function bide(x) real(4) :: x end function bide real(8) function dbide(x) real(8) :: x end function dbide end interface bide !!!!!!!!!!!!!!!!!!!!!!! ! MISSING CAI ! MISSING CBI ! MISSING CAID ! MISSING CBID !!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Airy functions and related !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Miscellanous functions !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! Spence dilogarithm interface spenc real(4) function spenc(x) real(4) :: x end function spenc real(8) function dspenc(x) real(8) :: x end function dspenc end interface spenc ! Initialize a Chebyshev series interface inits integer(4) function inits(os,nos,eta) real(4),dimension(nos) :: os integer(4) :: nos real(4) :: eta end function inits integer(4) function initds(dos,nos,eta) real(8),dimension(nos) :: dos integer(4) :: nos real(4) :: eta end function initds end interface inits ! Evaluate a Chebyshev series interface csevl real(4) function csevl(x,cs,n) real(4) :: x real(4),dimension(n) :: cs integer(4) :: n end function csevl real(8) function dcsevl(x,a,n) real(8) :: x real(8), dimension(n) :: a integer(4) :: n end function dcsevl end interface csevl !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! END Miscellanous functions !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! end module fvn_fnlib