R/MOEW.R

Defines functions rmoew hra.moew crf.moew ks.moew qq.moew pp.moew abic.moew

Documented in abic.moew crf.moew hra.moew ks.moew pp.moew qq.moew rmoew

## ***************************************************************************
## Probability density function(pdf) of Marshall-Olkin Extended Weibull(MOEW) distribution
dmoew <- function (x, alpha, lambda, log=FALSE)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(x)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (x <= 0))    
        stop("Invalid arguments")
     u <- -(x^alpha)
    num <- alpha * lambda * (x^(alpha-1.0))* exp(u)
    deno <- (1.0 - (1.0-lambda)*exp(u))^ 2.0
    pdf <- num/deno
    if(log) 
      pdf<- log(pdf)
    return(pdf)   
}
## ***************************************************************************
## Cummulative distribution function(cdf) of Marshall-Olkin Extended Weibull(MOEW) distribution
pmoew <- function (q, alpha, lambda, lower.tail=TRUE, log.p=FALSE)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(q)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (q <= 0))    
        stop("Invalid arguments")
      u <- -(q^alpha)
    cdf <- (1.0 - exp(u))/(1.0-(1.0-lambda)*exp(u))
    if(!lower.tail)
        cdf <- 1.0 - cdf
    if(log.p)
        cdf <- log(cdf)
    return(cdf)  
}
## ***************************************************************************
## Quantile function of Marshall-Olkin Extended Weibull(MOEW) distribution
qmoew <- function (p, alpha, lambda, lower.tail=TRUE, log.p=FALSE)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(p)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (p <= 0) || (p > 1))
        stop("Invalid arguments")
     qtl<- (log(1.0 + ((lambda*p)/(1.0-p))))^(1.0/alpha)    
  if(!lower.tail) 
      qtl<- (log(1.0 + ((lambda*(1.0-p))/p)))^(1.0/alpha)   
     if(log.p) 
        qtl<- log(qtl)    
    return(qtl)   
}
## ***************************************************************************
## Random variate generation from Marshall-Olkin Extended Weibull(MOEW) distribution
rmoew <- function(n, alpha, lambda)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(n)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (n <= 0))
        stop("Invalid arguments")
    u <- runif(n)
 return(log(1.0 + ((lambda*u)/(1.0-u)))^(1.0/alpha))
}
## *************************************************************************** 
## Reliability function of Marshall-Olkin Extended Weibull(MOEW) distribution
smoew <- function (x, alpha, lambda)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(x)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (x <= 0))
        stop("Invalid arguments")     
    u <- -(x^alpha)     
    return(1.0-(1.0 - exp(u))/(1.0-(1.0-lambda)*exp(u)))   
}
## ***************************************************************************
## Hazard function of Marshall-Olkin Extended Weibull(MOEW) distribution
hmoew <- function (x, alpha, lambda)
{
    if((!is.numeric(alpha)) || (!is.numeric(lambda)) || (!is.numeric(x)))
        stop("non-numeric argument to mathematical function")
    if((min(alpha) <= 0) || (min(lambda) <= 0) || (x <= 0))
        stop("Invalid arguments")  
     u <- -(x^alpha)  
    return(alpha * (x^(alpha-1.0))/(1.0 - (1.0-lambda)*exp(u)))   
} 
## ***************************************************************************
## Hazard rate average function of Marshall-Olkin Extended Weibull(MOEW) distribution
hra.moew <- function(x, alpha, lambda)
{
    r <- smoew(x, alpha, lambda)
    fra <-((-1)*log(r))/x
    return(fra)
}
## ***************************************************************************
## Conditional Hazard rate function of Marshall-Olkin Extended Weibull(MOEW) distribution
crf.moew <- function(x, t=0, alpha, lambda)
{
      t <- t
      x <- x
      nume<-hmoew(x+t, alpha, lambda)
      deno<-hmoew(x, alpha, lambda)
      return(nume/deno)
}
## ***************************************************************************
## Kolmogorov-Smirnov test (One-sample)for Marshall-Olkin Extended Weibull(MOEW) distribution
ks.moew <-function(x, alpha.est, lambda.est,
            alternative = c("less", "two.sided", "greater"), plot = FALSE, ...)
{
    alpha <- alpha.est
    lambda <- lambda.est
    res <- ks.test(x, pmoew, alpha, lambda, alternative = alternative)
        if(plot){
        plot(ecdf(x),do.points=FALSE, main='Empirical and Theoretical cdfs',
             xlab = 'x', ylab = 'Fn(x)', ...)
        mini <- min(x)
        maxi <- max(x)
        t <- seq(mini, maxi, by = 0.01)
        y <- pmoew(t, alpha, lambda)
        lines(t, y, lwd = 2, col = 2)
    }
    return(res)
}
## ***************************************************************************
## Quantile-Quantile(QQ) plot for Marshall-Olkin Extended Weibull(MOEW) distribution
qq.moew <- function(x, alpha.est, lambda.est, main = ' ', line.qt = FALSE, ...)
{
    xlab <- 'Empirical quantiles'
    ylab <- 'Theoretical quantiles'
    alpha <- alpha.est
    lambda <- lambda.est       
    n <- length(x)
    k <- seq(1, n, by = 1)
    P <- (k - 0.5) / n
    Finv <-qmoew(P, alpha, lambda)
    quantiles <-sort(x)
    limx<-c(min(x), max(x))
    plot(quantiles, Finv, xlab = xlab, ylab = ylab, xlim = limx, 
         ylim = limx, main = main, col = 4, lwd = 2, ...)
    lines(c(0,limx), c(0,limx), col = 2, lwd = 2)
    if(line.qt){
        quant <- quantile(x)
        x1 <- quant[2]
        x2 <- quant[4]
        y1 <- qmoew(0.25, alpha, lambda)
        y2 <- qmoew(0.75, alpha, lambda)
        m <- ((y2-y1) / (x2-x1))
        inter <- y1 - (m * x1)
        abline(inter, m, col = 2, lwd = 2)
    }
    invisible(list(x = quantiles, y = Finv))
}
## ***************************************************************************
## Probability-Probability(PP) plot for Marshall-Olkin Extended Weibull(MOEW) distribution
pp.moew <- function(x, alpha.est, lambda.est, main=' ',line=FALSE, ...)
{
    xlab <- 'Empirical distribution function'
    ylab <- 'Theoretical distribution function'
    alpha <- alpha.est
    lambda <- lambda.est
    F <- pmoew(x, alpha,lambda)
    Pemp <- sort(F)
    n <- length(x)
    k <- seq(1, n, by = 1)
    Pteo <-(k - 0.5) / n
    plot(Pemp, Pteo, xlab = xlab, ylab = ylab, col = 4, 
         xlim = c(0, 1), ylim = c(0, 1), main = main, lwd = 2, ...)
    if(line)
        lines(c(0, 1), c(0, 1), col = 2, lwd = 2)
    Cor.Coeff <- cor(Pemp, Pteo)
    Determination.Coeff <- (Cor.Coeff^2) * 100
    return(list(Cor.Coeff = Cor.Coeff, Determination.Coeff = Determination.Coeff))
}
## ***************************************************************************
# Akaike information criterium (AIC) and
# Schwartz information criterion (BIC) for Marshall-Olkin Extended Weibull distribution
 abic.moew <- function(x, alpha.est,lambda.est){ 
    alpha <- alpha.est
    lambda <- lambda.est
    n <- length(x)
    p <- 2
    f <- dmoew(x, alpha, lambda)
    l <- log(f)
    LogLik <- sum(l)
    AIC <- - 2 * LogLik  + 2 * p                      
    BIC <- - 2 * LogLik + p * log(n)                    
    return(list(LogLik = LogLik, AIC = AIC, BIC = BIC))
  } 
## ***************************************************************************

Try the reliaR package in your browser

Any scripts or data that you put into this service are public.

reliaR documentation built on May 1, 2019, 9:51 p.m.