| Directory: | ./ |
|---|---|
| File: | phys/moy_undefSTD.f90 |
| Date: | 2022-01-11 19:19:34 |
| Exec | Total | Coverage | |
|---|---|---|---|
| Lines: | 46 | 47 | 97.9% |
| Branches: | 16 | 18 | 88.9% |
| Line | Branch | Exec | Source |
|---|---|---|---|
| 1 | |||
| 2 | ! $Id: moy_undefSTD.F90 3435 2019-01-22 15:21:59Z fairhead $ | ||
| 3 | |||
| 4 | 480 | SUBROUTINE moy_undefstd(itap, itapm1) | |
| 5 | USE netcdf | ||
| 6 | USE dimphy | ||
| 7 | USE phys_state_var_mod | ||
| 8 | |||
| 9 | USE phys_cal_mod, ONLY: mth_len | ||
| 10 | IMPLICIT NONE | ||
| 11 | include "clesphys.h" | ||
| 12 | REAL :: missing_val | ||
| 13 | |||
| 14 | ! ==================================================================== | ||
| 15 | |||
| 16 | ! I. Musat : 09.2004 | ||
| 17 | |||
| 18 | ! Moyenne - a des frequences differentes - des valeurs bien definies | ||
| 19 | ! (.NE.missing_val) des variables interpolees a un niveau de | ||
| 20 | ! pression. | ||
| 21 | ! 1) les variables de type "day" (nout=1) ou "mth" (nout=2) sont sommees | ||
| 22 | ! tous les pas de temps de la physique | ||
| 23 | |||
| 24 | ! 2) les variables de type "NMC" (nout=3) sont calculees a partir | ||
| 25 | ! des valeurs instantannees toutes les 6 heures | ||
| 26 | |||
| 27 | |||
| 28 | ! NB: mettre "inst(X)" dans le write_hist*NMC.h ! | ||
| 29 | ! ==================================================================== | ||
| 30 | |||
| 31 | |||
| 32 | ! variables Input | ||
| 33 | ! INTEGER nlevSTD, klevSTD, itap | ||
| 34 | ! PARAMETER(klevSTD=17) | ||
| 35 | INTEGER itap, itapm1 | ||
| 36 | |||
| 37 | ! variables locales | ||
| 38 | ! INTEGER i, k, nout, n | ||
| 39 | ! PARAMETER(nout=3) !nout=1 day/nout=2 mth/nout=3 NMC | ||
| 40 | INTEGER i, k, n | ||
| 41 | ! REAL dtime, freq_outNMC(nout), freq_moyNMC(nout) | ||
| 42 | ! REAL freq_outNMC(nout), freq_calNMC(nout) | ||
| 43 | REAL freq_moynmc(nout) | ||
| 44 | |||
| 45 | ! variables Output | ||
| 46 | ! REAL tnondef(klon,klevSTD,nout) | ||
| 47 | ! REAL tsumSTD(klon,klevSTD,nout) | ||
| 48 | |||
| 49 | REAL un_jour | ||
| 50 | PARAMETER (un_jour=86400.) | ||
| 51 | ! REAL missing_val | ||
| 52 | |||
| 53 | ! missing_val = nf90_fill_real | ||
| 54 | missing_val=missing_val_nf90 | ||
| 55 | |||
| 56 |
2/2✓ Branch 0 taken 1440 times.
✓ Branch 1 taken 480 times.
|
1920 | DO n = 1, nout |
| 57 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1440 times.
|
1440 | IF (freq_outnmc(n)<0) THEN |
| 58 | ✗ | freq_moynmc(n) = (mth_len*un_jour)/freq_calnmc(n) | |
| 59 | ! print*,'moy_undefSTD n freq_out freq_moy =', | ||
| 60 | ! $n,freq_moyNMC(n) | ||
| 61 | ELSE | ||
| 62 | 1440 | freq_moynmc(n) = freq_outnmc(n)/freq_calnmc(n) | |
| 63 | END IF | ||
| 64 | |||
| 65 | ! calcul 1 fois pas mois, 1 fois par jour ou toutes les 6h | ||
| 66 | |||
| 67 |
7/8✓ Branch 0 taken 480 times.
✓ Branch 1 taken 960 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 480 times.
✓ Branch 4 taken 960 times.
✓ Branch 5 taken 480 times.
✓ Branch 6 taken 45 times.
✓ Branch 7 taken 915 times.
|
1440 | IF (n==1 .AND. itap==itapm1 .OR. n>1 .AND. mod(itap,nint(freq_outnmc(n)/ & |
| 68 | 480 | phys_tstep))==0) THEN | |
| 69 | |||
| 70 | ! print*,'moy_undefSTD n itap itapm1',n,itap,itapm1 | ||
| 71 | |||
| 72 |
2/2✓ Branch 0 taken 45 times.
✓ Branch 1 taken 765 times.
|
810 | DO k = 1, nlevstd |
| 73 |
2/2✓ Branch 0 taken 760410 times.
✓ Branch 1 taken 765 times.
|
762615 | DO i = 1, klon |
| 74 |
2/2✓ Branch 0 taken 726188 times.
✓ Branch 1 taken 34222 times.
|
761175 | IF (tnondef(i,k,n)/=(freq_moynmc(n))) THEN |
| 75 | tsumstd(i, k, n) = tsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k,n & | ||
| 76 | 726188 | )) | |
| 77 | usumstd(i, k, n) = usumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k,n & | ||
| 78 | 726188 | )) | |
| 79 | vsumstd(i, k, n) = vsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k,n & | ||
| 80 | 726188 | )) | |
| 81 | wsumstd(i, k, n) = wsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k,n & | ||
| 82 | 726188 | )) | |
| 83 | phisumstd(i, k, n) = phisumstd(i, k, n)/ & | ||
| 84 | 726188 | (freq_moynmc(n)-tnondef(i,k,n)) | |
| 85 | qsumstd(i, k, n) = qsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k,n & | ||
| 86 | 726188 | )) | |
| 87 | rhsumstd(i, k, n) = rhsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 88 | 726188 | ,n)) | |
| 89 | uvsumstd(i, k, n) = uvsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 90 | 726188 | ,n)) | |
| 91 | vqsumstd(i, k, n) = vqsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 92 | 726188 | ,n)) | |
| 93 | vtsumstd(i, k, n) = vtsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 94 | 726188 | ,n)) | |
| 95 | wqsumstd(i, k, n) = wqsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 96 | 726188 | ,n)) | |
| 97 | vphisumstd(i, k, n) = vphisumstd(i, k, n)/ & | ||
| 98 | 726188 | (freq_moynmc(n)-tnondef(i,k,n)) | |
| 99 | wtsumstd(i, k, n) = wtsumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 100 | 726188 | ,n)) | |
| 101 | u2sumstd(i, k, n) = u2sumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 102 | 726188 | ,n)) | |
| 103 | v2sumstd(i, k, n) = v2sumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 104 | 726188 | ,n)) | |
| 105 | t2sumstd(i, k, n) = t2sumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 106 | 726188 | ,n)) | |
| 107 | o3sumstd(i, k, n) = o3sumstd(i, k, n)/(freq_moynmc(n)-tnondef(i,k & | ||
| 108 | 726188 | ,n)) | |
| 109 | o3daysumstd(i, k, n) = o3daysumstd(i, k, n)/ & | ||
| 110 | 726188 | (freq_moynmc(n)-tnondef(i,k,n)) | |
| 111 | ELSE | ||
| 112 | 34222 | tsumstd(i, k, n) = missing_val | |
| 113 | 34222 | usumstd(i, k, n) = missing_val | |
| 114 | 34222 | vsumstd(i, k, n) = missing_val | |
| 115 | 34222 | wsumstd(i, k, n) = missing_val | |
| 116 | 34222 | phisumstd(i, k, n) = missing_val | |
| 117 | 34222 | qsumstd(i, k, n) = missing_val | |
| 118 | 34222 | rhsumstd(i, k, n) = missing_val | |
| 119 | 34222 | uvsumstd(i, k, n) = missing_val | |
| 120 | 34222 | vqsumstd(i, k, n) = missing_val | |
| 121 | 34222 | vtsumstd(i, k, n) = missing_val | |
| 122 | 34222 | wqsumstd(i, k, n) = missing_val | |
| 123 | 34222 | vphisumstd(i, k, n) = missing_val | |
| 124 | 34222 | wtsumstd(i, k, n) = missing_val | |
| 125 | 34222 | u2sumstd(i, k, n) = missing_val | |
| 126 | 34222 | v2sumstd(i, k, n) = missing_val | |
| 127 | 34222 | t2sumstd(i, k, n) = missing_val | |
| 128 | 34222 | o3sumstd(i, k, n) = missing_val | |
| 129 | 34222 | o3daysumstd(i, k, n) = missing_val | |
| 130 | END IF !tnondef(i,k,n).NE.(freq_moyNMC(n)) | ||
| 131 | END DO !i | ||
| 132 | END DO !k | ||
| 133 | END IF !MOD(itap,NINT(freq_outNMC(n)/phys_tstep)).EQ.0 | ||
| 134 | |||
| 135 | END DO !n | ||
| 136 | |||
| 137 | 480 | RETURN | |
| 138 | END SUBROUTINE moy_undefstd | ||
| 139 |