R/fm_tests.R

Defines functions .HStat .ztCV .zaCV Za sw

Documented in sw Za

sw<-function(data,p,v=15,ker_fun="parzen",aband=0,filter=0) {
  # p=order of the time polynomial in the null hypothesis.
  # v=number of auto-covariance terms to compute the spectrum
  #   at frequency zero.


  x=as.matrix(data)
  n=ncol(x)
  if ((p > 5) | (p <= -1)){
    stop("\nError: Number of polynomial order p is out of bound, p must be within (0,5)")

  }

  if ((n > 5) | (n < 1)){
    stop("\nError: Number of regressors n is out of bound, n must be within (1,5)")
  }


  lx=embed(x,2)[,-seq(n)]
  lx  = .detrend(lx,p)
  x   = .detrend(x[-1,],p)
  res     = x - lx%*%(solve(t(lx)%*%lx)%*%t(lx)%*%x)
  lhat    = t(.covarf(res,v,ker_fun,aband,filter=1))
  rstar   = (t(x)%*%lx - (nrow(x)*lhat))%*%solve(t(lx)%*%lx)

  rp=eigen(rstar)$value

  if(is.complex(rp)) {
    rp = -sort(-as.numeric(substr(rp,1,9)))
  } else {
    rp = -sort(-as.numeric(rp))

  }

  i = (n-1)*7 + p + 2

  sw_cv=matrix(c(-13.3203,-7.90074,-5.68767,0.931179, 1.29862, 1.98081,
    -19.8270,-13.7251,-11.0755,-0.862642,-0.164026, 1.08285,
    -28.9388,-21.2162,-17.9117,-3.66203,-2.57101,-0.785605,
    -36.1372,-27.7289,-24.1184,-6.77661,-5.39872,-3.08756,
    -41.7662,-33.3775,-29.2523,-9.59716,-7.88770,-5.18416,
    -48.5009,-39.1753,-34.7293,-12.5981,-10.6578,-7.71254,
    -54.7452,-44.7431,-40.1475,-15.8332,-13.5980,-10.1034,
    -24.1694,-17.4041,-14.0011,-1.34121,-0.675043,0.216183,
    -30.3486,-22.8687,-19.2077,-3.96148,-2.94051,-1.58208,
    -38.5394,-30.3688,-26.5009,-7.70250,-6.39894,-4.50105,
    -46.3520,-36.9254,-32.6648,-11.1637,-9.53160,-7.17430,
    -53.7001,-43.5059,-38.2381,-14.8370,-12.9377,-9.58422,
    -58.4497,-48.4860,-43.5082,-18.3258,-16.0107,-12.5003,
    -64.6997,-54.2080,-49.2730,-21.8619,-19.4758,-15.6027,
    -33.5131,-25.8869,-21.7689,-5.01961,-3.90496,-2.35839,
    -38.7908,-30.8022,-26.9233,-8.08677,-6.73112,-4.83394,
    -46.7257,-38.3314,-34.4585,-12.3999,-10.7383,-8.01409,
    -55.2815,-45.0332,-40.0670,-16.5618,-14.4237,-11.2332,
    -62.3235,-51.4318,-46.6842,-20.7364,-18.4388,-15.0289,
    -68.4246,-56.8563,-52.2014,-24.2596,-21.8186,-18.2722,
    -73.9199,-62.7270,-57.4913,-28.4254,-25.6386,-21.1985,
    -41.9612,-33.7871,-29.5294,-9.06114,-7.60418,-5.52542,
    -48.1227,-38.9531,-34.5175,-12.4327,-10.4811,-8.06809,
    -55.6054,-46.0721,-40.9803,-17.4810,-15.5728,-12.5394,
    -62.4136,-52.5681,-47.7474,-21.8013,-19.5115,-15.5649,
    -70.1908,-58.5536,-53.4159,-25.9875,-23.4269,-19.4836,
    -76.1623,-65.5816,-59.8560,-29.9115,-26.9531,-22.9176,
    -83.6880,-70.9083,-65.3731,-34.8047,-31.5040,-26.8843,
    -50.5217,-41.3236,-36.9087,-13.6822,-11.9771,-9.35654,
    -55.3076,-46.3877,-41.9660,-17.5556,-15.5670,-12.2844,
    -65.7127,-54.1185,-48.7697,-22.0346,-19.7357,-16.0502,
    -72.7761,-60.6057,-55.2194,-27.1912,-24.4528,-20.5812,
    -78.4725,-67.0663,-61.3885,-31.5129,-28.5568,-24.1560,
    -83.7687,-73.1045,-67.1595,-35.8531,-32.7386,-27.7290,
    -89.6184,-78.5531,-71.9555,-39.8177,-36.4714,-31.87066),35,6,byrow = TRUE)

  colnames(sw_cv)=c("1%","5%","10%","90%","95%","99%")

CV=sw_cv[i,]

  return(list(sw_stat=nrow(x)*(rp-1), sw_cv=CV))

}



#==Za test for unit root of a residual from coint regression
CZa <-function (y,x,p=1,v=15) {
  n=ncol(x)
  if (p>5) {stop("\nError: p > 5 is not allowed")}
  if (n<1 | n>5) {stop("\nError: The number of regressors n must be 1<n<5")}

  y = .detrend(y,p=p)
  x = .detrend(x,p=p)
  u = as.matrix(resid(lm(y~x)))


  ZA=Za(u,0,v=v)
  alpha=as.numeric(ZA$alpha)
  za=as.numeric(ZA$za)
  zt=as.numeric(ZA$zt)

  return(list(alpha=alpha,
              cza=za,
              cza_cv=.czaCV(nobs=nrow(u),n,p),
              czt=zt,
              czt_cv=.cztCV(nobs=nrow(u),n,p)))
}

Za<-function(y,p=1,v=15,ker_fun="parzen",aband=0,filter=0) {
  #p=order of the time polynomial in the fitted regression, must be -1,0,1,....
  y=as.matrix(y)

  if (p < -1) {stop("\nError: p < -1 is not allowed.")}

  if (ncol(y) > 1){stop("\nError: ZA cannot handle a data matrix.")}

  y2=embed(y,2)
  lx  = .detrend(y2[,2,drop=F],p)
  x   = .detrend(y2[,1,drop=F],p)
  alpha   =solve(t(lx)%*%lx)%*%t(lx)%*%x
  res     = x - lx%*%alpha
  lhat    = .covarf(res,v,ker_fun,aband,filter)

  tmp     = solve(t(lx)%*%lx)
  nobs    = nrow(res)
  za      = nobs*((((t(x)%*%lx)-(nrow(res)*lhat))%*%tmp)-1)
  var     = ((t(res)%*%res)/nobs) + 2*lhat
  vc      = var%*%tmp
  zt      = (za/nobs)/sqrt(diag(vc))

  return(list(alpha=as.numeric(alpha),
              za=as.numeric(za),
              za_cv=.zaCV(nobs,p),
              zt=as.numeric(zt),
              zt_cv=.ztCV(nobs,p)))

}


