!--------------------------------------------------------------------------- !--------------------------------------------------------------------------- !--------------------------------------------------------------------------- !+ ! Subroutine WAVE_ANAL (y_in, F1, F2, F3, F4, N_F, N_DATA, COEF_IN, RMS) ! ! Subroutine for anlyzing waves in a given region using a least squares model ! Subroutine is wrapper for NR routine SVDFIT ! ! Output: ! RMS(*) -- real array of variances with ! RMS(N_F+1) = sqrt(chi**2/N_data) !- subroutine wave_anal (y_in, f1, f2, f3, f4, n_f, n_data, coef_in, rms) use cesrv_struct use cesrv_interface use nr, only: svdfit, svdvar implicit none real(rp) y_in(:), rms(:) real(rp) f1(:), f2(:), f3(:), f4(:), coef_in(:) real(rp) f_com(4, 200), y(200), coef(4) real(rp) x(200), sig(200), cvm(200, 200), v(200, 200), w(200) real(rp) chisq integer i, n_data, n_f, n common / wave_anal_com / f_com interface function funcs(x,n) use nrtype implicit none real(dp), intent(in) :: x integer, intent(in) :: n real(dp), dimension(n) :: funcs end function funcs end interface ! if the number of data points is 1 or less than cannot do the analysis if (n_data .le. 1) then do i = 1, n_f coef_in(i) = 0 rms(i) = 0 enddo return endif ! load data into arrays do i = 1, n_data x(i) = i y(i) = y_in(i) f_com(1, i) = f1(i) if (n_f >= 2) f_com(2, i) = f2(i) if (n_f >= 3) f_com(3, i) = f3(i) if (n_f >= 4) f_com(4, i) = f4(i) sig(i) = 1.0 enddo ! call subroutines from Numerical Recipes n = n_data call svdfit (x(1:n), y(1:n), sig(1:n), coef(1:n_f), & v(1:n_f,1:n_f), w(1:n_f), chisq, funcs) call svdvar (v(1:n_f,1:n_f), w(1:n_f), cvm(1:n_f,1:n_f)) ! load coefs and rms's to arrays to be passed back to the calling routine. rms(n_f+1) = sqrt(chisq/n_data) do i = 1, n_f coef_in(i) = coef(i) rms(i) = sqrt(cvm(i, i)) * rms(n_f+1) enddo end subroutine