Ajout de plusieurs fonctions concernant l'approximation de la
distribution GAL
This commit is contained in:
parent
1e20a6a809
commit
1debac4cff
24 changed files with 730 additions and 38 deletions
2
R/cfLM.R
2
R/cfLM.R
|
@ -15,7 +15,7 @@
|
|||
#' @return Characteristic function value at point u for given parameter vector
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
cfLM <- function(u,param,time,type="mu",log=FALSE,start=0)
|
||||
cfLM <- function(u,param,time=1,type="mu",log=FALSE,start=0)
|
||||
{
|
||||
testparGAL(param,type,log)
|
||||
if(log)
|
||||
|
|
33
R/cgfEsscherGAL.R
Normal file
33
R/cgfEsscherGAL.R
Normal file
|
@ -0,0 +1,33 @@
|
|||
# Cumulant generating function of the
|
||||
# Esscher transform with parameter 1 of GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' Cumulant generating function of the
|
||||
#' Esscher transform with parameter 1 of GAL distribution
|
||||
#' @param u Transform variate
|
||||
#' @param param Parameter vector
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return Cumulant generating function value at point u for given parameter vector
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
cgfEsscherGAL <- function(u,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
log((exp(param[1]*(u+1))/(1-(1/2)*param[2]^2*(u+1)^2-param[3]*(u+1))^param[4])^eval.time/
|
||||
(exp(param[1])/(1-(1/2)*param[2]^2-param[3])^param[4])^eval.time)
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
|
||||
}
|
||||
}
|
||||
|
||||
|
|
@ -1,4 +1,3 @@
|
|||
# Moment generating function of GAL distribution
|
||||
# Cumulant generating function of GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
|
@ -6,40 +5,6 @@
|
|||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Moment generating function of GAL distribution
|
||||
#' @param u Transform variate
|
||||
#' @param param Parameter vector
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return Moment generating function value at point u for given parameter vector
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
mgfGAL <- function(u,param,type="mu",log=FALSE)
|
||||
{
|
||||
testparGAL(param,type,log)
|
||||
if(log)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
exp(exp(param[1])*u)*(1-(1/2)*exp(param[2])^2*u^2-exp(param[3])*u)^(-exp(param[4]))
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
exp(exp(param[1])*u)*((exp(param[2])^2*u^2)/2+(exp(param[3])*exp(param[2])*u)/sqrt(2)-(exp(param[2])*u)/(sqrt(2)*exp(param[3]))+1)^(-exp(param[4]))
|
||||
}
|
||||
}
|
||||
else
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
exp(param[1]*u)*(1-(1/2)*param[2]^2*u^2-param[3]*u)^(-param[4])
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
exp(param[1]*u)*((param[2]^2*u^2)/2+(param[3]*param[2]*u)/sqrt(2)-(param[2]*u)/(sqrt(2)*param[3])+1)^(-param[4])
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
#' Cumulant generating function of GAL distribution
|
||||
#' @param u Transform variate
|
||||
|
@ -74,4 +39,4 @@ cgfGAL <- function(u,param,type="mu",log=FALSE)
|
|||
log(exp(param[1]*u)*((param[2]^2*u^2)/2+(param[3]*param[2]*u)/sqrt(2)-(param[2]*u)/(sqrt(2)*param[3])+1)^(-param[4]))
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
60
R/diffcgfEsscherGAL.R
Normal file
60
R/diffcgfEsscherGAL.R
Normal file
|
@ -0,0 +1,60 @@
|
|||
# Differenciation of the cumulant generating fonction of the
|
||||
# Esscher transform with parameter 1 of the GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' Differenciation of the cumulant generating fonction of the
|
||||
#' Esscher transform with parameter 1 of the GAL distribution
|
||||
#' @param u Transform variate point of evaluation
|
||||
#' @param order Order of differenciation
|
||||
#' @param param Parameters of the GAL distirbution
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return The value of the derivative at the transform variate point of evaluation
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
diffcgfEsscherGAL <- function(u,order,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
if(order==1)
|
||||
{
|
||||
}
|
||||
if(order==2)
|
||||
{
|
||||
2*eval.time*param[4]*(2*param[3]^2+param[2]^4+2*param[2]^2+param[2]^4*u^2+2*param[2]^2*u*param[3]+2*param[3]*param[2]^2+2*param[2]^4*u)/(-2+param[2]^2*u^2+2*param[2]^2*u+param[2]^2+2*param[3]*u+2*param[3])^2
|
||||
}
|
||||
if(order==3)
|
||||
{
|
||||
-4*eval.time*param[4]*(6*param[2]^4+param[2]^6+3*param[2]^4*u^2*param[3]+6*param[2]^4*u*param[3]+6*param[2]^2*u*param[3]^2+4*param[3]^3+6*param[3]*param[2]^2+6*param[2]^4*u+param[2]^6*u^3+3*param[2]^6*u^2+3*param[2]^6*u+3*param[2]^4*param[3]+6*param[2]^2*param[3]^2)/(-2+param[2]^2*u^2+2*param[2]^2*u+param[2]^2+2*param[3]*u+2*param[3])^3
|
||||
}
|
||||
if(order==4)
|
||||
{
|
||||
|
||||
}
|
||||
}
|
||||
else if(type=="kappa")
|
||||
{
|
||||
if(order==1)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==2)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==3)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==4)
|
||||
{
|
||||
|
||||
}
|
||||
}
|
||||
}
|
76
R/diffcgfGAL.R
Normal file
76
R/diffcgfGAL.R
Normal file
|
@ -0,0 +1,76 @@
|
|||
# Differenciation of the cumulant generating fonction of the
|
||||
# GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' Differenciation of the cumulant generating fonction of the
|
||||
#' GAL distribution
|
||||
#' @param u Transform variate point of evaluation
|
||||
#' @param order Order of differenciation
|
||||
#' @param param Parameters of the GAL distirbution
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return The value of the derivative at the transform variate point
|
||||
#' of evaluation
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
diffcgfGAL <- function(u,order,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
if(order==1)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==2)
|
||||
{
|
||||
2*eval.time*param[4]*(2*param[2]^2*u*param[3]+
|
||||
2*param[3]^2+2*param[2]^2+param[2]^4*u^2)/
|
||||
(-2+param[2]^2*u^2+2*param[3]*u)^2
|
||||
}
|
||||
if(order==3)
|
||||
{
|
||||
-4*eval.time*param[4]*(3*param[2]^4*u^2*param[3]+
|
||||
6*param[2]^2*u*param[3]^2+param[2]^6*u^3+
|
||||
6*param[2]^4*u+6*param[2]^2*param[3]+4*param[3]^3)/
|
||||
(-2+param[2]^2*u^2+2*param[3]*u)^3
|
||||
}
|
||||
if(order==4)
|
||||
{
|
||||
(12*param[2]^8*param[4]*u^4+48*param[3]*param[2]^6*param[4]*u^3+
|
||||
(144*param[2]^6+144*param[3]^2*param[2]^4)*param[4]*u^2+
|
||||
(288*param[3]*param[2]^4+192*param[3]^3*param[2]^2)*param[4]*u+
|
||||
(48*param[2]^4+192*param[3]^2*param[2]^2+96*param[3]^4)*param[4])/
|
||||
(param[2]^8*u^8+8*param[3]*param[2]^6*u^7+
|
||||
(24*param[3]^2*param[2]^4-8*param[2]^6)*u^6+
|
||||
(32*param[3]^3*param[2]^2-48*param[3]*param[2]^4)*u^5+
|
||||
(24*param[2]^4-96*param[3]^2*param[2]^2+16*param[3]^4)*u^4+
|
||||
(96*param[3]*param[2]^2-64*param[3]^3)*u^3+
|
||||
(96*param[3]^2-32*param[2]^2)*u^2+(-64)*param[3]*u+16)
|
||||
}
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
if(order==1)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==2)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==3)
|
||||
{
|
||||
|
||||
}
|
||||
if(order==4)
|
||||
{
|
||||
|
||||
}
|
||||
}
|
||||
}
|
28
R/dnormapproxEsscherLM.R
Normal file
28
R/dnormapproxEsscherLM.R
Normal file
|
@ -0,0 +1,28 @@
|
|||
# Normal approximation of the density function of the Esscher
|
||||
# transform of a Laplace Motion
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Normal approximation of the density function of the
|
||||
#' Esscher transform of a Laplace Motion
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameter vector
|
||||
#' @param hEsscher Esscher transform parameter
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @param start Starting value of the process
|
||||
|
||||
#' @return Normal density function approximation of the Esscher transform
|
||||
#' of the specified Laplace motion
|
||||
dnormapproxEsscherLM <- function(x,param,hEsscher=0,eval.time=1,type="mu",log=FALSE,start=0)
|
||||
{
|
||||
dnorm(x,start+eval.time*(mGAL(1,param,type,log)+hEsscher*cmGAL(2,param,type,log)),
|
||||
sqrt(eval.time*cmGAL(2,param,type,log)))
|
||||
}
|
||||
|
||||
|
||||
|
22
R/dsaddleapproxGAL.R
Normal file
22
R/dsaddleapproxGAL.R
Normal file
|
@ -0,0 +1,22 @@
|
|||
# Saddlepoint approximation of the density function of the
|
||||
# GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Saddlepoint approximation of the density function of the
|
||||
#' GAL distribution
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameter vector
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
|
||||
#' @return Saddlepoint approximation of the density function
|
||||
dsaddleapproxGAL <- function(x,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
s <- saddlepointGAL(x,param,eval.time,type,log)
|
||||
1/sqrt(2*pi*diffcgfGAL(s,2,param,eval.time,type,log)) * exp(cgfGAL(s,param,type,log)-s*x)
|
||||
}
|
41
R/mgfGAL.R
Normal file
41
R/mgfGAL.R
Normal file
|
@ -0,0 +1,41 @@
|
|||
# Moment generating function of GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Moment generating function of GAL distribution
|
||||
#' @param u Transform variate
|
||||
#' @param param Parameter vector
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return Moment generating function value at point u for given parameter vector
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
mgfGAL <- function(u,param,type="mu",log=FALSE)
|
||||
{
|
||||
testparGAL(param,type,log)
|
||||
if(log)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
exp(exp(param[1])*u)*(1-(1/2)*exp(param[2])^2*u^2-exp(param[3])*u)^(-exp(param[4]))
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
exp(exp(param[1])*u)*((exp(param[2])^2*u^2)/2+(exp(param[3])*exp(param[2])*u)/sqrt(2)-(exp(param[2])*u)/(sqrt(2)*exp(param[3]))+1)^(-exp(param[4]))
|
||||
}
|
||||
}
|
||||
else
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
exp(param[1]*u)*(1-(1/2)*param[2]^2*u^2-param[3]*u)^(-param[4])
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
exp(param[1]*u)*((param[2]^2*u^2)/2+(param[3]*param[2]*u)/sqrt(2)-(param[2]*u)/(sqrt(2)*param[3])+1)^(-param[4])
|
||||
}
|
||||
}
|
||||
}
|
27
R/pnormapproxEsscherLM.R
Normal file
27
R/pnormapproxEsscherLM.R
Normal file
|
@ -0,0 +1,27 @@
|
|||
# Normal approximation of the distribution function of the Esscher
|
||||
# transform of a Laplace Motion
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Normal approximation of the distribution function of the
|
||||
#' Esscher transform of a Laplace Motion
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameter vector
|
||||
#' @param hEsscher Esscher transform parameter
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @param start Starting value of the process
|
||||
|
||||
#' @return Normal distribution function approximation
|
||||
pnormapproxEsscherLM <- function(x,param,hEsscher=0,eval.time=1,type="mu",log=FALSE,start=0)
|
||||
{
|
||||
pnorm(x,start+eval.time*(mGAL(1,param,type,log)+hEsscher*cmGAL(2,param,type,log)),
|
||||
sqrt(eval.time*cmGAL(2,param,type,log)))
|
||||
}
|
||||
|
||||
|
||||
|
33
R/psaddleapproxEsscherGAL.R
Normal file
33
R/psaddleapproxEsscherGAL.R
Normal file
|
@ -0,0 +1,33 @@
|
|||
# Saddlepoint approximation of the distribution function of the Esscher
|
||||
# transform of the GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Saddlepoint approximation of the distribution function of the Esscher
|
||||
#' transform of the GAL distribution
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameter vector
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
|
||||
#' @return Saddlepoint approximation of the distribution function
|
||||
psaddleapproxEsscherGAL <- function(x,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
s <- saddlepointEsscherGAL(x,param,eval.time,type,log)
|
||||
u <- s * sqrt(diffcgfEsscherGAL(s,2,param,eval.time,type,log))
|
||||
w <- sign(s)*sqrt(2*(s*x-cgfEsscherGAL(s,param,type,log)))
|
||||
|
||||
if(x==mGAL(1,param,type,log))
|
||||
{
|
||||
1/2 + diffcgfEsscherGAL(0,3,param,eval.time,type,log)/
|
||||
(6*sqrt(2*pi)*diffcgfEsscherGAL(0,2,param,eval.time,type,log)^(3/2))
|
||||
}
|
||||
else
|
||||
{
|
||||
pnorm(w)+dnorm(w)*(1/w-1/u)
|
||||
}
|
||||
}
|
33
R/psaddleapproxGAL.R
Normal file
33
R/psaddleapproxGAL.R
Normal file
|
@ -0,0 +1,33 @@
|
|||
# Saddlepoint approximation of the distribution function of the
|
||||
# GAL distribution
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
#' Saddlepoint approximation of the distribution function of the
|
||||
#' GAL distribution
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameter vector
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
|
||||
#' @return Saddlepoint approximation of the distribution function
|
||||
psaddleapproxGAL <- function(x,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
s <- saddlepointGAL(x,param,eval.time,type,log)
|
||||
u <- s * sqrt(diffcgfGAL(s,2,param,eval.time,type,log))
|
||||
w <- sign(s)*sqrt(2*(s*x-cgfGAL(s,param,type,log)))
|
||||
|
||||
if(x==mGAL(1,param,type,log))
|
||||
{
|
||||
1/2 + diffcgfGAL(0,3,param,eval.time,type,log)/
|
||||
(6*sqrt(2*pi)*diffcgfGAL(0,2,param,eval.time,type,log)^(3/2))
|
||||
}
|
||||
else
|
||||
{
|
||||
pnorm(w)+dnorm(w)*(1/w-1/u)
|
||||
}
|
||||
}
|
36
R/saddlepointEsscherGAL.R
Normal file
36
R/saddlepointEsscherGAL.R
Normal file
|
@ -0,0 +1,36 @@
|
|||
# Evaluation of the saddlepoint of the Esscher transform with
|
||||
# parameter 1 of the GAL distribution for given quantiles
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' Evaluation of the saddlepoint of the Esscher transform with
|
||||
#' parameter 1 of the GAL distribution for given quantiles
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameters of the underlying GAL distribution
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return The value of the saddlepoint for each point of the vector of quantiles
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
saddlepointEsscherGAL <- function(x,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
(-eval.time*param[1]*param[2]^2+eval.time*param[4]*param[2]^2+x*param[2]^2-
|
||||
eval.time*param[1]*param[3]+x*param[3]-
|
||||
sqrt(eval.time^2*param[1]^2*param[3]^2-2*eval.time*param[1]*param[3]^2*x+
|
||||
eval.time^2*param[4]^2*param[2]^4+x^2*param[3]^2+
|
||||
2*eval.time^2*param[1]^2*param[2]^2-
|
||||
4*eval.time*param[1]*param[2]^2*x+2*x^2*param[2]^2))/
|
||||
(param[2]^2*(eval.time*param[1]-x))
|
||||
}
|
||||
else if (type=="kappa")
|
||||
{
|
||||
|
||||
}
|
||||
}
|
32
R/saddlepointGAL.R
Normal file
32
R/saddlepointGAL.R
Normal file
|
@ -0,0 +1,32 @@
|
|||
# Evaluation of the saddlepoint of the GAL distribution for given quantiles
|
||||
#
|
||||
# Author: Francois Pelletier
|
||||
#
|
||||
# LGPL 3.0
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' Evaluation of the saddlepoint of the GAL distribution for given quantiles
|
||||
#' @param x vector of quantiles
|
||||
#' @param param Parameters of the GAL distribution
|
||||
#' @param eval.time Time of the process
|
||||
#' @param type Choose between "mu" or "kappa" parametrization
|
||||
#' @param log Logical for log-parameters
|
||||
#' @return The value of the saddlepoint for each point of the vector of quantiles
|
||||
#'
|
||||
#' @author Francois Pelletier
|
||||
saddlepointGAL <- function(x,param,eval.time=1,type="mu",log=FALSE)
|
||||
{
|
||||
if(type=="mu")
|
||||
{
|
||||
(-eval.time*param[1]*param[3]+eval.time*param[4]*param[2]^2+x*param[3]-
|
||||
(eval.time^2*param[1]^2*param[3]^2-2*eval.time*param[1]*param[3]^2*x+
|
||||
eval.time^2*param[4]^2*param[2]^4+x^2*param[3]^2+2*eval.time^2*param[1]^2*
|
||||
param[2]^2-4*eval.time*param[1]*param[2]^2*x+2*x^2*param[2]^2)^(1/2))/
|
||||
param[2]^2/(eval.time*param[1]-x)
|
||||
}
|
||||
if(type=="kappa")
|
||||
{
|
||||
|
||||
}
|
||||
}
|
|
@ -2,7 +2,7 @@
|
|||
\alias{cfLM}
|
||||
\title{Characteristic function of Laplace motion}
|
||||
\usage{
|
||||
cfLM(u, param, time, type = "mu", log = FALSE, start = 0)
|
||||
cfLM(u, param, time = 1, type = "mu", log = FALSE, start = 0)
|
||||
}
|
||||
\arguments{
|
||||
\item{u}{Transform variate}
|
||||
|
|
31
man/cgfEsscherGAL.Rd
Normal file
31
man/cgfEsscherGAL.Rd
Normal file
|
@ -0,0 +1,31 @@
|
|||
\name{cgfEsscherGAL}
|
||||
\alias{cgfEsscherGAL}
|
||||
\title{Cumulant generating function of the
|
||||
Esscher transform with parameter 1 of GAL distribution}
|
||||
\usage{
|
||||
cgfEsscherGAL(u, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{u}{Transform variate}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
Cumulant generating function value at point u for given
|
||||
parameter vector
|
||||
}
|
||||
\description{
|
||||
Cumulant generating function of the Esscher transform with
|
||||
parameter 1 of GAL distribution
|
||||
}
|
||||
\author{
|
||||
Francois Pelletier
|
||||
}
|
||||
|
34
man/diffcgfEsscherGAL.Rd
Normal file
34
man/diffcgfEsscherGAL.Rd
Normal file
|
@ -0,0 +1,34 @@
|
|||
\name{diffcgfEsscherGAL}
|
||||
\alias{diffcgfEsscherGAL}
|
||||
\title{Differenciation of the cumulant generating fonction of the
|
||||
Esscher transform with parameter 1 of the GAL distribution}
|
||||
\usage{
|
||||
diffcgfEsscherGAL(u, order, param, eval.time = 1, type = "mu",
|
||||
log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{u}{Transform variate point of evaluation}
|
||||
|
||||
\item{order}{Order of differenciation}
|
||||
|
||||
\item{param}{Parameters of the GAL distirbution}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
The value of the derivative at the transform variate point
|
||||
of evaluation
|
||||
}
|
||||
\description{
|
||||
Differenciation of the cumulant generating fonction of the
|
||||
Esscher transform with parameter 1 of the GAL distribution
|
||||
}
|
||||
\author{
|
||||
Francois Pelletier
|
||||
}
|
||||
|
33
man/diffcgfGAL.Rd
Normal file
33
man/diffcgfGAL.Rd
Normal file
|
@ -0,0 +1,33 @@
|
|||
\name{diffcgfGAL}
|
||||
\alias{diffcgfGAL}
|
||||
\title{Differenciation of the cumulant generating fonction of the
|
||||
GAL distribution}
|
||||
\usage{
|
||||
diffcgfGAL(u, order, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{u}{Transform variate point of evaluation}
|
||||
|
||||
\item{order}{Order of differenciation}
|
||||
|
||||
\item{param}{Parameters of the GAL distirbution}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
The value of the derivative at the transform variate point
|
||||
of evaluation
|
||||
}
|
||||
\description{
|
||||
Differenciation of the cumulant generating fonction of the
|
||||
GAL distribution
|
||||
}
|
||||
\author{
|
||||
Francois Pelletier
|
||||
}
|
||||
|
33
man/dnormapproxEsscherLM.Rd
Normal file
33
man/dnormapproxEsscherLM.Rd
Normal file
|
@ -0,0 +1,33 @@
|
|||
\name{dnormapproxEsscherLM}
|
||||
\alias{dnormapproxEsscherLM}
|
||||
\title{Normal approximation of the density function of the
|
||||
Esscher transform of a Laplace Motion}
|
||||
\usage{
|
||||
dnormapproxEsscherLM(x, param, hEsscher = 0, eval.time = 1, type = "mu",
|
||||
log = FALSE, start = 0)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{hEsscher}{Esscher transform parameter}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
|
||||
\item{start}{Starting value of the process}
|
||||
}
|
||||
\value{
|
||||
Normal density function approximation of the Esscher
|
||||
transform of the specified Laplace motion
|
||||
}
|
||||
\description{
|
||||
Normal approximation of the density function of the Esscher
|
||||
transform of a Laplace Motion
|
||||
}
|
||||
|
27
man/dsaddleapproxGAL.Rd
Normal file
27
man/dsaddleapproxGAL.Rd
Normal file
|
@ -0,0 +1,27 @@
|
|||
\name{dsaddleapproxGAL}
|
||||
\alias{dsaddleapproxGAL}
|
||||
\title{Saddlepoint approximation of the density function of the
|
||||
GAL distribution}
|
||||
\usage{
|
||||
dsaddleapproxGAL(x, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
Saddlepoint approximation of the density function
|
||||
}
|
||||
\description{
|
||||
Saddlepoint approximation of the density function of the
|
||||
GAL distribution
|
||||
}
|
||||
|
32
man/pnormapproxEsscherLM.Rd
Normal file
32
man/pnormapproxEsscherLM.Rd
Normal file
|
@ -0,0 +1,32 @@
|
|||
\name{pnormapproxEsscherLM}
|
||||
\alias{pnormapproxEsscherLM}
|
||||
\title{Normal approximation of the distribution function of the
|
||||
Esscher transform of a Laplace Motion}
|
||||
\usage{
|
||||
pnormapproxEsscherLM(x, param, hEsscher = 0, eval.time = 1, type = "mu",
|
||||
log = FALSE, start = 0)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{hEsscher}{Esscher transform parameter}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
|
||||
\item{start}{Starting value of the process}
|
||||
}
|
||||
\value{
|
||||
Normal distribution function approximation
|
||||
}
|
||||
\description{
|
||||
Normal approximation of the distribution function of the
|
||||
Esscher transform of a Laplace Motion
|
||||
}
|
||||
|
27
man/psaddleapproxEsscherGAL.Rd
Normal file
27
man/psaddleapproxEsscherGAL.Rd
Normal file
|
@ -0,0 +1,27 @@
|
|||
\name{psaddleapproxEsscherGAL}
|
||||
\alias{psaddleapproxEsscherGAL}
|
||||
\title{Saddlepoint approximation of the distribution function of the Esscher
|
||||
transform of the GAL distribution}
|
||||
\usage{
|
||||
psaddleapproxEsscherGAL(x, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
Saddlepoint approximation of the distribution function
|
||||
}
|
||||
\description{
|
||||
Saddlepoint approximation of the distribution function of
|
||||
the Esscher transform of the GAL distribution
|
||||
}
|
||||
|
27
man/psaddleapproxGAL.Rd
Normal file
27
man/psaddleapproxGAL.Rd
Normal file
|
@ -0,0 +1,27 @@
|
|||
\name{psaddleapproxGAL}
|
||||
\alias{psaddleapproxGAL}
|
||||
\title{Saddlepoint approximation of the distribution function of the
|
||||
GAL distribution}
|
||||
\usage{
|
||||
psaddleapproxGAL(x, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameter vector}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
Saddlepoint approximation of the distribution function
|
||||
}
|
||||
\description{
|
||||
Saddlepoint approximation of the distribution function of
|
||||
the GAL distribution
|
||||
}
|
||||
|
32
man/saddlepointEsscherGAL.Rd
Normal file
32
man/saddlepointEsscherGAL.Rd
Normal file
|
@ -0,0 +1,32 @@
|
|||
\name{saddlepointEsscherGAL}
|
||||
\alias{saddlepointEsscherGAL}
|
||||
\title{Evaluation of the saddlepoint of the Esscher transform with
|
||||
parameter 1 of the GAL distribution for given quantiles}
|
||||
\usage{
|
||||
saddlepointEsscherGAL(x, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameters of the underlying GAL
|
||||
distribution}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
The value of the saddlepoint for each point of the vector
|
||||
of quantiles
|
||||
}
|
||||
\description{
|
||||
Evaluation of the saddlepoint of the Esscher transform with
|
||||
parameter 1 of the GAL distribution for given quantiles
|
||||
}
|
||||
\author{
|
||||
Francois Pelletier
|
||||
}
|
||||
|
30
man/saddlepointGAL.Rd
Normal file
30
man/saddlepointGAL.Rd
Normal file
|
@ -0,0 +1,30 @@
|
|||
\name{saddlepointGAL}
|
||||
\alias{saddlepointGAL}
|
||||
\title{Evaluation of the saddlepoint of the GAL distribution for given quantiles}
|
||||
\usage{
|
||||
saddlepointGAL(x, param, eval.time = 1, type = "mu", log = FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{vector of quantiles}
|
||||
|
||||
\item{param}{Parameters of the GAL distribution}
|
||||
|
||||
\item{eval.time}{Time of the process}
|
||||
|
||||
\item{type}{Choose between "mu" or "kappa"
|
||||
parametrization}
|
||||
|
||||
\item{log}{Logical for log-parameters}
|
||||
}
|
||||
\value{
|
||||
The value of the saddlepoint for each point of the vector
|
||||
of quantiles
|
||||
}
|
||||
\description{
|
||||
Evaluation of the saddlepoint of the GAL distribution for
|
||||
given quantiles
|
||||
}
|
||||
\author{
|
||||
Francois Pelletier
|
||||
}
|
||||
|
Loading…
Reference in a new issue