.zaCV<-function(n,p) {

  i = round(n/50) + 1
  if ((n %% 50) == 0) {  i = i - 1 }

  if (i > 10) { i = 10}

  if (p > 5) {stop("\nError: p cannot be greater than 5")}
  i = (i-1)*7 + p + 2

  za_cv=matrix(c(-12.7373, -7.56408, -5.49383,  0.961220,   1.3303500,  2.165410,
           -18.5354,-12.92950,-10.43170, -0.720203,  -0.0196524,  1.240320,
           -25.2438,-19.30330,-16.54990, -3.643880,  -2.5655300, -0.627704,
           -30.5744,-24.39910,-21.36110, -6.361920,  -5.0722700, -2.670510,
           -35.0775,-28.70120,-25.35500, -9.040050,  -7.4862800, -4.775960,
           -38.4996,-32.42080,-29.32720,-11.881100, -10.1905000, -7.253620,
           -42.4844,-36.63170,-33.10240,-14.363400, -12.3512000, -9.111360,
           -12.6659, -7.83927, -5.66818,  0.939938,   1.2877700,  2.082020,
           -19.7950,-13.87760,-11.15870, -0.840616,  -0.0840653,  1.186070,
           -27.4162,-20.48430,-17.38810, -3.868380,  -2.6042100, -0.770390,
           -33.9379,-26.01560,-22.54920, -6.529590,  -5.2013900, -3.031720,
           -39.7563,-31.66320,-27.80090, -9.535910,  -7.8289400, -5.238520,
           -43.5637,-35.76820,-32.03460,-12.145200, -10.2447000, -7.271190,
           -48.2433,-40.41640,-36.54210,-15.155100, -12.9602000, -9.758410,
           -13.3651, -7.90243, -5.49412,  0.966783,   1.3365000,  2.079380,
           -19.6059,-13.69200,-10.87210, -0.787890,  -0.0876999,  0.950561,
           -27.6148,-20.83650,-17.61650, -3.836940,  -2.7505600, -0.842735,
           -34.1097,-26.79860,-23.16000, -6.450460,  -5.1004700, -3.111050,
           -40.3925,-32.00600,-28.27850, -9.471100,  -7.7914000, -4.928180,
           -45.0052,-37.22530,-33.21770,-12.282100, -10.5302000, -7.432020,
           -50.7937,-42.05080,-37.54270,-15.323800, -13.2086000, -9.742120,
           -13.3692, -7.89486, -5.71541,  0.948937,   1.3080100,  2.104970,
           -19.9486,-13.99130,-11.15860, -0.787331,  -0.0269699,  1.137410,
           -27.9931,-21.15760,-17.91860, -3.810260,  -2.7187000, -0.837992,
           -35.0490,-27.19400,-23.67090, -6.654870,  -5.2355000, -3.072310,
           -40.3521,-32.48500,-28.57750, -9.518530,  -7.7819400, -5.012510,
           -47.1751,-38.30980,-33.86580,-12.461800, -10.6589000, -7.466500,
           -52.0322,-42.86550,-38.53990,-15.422300, -13.2436000, -9.670280,
           -14.0823, -8.28333, -5.99486,  0.920818,   1.2714000,  2.033400,
           -21.4999,-13.80700,-11.09280, -0.801395,  -0.0878569,  1.036880,
           -28.7263,-21.11960,-17.80700, -3.810680,  -2.6088900, -0.808609,
           -35.5745,-27.30030,-23.55160, -6.603350,  -5.1786000, -2.972270,
           -40.0782,-32.74930,-28.75610, -9.329770,  -7.6812000, -5.077950,
           -47.3737,-38.09540,-33.69890,-12.323400, -10.4146000, -7.426450,
           -53.7801,-43.68990,-38.88260,-15.176600, -13.1545000, -9.671880,
           -13.9719, -8.17224, -5.76096,  0.950562,   1.3158300,  2.114710,
           -20.3875,-13.86830,-11.20520, -0.916779,  -0.2207140,  0.941118,
           -28.9907,-21.64720,-17.94390, -3.697590,  -2.6426800, -0.807373,
           -35.7256,-27.43080,-23.58360, -6.563490,  -5.2432300, -2.977630,
           -41.5248,-32.81460,-28.72710, -9.471330,  -7.8264300, -5.183640,
           -48.3567,-38.54880,-33.96850,-12.428400, -10.4731000, -7.275080,
           -53.1057,-43.76040,-39.21200,-15.419000, -13.3191000, -9.614890,
           -13.5730, -8.06977, -5.65113,  0.961240,   1.2807400,  2.078150,
           -19.9323,-13.81100,-11.12470, -0.845649,  -0.1537010,  1.089490,
           -27.8491,-21.25440,-17.91200, -3.805990,  -2.7328700, -0.935069,
           -35.7010,-26.99990,-23.38520, -6.543370,  -5.1743000, -2.795640,
           -42.0137,-33.27630,-28.93870, -9.560160,  -7.9480800, -5.285030,
           -48.1776,-38.66880,-34.24290,-12.422100, -10.5889000, -7.498720,
           -53.3845,-43.42380,-38.81020,-15.439200, -13.3112000, -9.643370,
           -13.7148, -8.13537, -5.76289,  0.942782,   1.3165900,  2.104580,
           -20.0305,-13.89550,-11.26980, -0.883212,  -0.1676460,  1.097420,
           -28.7399,-21.34320,-17.94440, -3.733980,  -2.6446100, -0.831958,
           -35.5990,-27.53600,-23.79860, -6.539610,  -5.2432800, -2.910020,
           -41.5429,-33.13650,-29.09500, -9.576210,  -7.8973200, -5.065490,
           -47.6170,-38.78650,-34.29400,-12.405000, -10.5413000, -7.667050,
           -52.6490,-43.58220,-39.18470,-15.437400, -13.3723000, -9.786780,
           -13.6941, -7.95984, -5.77783,  0.915282,   1.2613500,  1.996100,
           -19.7027,-14.00460,-11.15910, -0.780447,  -0.0928893,  1.110800,
           -28.4947,-21.10970,-17.79350, -3.819180,  -2.7007500, -0.873863,
           -35.6557,-27.76970,-23.73180, -6.633600,  -5.3319700, -2.786940,
           -41.6673,-33.29610,-28.98350, -9.624710,  -7.9421800, -5.233220,
           -48.2618,-38.75930,-34.28990,-12.589700, -10.6462000, -7.411540,
           -54.1172,-43.86230,-39.26150,-15.616100, -13.3251000, -9.929630,
           -13.3203, -7.90074, -5.68767,  0.931179,   1.2986200,  1.980810,
           -19.8270,-13.72510,-11.07550, -0.862642,  -0.1640260,  1.082850,
           -28.9388,-21.21620,-17.91170, -3.662030,  -2.5710100, -0.785605,
           -36.1372,-27.72890,-24.11840, -6.776610,  -5.3987200, -3.087560,
           -41.7662,-33.37750,-29.25230, -9.597160,  -7.8877000, -5.184160,
           -48.5009,-39.17530,-34.72930,-12.598100, -10.6578000, -7.712540,
           -54.7452,-44.74310,-40.14750,-15.833200, -13.5980000,-10.103400),70,6,byrow=TRUE)
  colnames(za_cv)=c("1%","5%","10%","90%","95%","99%")
  CV=za_cv[i,]
  return(CV)

}



.ztCV<-function(n,p) {

  i = round(n/50) + 1
  if ((n %% 50) == 0) {  i = i - 1 }

  if (i > 10) { i = 10}

  if (p > 5) {stop("\nError: p cannot be greater than 5")}
  i = (i-1)*7 + p + 2

  zt_cv=matrix(c(-2.63467,-1.95254,-1.62044, 0.910216, 1.3050800, 2.080880,
         -3.63993,-2.94935,-2.61560,-0.369306,-0.0116304, 0.666745,
         -4.20045,-3.54490,-3.21450,-1.207730,-0.8962150,-0.237604,
         -4.65813,-3.99463,-3.66223,-1.692140,-1.3903100,-0.819931,
         -5.07175,-4.39197,-4.03090,-2.065030,-1.7832900,-1.218300,
         -5.45384,-4.73277,-4.39304,-2.403330,-2.1543300,-1.623570,
         -5.82090,-5.13053,-4.73415,-2.664660,-2.3986800,-1.881930,
         -2.53279,-1.94976,-1.62656, 0.915249, 1.3167900, 2.117870,
         -3.56634,-2.93701,-2.61518,-0.439283,-0.0498821, 0.694244,
         -4.08920,-3.46145,-3.17093,-1.258390,-0.9195330,-0.298641,
         -4.56873,-3.89966,-3.59161,-1.725430,-1.4451300,-0.894085,
         -4.97062,-4.33552,-4.00795,-2.125190,-1.8578500,-1.305660,
         -5.26901,-4.62509,-4.29928,-2.421130,-2.1500200,-1.658320,
         -5.54856,-4.95553,-4.63476,-2.717630,-2.4650800,-1.994500,
         -2.60249,-1.94232,-1.59497, 0.912961, 1.3070900, 2.023750,
         -3.43911,-2.91515,-2.58414,-0.404598,-0.0481033, 0.538450,
         -4.00519,-3.46110,-3.15517,-1.253320,-0.9580710,-0.320677,
         -4.46919,-3.87624,-3.58887,-1.703540,-1.4403400,-0.920625,
         -4.84725,-4.25239,-3.95439,-2.113820,-1.8549500,-1.264060,
         -5.15555,-4.59557,-4.30149,-2.412710,-2.1937000,-1.704470,
         -5.46544,-4.89343,-4.58188,-2.741510,-2.4972300,-2.023900,
         -2.58559,-1.94477,-1.62458, 0.905676, 1.3037100, 2.018810,
         -3.46419,-2.91242,-2.58837,-0.410558,-0.0141618, 0.665034,
         -4.00090,-3.45423,-3.16252,-1.240400,-0.9376580,-0.304433,
         -4.45303,-3.89216,-3.61209,-1.742460,-1.4828000,-0.906047,
         -4.79484,-4.22115,-3.92941,-2.114340,-1.8363200,-1.302740,
         -5.15005,-4.58359,-4.30336,-2.449720,-2.2131200,-1.683300,
         -5.42757,-4.88604,-4.60358,-2.740440,-2.5020500,-2.040080,
         -2.65229,-1.99090,-1.66577, 0.875165, 1.2706800, 2.044140,
         -3.49260,-2.87595,-2.56885,-0.416310,-0.0488941, 0.611200,
         -3.99417,-3.42290,-3.13981,-1.250960,-0.9509160,-0.310521,
         -4.42462,-3.85645,-3.56568,-1.731080,-1.4587300,-0.934604,
         -4.72243,-4.22262,-3.94435,-2.106600,-1.8423300,-1.267020,
         -5.12654,-4.55072,-4.24765,-2.434560,-2.1888700,-1.730810,
         -5.46995,-4.87930,-4.57608,-2.712260,-2.4836700,-2.005970,
         -2.63492,-1.96775,-1.62969, 0.904516, 1.3137100, 2.032860,
         -3.44558,-2.84182,-2.57313,-0.469204,-0.1283580, 0.553411,
         -3.99140,-3.41543,-3.13588,-1.235850,-0.9445000,-0.311271,
         -4.43404,-3.84922,-3.56413,-1.738540,-1.4858500,-0.896978,
         -4.75946,-4.19562,-3.91052,-2.099970,-1.8603400,-1.329870,
         -5.14042,-4.56772,-4.25699,-2.438820,-2.1892200,-1.673710,
         -5.39389,-4.85343,-4.57927,-2.734970,-2.4992100,-2.002470,
         -2.58970,-1.95674,-1.61786, 0.902516, 1.3221500, 2.053830,
         -3.44036,-2.86974,-2.58294,-0.451590,-0.0789340, 0.631864,
         -3.95420,-3.43052,-3.13924,-1.233280,-0.9389860,-0.375491,
         -4.40180,-3.79982,-3.52726,-1.715980,-1.4458400,-0.885303,
         -4.77897,-4.21672,-3.93324,-2.123090,-1.8843100,-1.339160,
         -5.13508,-4.56464,-4.27617,-2.443580,-2.1882600,-1.727840,
         -5.35071,-4.82097,-4.54914,-2.733770,-2.4887400,-2.014370,
         -2.60653,-1.96391,-1.63477, 0.890881, 1.2929600, 1.971630,
         -3.42692,-2.86280,-2.57220,-0.463397,-0.0922419, 0.613101,
         -3.99299,-3.41999,-3.13524,-1.238570,-0.9299150,-0.337193,
         -4.41297,-3.83582,-3.55450,-1.724080,-1.4491500,-0.872755,
         -4.75811,-4.18759,-3.92599,-2.127990,-1.8846300,-1.371180,
         -5.08726,-4.53617,-4.26643,-2.446940,-2.1910900,-1.723290,
         -5.33780,-4.82542,-4.54802,-2.734600,-2.5072600,-2.029270,
         -2.58687,-1.93939,-1.63192, 0.871242, 1.2661100, 1.966410,
         -3.38577,-2.86443,-2.57318,-0.391939,-0.0498984, 0.659539,
         -3.93785,-3.39130,-3.10317,-1.248360,-0.9563490,-0.334478,
         -4.39967,-3.85724,-3.55951,-1.745780,-1.4637400,-0.870275,
         -4.74764,-4.20488,-3.91350,-2.123840,-1.8820200,-1.368530,
         -5.07739,-4.52487,-4.25185,-2.436740,-2.2228900,-1.729550,
         -5.36172,-4.81947,-4.53837,-2.744480,-2.5136700,-2.030650,
         -2.58364,-1.95730,-1.63110, 0.903082, 1.2861300, 2.006050,
         -3.45830,-2.87104,-2.59369,-0.451613,-0.1060250, 0.536687,
         -3.99783,-3.43182,-3.16171,-1.260320,-0.9563270,-0.305719,
         -4.40298,-3.86066,-3.56940,-1.745880,-1.4842900,-0.914111,
         -4.84459,-4.23012,-3.93845,-2.151350,-1.8987600,-1.396540,
         -5.10571,-4.56846,-4.28913,-2.476370,-2.2251700,-1.795860,
         -5.39872,-4.86396,-4.58525,-2.789710,-2.5618100,-2.140420),70,6,byrow=TRUE)
  colnames(zt_cv)=c("1%","5%","10%","90%","95%","99%")
  CV=zt_cv[i,]
  return(CV)

}


.czaCV<-function (nobs,n,p) {


  cza_cv1=matrix(c(-21.4671,-15.0795,-12.3580, -0.435276,  0.324484,  1.512270,
                   -27.9595,-20.4517,-16.9301, -2.626460, -1.634170,  0.328466,
                   -35.7997,-27.1717,-23.1708, -5.643440, -4.173170, -1.958920,
                   -40.6091,-32.6137,-28.6745, -8.689830, -7.053230, -4.010580,
                   -49.1926,-38.7258,-33.9488,-12.131800,-10.025000, -7.035770,
                   -54.7842,-44.3203,-38.9217,-14.778700,-12.685800, -9.066600,
                   -59.6346,-49.3182,-44.3012,-18.021900,-15.843700,-11.854400,
                   -30.8611,-22.2662,-18.5434, -2.754930, -1.533390,  0.290811,
                   -34.4670,-26.3162,-22.4539, -4.879970, -3.533600, -1.058470,
                   -41.7400,-32.5797,-28.2930, -8.016530, -6.351310, -3.799320,
                   -47.3619,-38.0365,-33.7480,-11.294500, -9.424600, -6.009060,
                   -51.6608,-42.5369,-37.9949,-13.957700,-11.927900, -8.532240,
                   -58.3279,-48.7145,-43.7128,-17.605000,-15.369400,-11.629800,
                   -61.9607,-52.2508,-47.2635,-20.595500,-17.925500,-13.258200,
                   -35.4272,-27.3675,-23.4843, -5.480910, -4.029230, -1.712820,
                   -40.2438,-31.7486,-27.5563, -7.765510, -6.014900, -2.937320,
                   -48.3839,-37.5071,-32.9760,-10.654000, -8.521630, -5.294400,
                   -51.1926,-42.6630,-38.1287,-13.802400,-11.320800, -7.729800,
                   -59.5024,-48.2790,-42.8624,-16.770800,-14.523500,-10.753800,
                   -63.9559,-52.8664,-47.6602,-20.344000,-17.621500,-13.714400,
                   -68.3320,-57.8818,-52.5888,-23.603700,-20.576500,-15.695600,
                   -42.7639,-33.8215,-29.2817, -8.118790, -6.385720, -3.255560,
                   -46.1569,-36.9237,-32.4094,-10.344300, -8.235620, -4.678770,
                   -53.8812,-42.7055,-38.2874,-13.589400,-11.140100, -7.607650,
                   -57.3691,-47.1248,-42.7974,-16.793500,-14.239000,-10.268700,
                   -64.3988,-52.7165,-47.8007,-20.128400,-17.177500,-12.674200,
                   -69.5552,-58.1103,-52.1035,-22.921200,-20.048900,-15.352700,
                   -72.3939,-62.5092,-57.0232,-26.400700,-23.074100,-18.252900,
                   -47.8957,-38.5540,-33.7328,-10.593400, -8.610880, -5.183740,
                   -52.0405,-41.9746,-37.4380,-13.046400,-10.991300, -7.534540,
                   -57.4362,-47.2991,-42.3937,-15.964200,-13.513600, -9.445750,
                   -63.1737,-52.2942,-46.9920,-19.471600,-16.799100,-12.543300,
                   -67.1194,-56.5680,-51.5684,-22.924100,-19.749000,-14.639600,
                   -74.2638,-62.5804,-57.0437,-25.875500,-22.756900,-17.346600,
                   -79.3928,-67.5730,-61.5408,-28.752400,-25.585100,-19.614900),35,6,byrow=TRUE)

  cza_cv2=matrix(c(-22.9188,-15.7706,-12.5481, -0.548982,  0.295732,  1.440300,
                   -26.5556,-20.1830,-16.7501, -2.519110, -1.515320,  0.191855,
                   -35.1197,-27.0749,-23.3370, -5.735100, -4.329040, -2.006560,
                   -41.9204,-32.6661,-28.5846, -8.814800, -7.094170, -4.592260,
                   -48.3478,-38.7616,-34.2542,-11.898000,-10.011300, -6.913390,
                   -52.5567,-43.1768,-38.5840,-15.068500,-12.821200, -9.135630,
                   -59.3727,-49.0396,-43.5940,-18.043200,-15.636100,-11.946700,
                   -29.9396,-21.9595,-18.3809, -2.801580, -1.646300,  0.268450,
                   -34.7599,-26.1676,-22.3849, -4.933640, -3.569400, -1.180880,
                   -40.7391,-32.3049,-27.9239, -8.005880, -6.356480, -3.389630,
                   -47.1627,-37.3766,-32.7183,-11.092600, -9.241420, -6.078100,
                   -53.3108,-42.5974,-38.0402,-14.252500,-11.957800, -8.691890,
                   -57.6851,-47.7086,-42.9647,-17.499600,-15.051000,-11.346700,
                   -64.4858,-53.4701,-48.1205,-20.764000,-18.223300,-14.115600,
                   -35.8116,-27.8176,-23.6242, -5.398380, -3.843290, -1.439640,
                   -40.7124,-32.0367,-27.4329, -7.502890, -5.752550, -2.807330,
                   -45.9483,-37.0641,-32.6862,-10.639400, -8.677680, -5.657880,
                   -52.4024,-42.5639,-37.5381,-13.872200,-11.593500, -7.902960,
                   -57.6021,-47.2047,-42.4496,-16.988700,-14.457700,-10.299800,
                   -63.6043,-52.4479,-47.5632,-20.026700,-17.460500,-13.308800,
                   -69.6351,-57.9399,-52.3485,-23.668600,-20.609800,-15.787900,
                   -42.2399,-33.3270,-28.9168, -7.945340, -6.183200, -3.435270,
                   -45.7984,-36.7277,-32.5747,-10.381900, -8.459570, -5.149170,
                   -52.4921,-42.1115,-37.5244,-13.187800,-10.932700, -7.393700,
                   -57.5111,-47.2835,-42.0975,-16.486600,-14.087400,-10.425200,
                   -62.7764,-52.1772,-47.0647,-19.758000,-16.892800,-12.211200,
                   -67.9295,-57.0921,-51.9770,-22.789900,-19.734900,-14.888500,
                   -74.2355,-62.1294,-56.5681,-26.094500,-23.059400,-18.039500,
                   -47.7363,-38.1529,-33.8043,-10.779900, -8.635160, -5.403910,
                   -52.2272,-42.1237,-37.6132,-13.123400,-10.839600, -7.096560,
                   -57.2914,-47.2188,-42.3110,-15.954800,-13.467100, -9.601970,
                   -62.9673,-51.7677,-46.7206,-19.281700,-16.491500,-11.861200,
                   -68.6468,-56.9128,-51.5857,-22.322800,-19.388300,-14.623100,
                   -72.8272,-61.3012,-56.0305,-25.852600,-22.749800,-17.350000,
                   -77.6934,-66.0426,-60.5481,-28.953600,-25.633300,-20.007900),35,6,byrow=TRUE)

  cza_cv3=matrix(c(-22.3813,-15.4849,-12.4695, -0.558307,   0.220102,  1.443700,
                   -27.3153,-19.5886,-16.6016, -2.587170,  -1.491350,  0.206122,
                   -33.6704,-26.4351,-22.8739, -5.643390,  -4.257680, -1.753470,
                   -41.7185,-32.9010,-28.6665, -8.861330,  -7.189260, -4.504270,
                   -46.7902,-37.6643,-33.3826,-11.838500,  -9.814200, -6.886120,
                   -52.5711,-42.7425,-38.4843,-15.023300, -12.770900, -9.500420,
                   -58.4246,-48.0222,-43.0556,-18.201200, -15.937100,-12.153500,
                   -30.0280,-21.7066,-18.1450, -2.886070,  -1.711980,  0.206875,
                   -33.6676,-25.9025,-22.1912, -5.019700,  -3.551640, -1.089310,
                   -39.7084,-31.6813,-27.4115, -7.988830,  -6.328090, -3.631620,
                   -46.6211,-37.3207,-32.7405,-11.169100,  -9.281480, -5.849230,
                   -52.1981,-42.7974,-38.0418,-14.324300, -12.152400, -8.716170,
                   -57.0630,-47.6883,-42.9236,-17.256800, -15.102200,-11.284400,
                   -62.0737,-52.0128,-47.1553,-20.715700, -18.119700,-14.074100,
                   -35.6430,-27.8195,-23.6376, -5.348680,  -3.912910, -1.504480,
                   -39.3950,-31.0996,-27.0114, -7.359310,  -5.704700, -3.111720,
                   -46.0777,-36.6083,-32.3602,-10.605700,  -8.592380, -5.363540,
                   -51.8316,-41.8956,-37.5345,-13.618500, -11.283400, -7.847300,
                   -56.0726,-47.0288,-41.8627,-16.883000, -14.492700,-10.578000,
                   -62.2422,-52.5135,-47.1509,-20.069800, -17.405500,-12.904100,
                   -67.4764,-56.5852,-51.4893,-23.142600, -20.212300,-16.028500,
                   -42.0547,-32.6722,-28.7365, -8.257050,  -6.470990, -3.591750,
                   -45.6434,-36.5854,-32.2959,-10.096600,  -8.048260, -4.951480,
                   -51.9478,-42.0463,-37.1118,-13.224200, -11.122600, -7.319300,
                   -55.6784,-46.7367,-42.0064,-16.725900, -14.061300, -9.973990,
                   -62.8400,-51.3055,-46.2511,-19.692500, -17.143900,-12.733800,
                   -67.4053,-57.0160,-51.4235,-22.724000, -19.955900,-15.408600,
                   -71.7723,-60.8535,-55.9025,-26.118900, -23.117000,-17.921400,
                   -47.6549,-37.6107,-33.1369,-10.572600,  -8.549980, -5.290340,
                   -51.6149,-41.1989,-36.7877,-13.117000, -10.879600, -7.211170,
                   -56.1660,-46.2705,-41.8297,-16.062200, -13.737200, -9.493930,
                   -61.1654,-51.1310,-46.0271,-19.194900, -16.592800,-12.090500,
                   -67.6881,-56.6089,-51.3427,-22.184700, -19.194100,-14.597900,
                   -71.2216,-61.0072,-55.6162,-25.629700, -22.541500,-17.004400,
                   -77.4278,-65.2785,-59.6897,-28.881900, -25.389400,-20.022000),35,6,byrow=TRUE)

  cza_cv4=matrix(c(-21.8958,-15.3156,-12.3940,  -0.460927,   0.308737,  1.594420,
                   -26.9142,-20.0911,-16.7770,  -2.577280,  -1.539590,  0.182089,
                   -34.5565,-26.2075,-22.5065,  -5.632210,  -4.258390, -2.099050,
                   -40.5353,-31.8194,-27.8596,  -8.706590,  -7.206280, -4.563930,
                   -46.2889,-37.2800,-33.0457, -11.883100, -10.052200, -7.177530,
                   -51.0380,-42.1892,-37.7579, -15.023300, -12.806200, -9.564880,
                   -56.6046,-47.2833,-42.6456, -17.965100, -15.529900,-12.099600,
                   -29.1299,-21.6087,-17.9928,  -2.714440,  -1.596060,  0.247672,
                   -33.0966,-25.0864,-21.4664,  -4.877780,  -3.460740, -1.340830,
                   -39.4106,-31.4881,-27.3006,  -7.854630,  -6.102050, -3.526200,
                   -44.0881,-36.4696,-32.1768, -11.201200,  -9.262790, -6.144640,
                   -50.9749,-42.0841,-37.4623, -14.250500, -11.979700, -8.412200,
                   -56.6213,-46.8568,-41.9155, -17.300300, -14.900100,-11.253200,
                   -60.7782,-51.7033,-46.8274, -20.710100, -18.287200,-14.264100,
                   -35.3726,-27.1370,-23.5479,  -5.177460,  -3.769430, -1.541590,
                   -38.5206,-31.0636,-27.0320,  -7.477610,  -5.935580, -3.162880,
                   -44.1830,-35.7245,-31.5933, -10.419100,  -8.368340, -5.481130,
                   -50.9516,-41.2693,-36.8226, -13.555600, -11.318100, -7.943820,
                   -55.4022,-46.4845,-41.5196, -16.763400, -14.406000,-10.377500,
                   -59.4185,-50.2354,-45.4775, -20.122300, -17.402100,-13.173800,
                   -64.6564,-55.2458,-50.4576, -23.045400, -20.317600,-16.155200,
                   -41.1245,-31.7777,-27.7403,  -7.844470,  -6.083280, -3.230090,
                   -44.6757,-35.4056,-31.3301, -10.098300,  -8.130890, -4.928990,
                   -50.0936,-40.7371,-36.0824, -13.053500, -10.796300, -7.071950,
                   -54.8735,-45.2926,-40.8791, -16.275500, -13.900300, -9.843700,
                   -60.4991,-50.6938,-45.7933, -19.443300, -16.668300,-12.361900,
                   -65.3403,-54.9457,-49.7471, -22.604700, -19.684700,-15.233200,
                   -69.8916,-59.2533,-54.3292, -25.905400, -22.828500,-17.893700,
                   -45.8851,-37.1075,-32.4673, -10.606400,  -8.635590, -5.390080,
                   -49.3034,-40.9522,-36.4291, -12.995300, -10.712500, -7.270990,
                   -54.2729,-44.8254,-40.4288, -15.884300, -13.447700, -9.362610,
                   -60.5904,-50.0341,-45.1484, -18.899300, -15.943200,-11.803600,
                   -64.4973,-53.9015,-49.2666, -21.917000, -19.160600,-14.363100,
                   -69.5759,-59.1348,-53.9680, -25.209600, -22.175200,-16.972300,
                   -72.9500,-63.2358,-58.1154, -28.392700, -25.151300,-20.086200),35,6,byrow=TRUE)

  cza_cv5=matrix(c(-21.1622, -15.0960, -12.1119,  -0.531024,  0.237703,   1.511850,
                   -25.7667, -19.1914, -16.1871,  -2.563240, -1.486990,   0.202784,
                   -32.4541, -25.5105, -22.0564,  -5.713050, -4.396150,  -2.016020,
                   -38.1867, -30.5617, -26.8962,  -8.740710, -7.178020,  -4.597260,
                   -42.7783, -35.0825, -31.3305, -11.627600, -9.976790,  -7.155380,
                   -47.8564, -39.8545, -35.8211, -14.762800,-12.703900,  -9.712580,
                   -52.6929, -43.8877, -39.9161, -17.715100,-15.646200, -12.090700,
                   -28.0512, -20.9592, -17.6168,  -2.794650, -1.665530,   0.192170,
                   -32.0404, -24.5234, -21.1884,  -4.958330, -3.539340,  -1.363110,
                   -37.6801, -29.6520, -25.9967,  -7.752490, -6.212510,  -3.701190,
                   -42.2809, -34.5729, -30.7997, -10.949300, -9.116500,  -6.165310,
                   -47.4805, -39.1569, -35.3499, -14.098900,-11.917600,  -8.615570,
                   -50.8097, -43.4659, -39.1938, -17.034800,-14.794500, -11.264200,
                   -55.8249, -47.5401, -43.3989, -20.063100,-17.700700, -13.670400,
                   -33.9682, -26.0637, -22.7309,  -5.341500, -3.873450,  -1.452700,
                   -36.7304, -29.3862, -25.8572,  -7.347750, -5.669920,  -3.002520,
                   -41.1666, -33.7144, -29.9410, -10.417500, -8.452800,  -5.420070,
                   -46.9132, -38.5770, -34.7333, -13.301100,-11.242700,  -7.735180,
                   -51.4276, -42.8703, -38.8937, -16.580600,-14.178900, -10.459900,
                   -55.3363, -46.9459, -43.0831, -19.535400,-17.110500, -13.193400,
                   -58.9798, -50.5660, -46.8111, -22.623800,-19.996800, -15.841700,
                   -38.0643, -30.4296, -26.7042,  -7.691100, -6.103050,  -3.274240,
                   -41.6270, -33.7741, -29.8894,  -9.967230, -8.043360,  -4.918710,
                   -45.5533, -37.9883, -33.9732, -12.638800,-10.650500,  -7.324200,
                   -50.6468, -42.6005, -38.2657, -15.813100,-13.504900,  -9.895020,
                   -55.8297, -47.1233, -42.4050, -18.945400,-16.368600, -12.448100,
                   -58.2503, -49.9445, -46.0380, -21.750300,-18.989800, -15.107500,
                   -62.8495, -54.0570, -49.6752, -24.850700,-22.153600, -17.446300,
                   -43.6443, -34.8656, -31.0302, -10.382200, -8.243010,  -5.194620,
                   -45.8218, -37.6995, -33.8551, -12.479800,-10.567500,  -7.007290,
                   -50.4771, -42.2573, -38.3627, -15.347500,-13.071400,  -9.323880,
                   -54.5879, -46.0684, -42.3553, -18.152900,-15.546600, -11.927400,
                   -57.8477, -49.6939, -45.5737, -21.301900,-18.848300, -14.437300,
                   -63.0028, -53.8536, -49.3811, -24.093100,-21.161200, -16.676800,
                   -65.1981, -57.3151, -53.1312, -27.230100,-24.374400, -20.152500),35,6,byrow=TRUE)

  colnames(cza_cv1)=colnames(cza_cv2)=colnames(cza_cv3)=colnames(cza_cv4)=colnames(cza_cv5)=c("1%","5%","10%","90%","95%","99%")

  if (p>5) {stop("\nError: p cannot be greater 5")}
  if (n<1 || n>5) {stop("\nError: The number of regressors n must be 1<n<5")}

  if (nobs>=500) {CZA_CV= cza_cv1
  } else if (nobs>=400 & nobs<=499) {CZA_CV= cza_cv2
  } else if (nobs>=300 & nobs<=399) {CZA_CV= cza_cv3
  } else if (nobs>=200 & nobs<=299) {CZA_CV= cza_cv4
  } else if (nobs>=1 & nobs<=199)   {CZA_CV= cza_cv5    }

  m = (n-1)*7 + p + 2

  return(CZA_CV[m,])

}



.cztCV <-function (nobs,n,p) {
  if (p>5) {stop("\nError: p cannot be greater 5")}
  if (n<1 | n>5) {stop("\nError: The number of regressors n must be 1<n<5")}

  czt_cv1=matrix(c(-3.28608,-2.71123,-2.44427,-0.228267,0.196845,1.078450,
                   -3.88031,-3.35851,-3.03798,-1.011440,-0.653342,0.153117 ,
                   -4.36339,-3.84931,-3.52926,-1.590690,-1.276910,-0.688550,
                   -4.69226,-4.16473,-3.91069,-2.034990,-1.751670,-1.169090,
                   -5.12583,-4.55603,-4.24350,-2.430620,-2.159180,-1.632410,
                   -5.45902,-4.85433,-4.54552,-2.689990,-2.450590,-1.962130,
                   -5.68874,-5.13084,-4.85451,-3.012870,-2.774700,-2.347740,
                   -3.95399,-3.33181,-3.01057,-0.964258,-0.632140,0.148153 ,
                   -4.29147,-3.77581,-3.47606,-1.474350,-1.156490,-0.382089,
                   -4.80216,-4.16163,-3.87422,-1.956610,-1.689750,-1.176240,
                   -5.08973,-4.49148,-4.22534,-2.347630,-2.095060,-1.523680,
                   -5.28946,-4.77944,-4.49057,-2.634830,-2.392270,-1.882620,
                   -5.64107,-5.10086,-4.81771,-2.953130,-2.742330,-2.302930,
                   -5.84555,-5.26853,-5.01340,-3.214190,-2.957900,-2.501590,
                   -4.25439,-3.69759,-3.42840,-1.498520,-1.226940,-0.593763,
                   -4.62332,-4.12603,-3.83833,-1.916320,-1.652710,-0.937750,
                   -5.09990,-4.50073,-4.18896,-2.265530,-1.974590,-1.416160,
                   -5.23982,-4.74879,-4.50065,-2.590040,-2.306010,-1.766240,
                   -5.63745,-5.07700,-4.77794,-2.880290,-2.663050,-2.255290,
                   -5.87733,-5.31763,-5.03729,-3.175260,-2.940430,-2.543290,
                   -6.08463,-5.57014,-5.29279,-3.458900,-3.210350,-2.683310,
                   -4.68825,-4.14264,-3.83668,-1.890220,-1.625430,-1.021710,
                   -5.00664,-4.43544,-4.14709,-2.243340,-1.943040,-1.292580,
                   -5.42102,-4.77343,-4.48998,-2.572090,-2.303660,-1.798850,
                   -5.60249,-5.02686,-4.77574,-2.891950,-2.617260,-2.092530,
                   -5.90744,-5.31272,-5.04121,-3.160760,-2.896670,-2.442740,
                   -6.16639,-5.58218,-5.28049,-3.402630,-3.157650,-2.702510,
                   -6.29638,-5.79252,-5.52324,-3.653720,-3.401150,-2.945140,
                   -4.99327,-4.43088,-4.13314,-2.195770,-1.948060,-1.339550,
                   -5.28724,-4.72773,-4.46224,-2.525560,-2.251210,-1.755920,
                   -5.53603,-5.03231,-4.74442,-2.811010,-2.539780,-2.014640,
                   -5.85790,-5.28516,-4.99765,-3.116500,-2.856840,-2.386430,
                   -6.03218,-5.50167,-5.24244,-3.378980,-3.131820,-2.579770,
                   -6.38137,-5.80056,-5.52693,-3.628560,-3.374820,-2.855110,
                   -6.60394,-6.03056,-5.73651,-3.831740,-3.560480,-3.095600),35,6,byrow=TRUE)

  czt_cv2=matrix(c(-3.39320, -2.78062, -2.47410, -0.279165,  0.172570,  1.017570,
                   -3.81898, -3.34274, -3.04197, -0.984635, -0.632195,  0.078616,
                   -4.43824, -3.83476, -3.53856, -1.597690, -1.325380, -0.682733,
                   -4.78731, -4.19879, -3.90468, -2.036200, -1.785190, -1.255400,
                   -5.15859, -4.55815, -4.27559, -2.404020, -2.151480, -1.649910,
                   -5.36666, -4.82211, -4.55480, -2.730390, -2.475860, -1.963420,
                   -5.70533, -5.14149, -4.83768, -2.989680, -2.754670, -2.332440,
                   -3.88099, -3.31554, -3.00918, -1.014000, -0.666507,  0.112207,
                   -4.35920, -3.76677, -3.47891, -1.478870, -1.174610, -0.457611,
                   -4.73655, -4.17175, -3.87843, -1.956220, -1.672730, -1.057520,
                   -5.03407, -4.48465, -4.18736, -2.320470, -2.068440, -1.546200,
                   -5.37301, -4.80609, -4.50790, -2.658160, -2.391000, -1.905160,
                   -5.63842, -5.08273, -4.79419, -2.952110, -2.720470, -2.261140,
                   -5.95823, -5.38482, -5.08735, -3.238620, -2.986610, -2.580600,
                   -4.29209, -3.74752, -3.44785, -1.496640, -1.193630, -0.540536,
                   -4.73620, -4.16373, -3.83159, -1.878260, -1.567860, -0.906299,
                   -4.98331, -4.47817, -4.18238, -2.275440, -1.997330, -1.459560,
                   -5.34322, -4.77455, -4.47877, -2.605810, -2.346690, -1.820750,
                   -5.61331, -5.05800, -4.77543, -2.912280, -2.648290, -2.130150,
                   -5.94606, -5.34094, -5.05669, -3.173140, -2.928330, -2.501310,
                   -6.17994, -5.62560, -5.32022, -3.459190, -3.219280, -2.738380,
                   -4.68326, -4.13893, -3.83504, -1.885940, -1.597830, -1.029000,
                   -5.01959, -4.44111, -4.16075, -2.242250, -1.965500, -1.367530,
                   -5.35312, -4.76318, -4.48253, -2.533500, -2.268620, -1.749660,
                   -5.65846, -5.05443, -4.74318, -2.860210, -2.616330, -2.150960,
                   -5.89297, -5.33097, -5.03686, -3.137800, -2.883990, -2.368950,
                   -6.11791, -5.59035, -5.29834, -3.392830, -3.131940, -2.645580,
                   -6.43463, -5.83831, -5.54375, -3.635260, -3.408220, -2.977310,
                   -4.99049, -4.45174, -4.15603, -2.223880, -1.941070, -1.409330,
                   -5.37057, -4.77929, -4.48921, -2.544310, -2.272970, -1.726750,
                   -5.61805, -5.06136, -4.76461, -2.816510, -2.547850, -2.049560,
                   -5.88425, -5.29788, -5.01558, -3.106980, -2.837810, -2.330350,
                   -6.15156, -5.57259, -5.28198, -3.360620, -3.101400, -2.610650,
                   -6.37314, -5.80031, -5.51577, -3.636860, -3.385050, -2.871760,
                   -6.58251, -6.03057, -5.74573, -3.850370, -3.604850, -3.119320),35,6,byrow=TRUE)

  czt_cv3=matrix(c(-3.36203, -2.77548, -2.46139, -0.286807,  0.132866,  1.034710,
                   -3.90239, -3.32711, -3.03723, -0.996528, -0.605509,  0.118508,
                   -4.32982, -3.81156, -3.51879, -1.594530, -1.290250, -0.576746,
                   -4.81264, -4.24058, -3.93314, -2.052260, -1.797340, -1.238670,
                   -5.09929, -4.53317, -4.26022, -2.390470, -2.150620, -1.661210,
                   -5.40020, -4.84728, -4.56541, -2.720730, -2.482760, -2.012380,
                   -5.72554, -5.14543, -4.85290, -3.036420, -2.797470, -2.388770,
                   -3.93064, -3.31039, -3.00695, -1.025510, -0.692057,  0.104883,
                   -4.30844, -3.76971, -3.48291, -1.498670, -1.182930, -0.449296,
                   -4.69802, -4.16002, -3.85937, -1.951720, -1.669410, -1.078730,
                   -5.09621, -4.51913, -4.22178, -2.320050, -2.069400, -1.524400,
                   -5.39988, -4.84499, -4.54918, -2.662410, -2.408860, -1.945180,
                   -5.67194, -5.12143, -4.83266, -2.957870, -2.715750, -2.267830,
                   -5.90971, -5.38093, -5.10006, -3.245900, -3.009990, -2.555900,
                   -4.32518, -3.77645, -3.46220, -1.487240, -1.199310, -0.531819,
                   -4.66166, -4.12423, -3.82665, -1.859920, -1.567700, -0.952556,
                   -5.06263, -4.47715, -4.19478, -2.272280, -1.989350, -1.408570,
                   -5.39577, -4.79037, -4.51644, -2.601860, -2.320670, -1.824480,
                   -5.62591, -5.09997, -4.78451, -2.895430, -2.661080, -2.162810,
                   -5.96117, -5.38487, -5.08529, -3.191760, -2.956770, -2.457500,
                   -6.18044, -5.61962, -5.32402, -3.444530, -3.186000, -2.750240,
                   -4.69949, -4.11581, -3.84809, -1.916520, -1.630970, -1.063540,
                   -5.02878, -4.48050, -4.18169, -2.200230, -1.921960, -1.371220,
                   -5.37891, -4.82102, -4.49501, -2.551000, -2.294070, -1.763130,
                   -5.59926, -5.07560, -4.78056, -2.890470, -2.618340, -2.113720,
                   -5.97404, -5.35040, -5.03148, -3.158380, -2.916660, -2.445700,
                   -6.20250, -5.64756, -5.33112, -3.402550, -3.168000, -2.737950,
                   -6.40258, -5.84695, -5.58164, -3.678110, -3.427660, -2.973150,
                   -5.02873, -4.44103, -4.15164, -2.197920, -1.941000, -1.394670,
                   -5.36834, -4.76996, -4.46992, -2.536660, -2.272570, -1.733550,
                   -5.59537, -5.05016, -4.78520, -2.830930, -2.572790, -2.075030,
                   -5.85590, -5.33224, -5.03207, -3.114890, -2.860070, -2.365510,
                   -6.20771, -5.62475, -5.32273, -3.364390, -3.108060, -2.638990,
                   -6.38397, -5.87287, -5.56819, -3.633760, -3.379170, -2.872150,
                   -6.69353, -6.08474, -5.78590, -3.872310, -3.610220, -3.149080),35,6,byrow=TRUE)

  czt_cv4=matrix(c(-3.35671,-2.77519,-2.46594,-0.254099, 0.196134, 1.0722200,
                   -3.92428,-3.38037,-3.08215,-1.007590,-0.634217, 0.0945623,
                   -4.48168,-3.83395,-3.54540,-1.602050,-1.318400,-0.7343220,
                   -4.82954,-4.23468,-3.94803,-2.054720,-1.804340,-1.2724500,
                   -5.19748,-4.57984,-4.28594,-2.422190,-2.184830,-1.7307100,
                   -5.48348,-4.89872,-4.60436,-2.754230,-2.519590,-2.0623100,
                   -5.82241,-5.21284,-4.90675,-3.031450,-2.791120,-2.3881800,
                   -3.88242,-3.33232,-3.01999,-0.988265,-0.633419, 0.1213200,
                   -4.36630,-3.76414,-3.46091,-1.486250,-1.150770,-0.4984220,
                   -4.76842,-4.20038,-3.89975,-1.934330,-1.634070,-1.0429000,
                   -5.05007,-4.54203,-4.23534,-2.357210,-2.103300,-1.5796500,
                   -5.46384,-4.89647,-4.60567,-2.666740,-2.412270,-1.9288400,
                   -5.80068,-5.17731,-4.86360,-2.973540,-2.715480,-2.2515200,
                   -6.01552,-5.48792,-5.18651,-3.277320,-3.051930,-2.6231300,
                   -4.37038,-3.77348,-3.48123,-1.464680,-1.197120,-0.5229130,
                   -4.71164,-4.17296,-3.87214,-1.888240,-1.617920,-0.9989730,
                   -5.07287,-4.49791,-4.19539,-2.255370,-1.977750,-1.4207300,
                   -5.43158,-4.85660,-4.55542,-2.595130,-2.344480,-1.8825300,
                   -5.71928,-5.15509,-4.85008,-2.918690,-2.678920,-2.1653700,
                   -5.95901,-5.38920,-5.10190,-3.219210,-2.970880,-2.4910500,
                   -6.24842,-5.69150,-5.39236,-3.478760,-3.228140,-2.8195400,
                   -4.76132,-4.12120,-3.81887,-1.876400,-1.579880,-0.9592470,
                   -5.07595,-4.49599,-4.18062,-2.221810,-1.954290,-1.3281600,
                   -5.41865,-4.82420,-4.51442,-2.545840,-2.288980,-1.7112900,
                   -5.69988,-5.10837,-4.81872,-2.878610,-2.625370,-2.1074500,
                   -6.03815,-5.41121,-5.11067,-3.157260,-2.895720,-2.3923600,
                   -6.31746,-5.67322,-5.35729,-3.424450,-3.182550,-2.7228700,
                   -6.54722,-5.92036,-5.63475,-3.686190,-3.440870,-2.9959000,
                   -5.06954,-4.48980,-4.16461,-2.227700,-1.956820,-1.3968500,
                   -5.35737,-4.81634,-4.52940,-2.544160,-2.263550,-1.7366900,
                   -5.65024,-5.06222,-4.78444,-2.840190,-2.558010,-2.0343800,
                   -6.01717,-5.38593,-5.07183,-3.108540,-2.830150,-2.3831600,
                   -6.22810,-5.62644,-5.32983,-3.379200,-3.110220,-2.5841200,
                   -6.51923,-5.91250,-5.61917,-3.646040,-3.378070,-2.9197900,
                   -6.74433,-6.15641,-5.85483,-3.885590,-3.628840,-3.2279100),35,6,byrow=TRUE)

  czt_cv5=matrix(c(-3.40026, -2.81980, -2.49012, -0.284064,  0.162780,  0.9911820,
                   -4.02456, -3.40397, -3.08903, -0.998765, -0.638257,  0.0929366,
                   -4.50406, -3.91574, -3.60618, -1.646400, -1.341260, -0.6749940,
                   -4.97750, -4.31424, -4.00116, -2.070390, -1.807580, -1.2462200,
                   -5.29795, -4.65255, -4.36236, -2.437560, -2.207440, -1.7438400,
                   -5.69006, -5.02821, -4.70153, -2.785330, -2.550540, -2.1222100,
                   -6.01114, -5.32900, -5.01614, -3.104580, -2.871080, -2.4594400,
                   -4.03875, -3.38465, -3.06445, -1.014520, -0.670171,  0.0830536,
                   -4.49697, -3.83781, -3.52924, -1.506570, -1.181310, -0.4945740,
                   -4.85358, -4.24290, -3.92668, -1.932680, -1.676680, -1.1196900,
                   -5.23415, -4.63779, -4.32076, -2.352030, -2.102990, -1.5823600,
                   -5.60428, -4.99996, -4.67591, -2.715120, -2.456630, -1.9799900,
                   -5.89816, -5.30839, -4.98307, -3.019980, -2.784030, -2.3397100,
                   -6.24667, -5.61312, -5.28841, -3.323730, -3.076810, -2.6524300,
                   -4.50725, -3.84730, -3.53859, -1.501980, -1.210630, -0.4949360,
                   -4.87844, -4.22489, -3.92431, -1.887020, -1.591870, -0.9721720,
                   -5.20113, -4.56724, -4.27167, -2.295340, -2.032260, -1.4347900,
                   -5.61984, -4.95138, -4.63381, -2.620620, -2.349030, -1.8171300,
                   -5.93516, -5.26326, -4.95702, -2.971580, -2.706680, -2.2209400,
                   -6.20848, -5.57967, -5.28403, -3.271150, -3.015210, -2.5836700,
                   -6.52806, -5.84919, -5.55596, -3.541440, -3.307900, -2.8887200,
                   -4.84291, -4.21809, -3.89360, -1.882960, -1.623370, -0.9987490,
                   -5.18976, -4.56495, -4.23781, -2.239730, -1.957450, -1.3628200,
                   -5.49570, -4.91049, -4.57949, -2.548440, -2.300400, -1.8110800,
                   -5.85200, -5.24753, -4.90738, -2.895150, -2.626350, -2.1151300,
                   -6.25788, -5.59734, -5.23154, -3.205430, -2.953040, -2.4987600,
                   -6.42744, -5.80415, -5.49459, -3.468360, -3.204570, -2.7845400,
                   -6.79276, -6.11558, -5.77461, -3.749870, -3.497030, -3.0737800,
                   -5.25985, -4.56675, -4.25742, -2.241590, -1.937600, -1.4005500,
                   -5.53963, -4.88523, -4.55008, -2.531590, -2.265580, -1.7446900,
                   -5.86277, -5.23537, -4.92559, -2.841600, -2.581540, -2.0817100,
                   -6.16676, -5.52360, -5.22425, -3.124550, -2.847850, -2.4124600,
                   -6.43205, -5.80308, -5.46594, -3.424170, -3.199180, -2.6979100,
                   -6.81177, -6.11377, -5.74083, -3.678260, -3.419960, -2.9514500,
                   -6.98960, -6.36882, -6.03754, -3.955730, -3.711920, -3.3076600),35,6,byrow=TRUE)

  colnames(czt_cv1)=colnames(czt_cv2)=colnames(czt_cv3)=colnames(czt_cv4)=colnames(czt_cv5)=c("1%","5%","10%","90%","95%","99%")


  if (nobs>=500) {
    CZT_CV= czt_cv1
  } else if (nobs>=400 & nobs<=499) {CZT_CV= czt_cv2
  } else if (nobs>=300 & nobs<=399) {CZT_CV= czt_cv3
  } else if (nobs>=200 & nobs<=299) {CZT_CV= czt_cv4
  } else if (nobs>=1 & nobs<=199)   {CZT_CV= czt_cv5}

  m = (n-1)*7 + p + 2

  return(CZT_CV[m,])

}



.GStat<-function (y,
                 p=c(-1,0,1)[3],
                 q=5,
                 v=10,#degree of time polynomial
                 ker_fun="parzen",
                 aband=0,
                 filter=0) {
  #Ho: y is I(0)
  # p order of the time polynomial in the null hypothesis
  # q order of the time polynomial in the fitted regression
  # p=-1, type="none"
  # p=0, type="const"
  # p=1, type="trend
  y=as.matrix(y)

  if (p >= q) {stop("\nError: p >= q  is not allowed.")}
  if (p < -1) {stop("\nError: p < -1 is not allowed.")}
  if (q <  0) {stop("\nError: q <  0 is not allowed.")}

  if (ncol(y) > 1) {stop("\nError: GSTAT handles a single time series.")}

  resid0  = .detrend(y,p=1)
  rss0   = t(resid0)%*%resid0
  omga   = .lrvar(resid0,v, ker_fun,aband,filter)
  resid1  = .detrend(y,p=q)
  rss1   = t(resid1)%*%resid1
  stat  = as.numeric((rss0 - rss1)/omga)
  return(list(gstat=stat, p.value=as.numeric(2.134876*dchisq(stat,q-p))))

}



.HStat <- function(y,
                  x,
                  p=1,
                  q,
                  v,
                  type=c("trend","all"),
                  ker_fun="parzen",
                  M=c("CCR","FM"),
                  aband=0,
                  filter=1){
  M=match.arg(M)
  type=match.arg(type)
  #p is the order of time polynomial under the null
  #q is the order of time polynomial of the fitted equation

  if (p >= q) {stop("\nError: p >= q is not allowed.")}

  if (M=="CCR") {
    out= ccrQ(y,x,type=type,q=q,v=v,ker_fun=ker_fun,aband=aband,filter=filter)
  } else {
    out= fmQ(y,x,type=type,q=q,v=v,ker_fun=ker_fun,aband=aband,filter=filter)
  }

  BETA=as.matrix(out$coefTable[,1])

  r = cbind(matrix(rep(0,(q-p)*(nrow(BETA)-(q-p))), q-p,(nrow(BETA)-(q-p))),diag(1,q-p,q-p))

  hstat = t(r %*% BETA)%*%solve(r%*%(out$vcov)%*%t(r)) %*% (r %*% BETA)

  return(list(statistic=as.numeric(hstat),
              p.value=2.134876*as.numeric(dchisq(hstat,q-p))))
}


.JStat<-function (y,
                 p=c(-1,0,1)[3],
                 q=5,
                 v=10,#degree of time polynomial
                 ker_fun="parzen",
                 aband=0,
                 filter=0) {
#Ho: y is I(1)
  # p order of the time polynomial in the null hypothesis
  # q order of the time polynomial in the fitted regression
  # p=-1, type="none"
  # p=0, type="const"
  # p=1, type="trend

  y=as.matrix(y)

  if (p < -1){stop("\nError: p < -1 is not allowed.")  }
  if (p >= q) {stop("\nError: p>=q is not allowed.")}
  if (q < 0) {stop("\nError: q<0 is not allowed.")}

  if ((q-p > 6) ){
    stop("\nError: q-p>6 is not allowed.")
  }

  if (ncol(y) > 1) {stop("\nError: GSTAT handles a single time series.")}

  resid0  = .detrend(y,p=1)
  rss0   = t(resid0)%*%resid0

  resid1  = .detrend(y,p=q)
  rss1   = t(resid1)%*%resid1
  stat  = as.numeric((rss0 - rss1)/rss1)

  return(list(jstat=stat, jstat_cv=.JStatCV(p,q)))

}



.JStatCV <-function (p,q) {

  jstat_cv=matrix(c(1.07180e-03, 0.020517200, 0.07145820,  8.324310,  11.788500,  20.92080,
                  5.19788e-02, 0.270541000, 0.63794900, 28.849200,  39.533800,  78.52090,
                  2.14233e-01, 0.717328000, 1.18753000, 40.592900,  63.828300, 109.55200,
                  4.27201e-01, 1.102570000, 1.84945000, 54.955600,  74.701700, 140.49200,
                  6.43955e-01, 1.669590000, 2.60643000, 64.872700,  97.729300, 173.57400,
                  8.01434e-01, 1.972880000, 3.19687000, 80.631600, 119.679000, 205.70200,
                  1.96702e-04, 0.005144360, 0.02364200,  5.195760,   7.356860,  17.24810,
                  3.05338e-02, 0.136833000, 0.24253200,  8.385260,  12.313900,  22.70070,
                  1.04149e-01, 0.357789000, 0.60588600, 11.660300,  16.907500,  31.52110,
                  2.38625e-01, 0.589331000, 0.88895300, 14.261500,  20.393600,  37.72030,
                  4.19589e-01, 0.853960000, 1.29684000, 17.351500,  24.028000,  41.49410,
                  5.21823e-01, 1.115690000, 1.54805000, 21.595400,  30.050300,  48.89620,
                  8.48213e-05, 0.002203730, 0.00979294,  1.820050,   2.749320,   5.21620,
                  1.00085e-02, 0.065470000, 0.11596700,  2.641900,   3.623610,   6.15172,
                  5.54527e-02, 0.155769000, 0.25979000,  4.105700,   5.407130,   9.23626,
                  1.16631e-01, 0.293655000, 0.45443600,  5.174640,   6.841250,  11.63890,
                  1.95374e-01, 0.416370000, 0.60669800,  6.360580,   8.529720,  13.04460,
                  3.03570e-01, 0.609157000, 0.84863500,  7.290640,   9.880160,  15.81920,
                  3.67725e-05, 0.001615320, 0.00621955,  1.089880,   1.550740,   2.63083,
                  6.43190e-03, 0.034136900, 0.07235440,  1.787210,   2.299980,   3.53964,
                  3.69344e-02, 0.113835000, 0.18984500,  2.704870,   3.482800,   5.76540,
                  7.97553e-02, 0.177960000, 0.30472300,  3.485560,   4.577560,   7.06036,
                  1.52349e-01, 0.297034000, 0.43268900,  3.958690,   4.971440,   8.35702,
                  2.42917e-01, 0.434832000, 0.59794500,  4.574800,   5.739000,   9.39981,
                  3.88274e-05, 0.000898215, 0.00458721,  0.774960,   1.089390,   1.92471,
                  5.48749e-03, 0.027122600, 0.05365020,  1.306710,   1.648860,   2.53443,
                  3.70907e-02, 0.082864300, 0.14288300,  1.884820,   2.470620,   4.25667,
                  6.35456e-02, 0.151567000, 0.23811400,  2.325810,   3.067320,   4.77040,
                  1.10551e-01, 0.223140000, 0.31675200,  2.758910,   3.438420,   5.56500,
                  1.57436e-01, 0.320430000, 0.44975100,  3.230740,   4.060230,   6.76721,
                  1.72993e-05, 0.000836363, 0.00376620,  0.597227,   0.855310,   1.54580,
                  3.51993e-03, 0.020144600, 0.04486950,  1.033410,   1.342600,   2.10498,
                  2.26900e-02, 0.072581300, 0.11851900,  1.477140,   1.935830,   2.95746,
                  4.58234e-02, 0.119785000, 0.18035900,  1.786830,   2.393530,   4.03406,
                  1.05465e-01, 0.200639000, 0.27641100,  2.317180,   2.855180,   4.57054,
                  1.53064e-01, 0.249195000, 0.35246000,  2.632950,   3.343340,   5.00488,
                  2.66160e-05, 0.000900911, 0.00357452,  0.507448,   0.728089,   1.30758,
                  4.52386e-03, 0.015926800, 0.03530070,  0.823350,   1.087000,   1.79438,
                  1.68792e-02, 0.049500300, 0.08530120,  1.158690,   1.535440,   2.48833,
                  4.30411e-02, 0.102228000, 0.15714700,  1.485400,   1.898440,   2.97122,
                  7.53796e-02, 0.168206000, 0.25493800,  1.805060,   2.418700,   3.74138,
                  1.01394e-01, 0.228091000, 0.29815500,  2.169010,   2.669520,   3.92965),42,6)

colnames(jstat_cv)=c("1%","5%","10%","90%","95%","99%")

  if ((p > 5) | (p < -1)){
    stop("\nError: p > 5 or p < -1 is not allowed.")

  }

  if ((q-p > 6) ){
    stop("\nError: q-p>6 is not allowed.")
  }

  m = (p+1)*6 + (q-p)


  return(jstat_cv[m,])

}

Try the COINT package in your browser

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

COINT documentation built on Sept. 9, 2025, 5:51 p.m.