cdfmoy.f90 7.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197
  1. PROGRAM cdfmoy
  2. !!-----------------------------------------------------------------------
  3. !! *** PROGRAM cdfmoy ***
  4. !!
  5. !! ** Purpose: Compute mean values for all the variables in a bunch
  6. !! of cdf files given as argument
  7. !! Store the results on a 'similar' cdf file.
  8. !!
  9. !! ** Method: Try to avoid 3 d arrays
  10. !!
  11. !! history :
  12. !! Original code : J.M. Molines (Nov 2004 ) for ORCA025
  13. !! J.M. Molines (Apr 2005 ) put all NCF stuff in module
  14. !! now valid for grid T U V W icemod
  15. !! Modified : P. Mathiot (June 2007) update for forcing fields
  16. !!-----------------------------------------------------------------------
  17. !! $Rev: 321 $
  18. !! $Date: 2010-05-20 06:46:20 +0200 (Thu, 20 May 2010) $
  19. !! $Id: cdfmoy.f90 321 2010-05-20 04:46:20Z molines $
  20. !!--------------------------------------------------------------
  21. !!
  22. USE cdfio
  23. IMPLICIT NONE
  24. INTEGER :: jk,jt,jvar, jv , jtt,jkk !: dummy loop index
  25. INTEGER :: ierr !: working integer
  26. INTEGER :: narg, iargc !:
  27. INTEGER :: npiglo,npjglo, npk ,nt !: size of the domain
  28. INTEGER :: nvars !: Number of variables in a file
  29. INTEGER :: ntframe !: Cumul of time frame
  30. INTEGER , DIMENSION(:), ALLOCATABLE :: id_var , & !: arrays of var id's
  31. & ipk , & !: arrays of vertical level for each var
  32. & id_varout,&
  33. & id_varout2
  34. REAL(KIND=8) , DIMENSION (:,:), ALLOCATABLE :: tab, tab2 !: Arrays for cumulated values
  35. REAL(KIND=8) :: total_time
  36. REAL(KIND=4) , DIMENSION (:,:), ALLOCATABLE :: v2d ,& !: Array to read a layer of data
  37. & rmean, rmean2
  38. REAL(KIND=4),DIMENSION(1) :: timean
  39. REAL(KIND=4),DIMENSION(365) :: tim
  40. CHARACTER(LEN=256) :: cfile ,cfileout, cfileout2 !: file name
  41. CHARACTER(LEN=256) :: cdep
  42. CHARACTER(LEN=256) ,DIMENSION(:), ALLOCATABLE:: cvarname !: array of var name
  43. CHARACTER(LEN=256) ,DIMENSION(:), ALLOCATABLE:: cvarname2 !: array of var22 name for output
  44. TYPE (variable), DIMENSION(:), ALLOCATABLE :: typvar, typvar2
  45. INTEGER :: ncout, ncout2
  46. INTEGER :: istatus
  47. LOGICAL :: lcaltmean
  48. !!
  49. !! Read command line
  50. narg= iargc()
  51. IF ( narg == 0 ) THEN
  52. PRINT *,' Usage : cdfmoy ''list_of_ioipsl_model_output_files'' '
  53. STOP
  54. ENDIF
  55. !!
  56. !! Initialisation from 1st file (all file are assume to have the same geometry)
  57. CALL getarg (1, cfile)
  58. npiglo= getdim (cfile,'x')
  59. npjglo= getdim (cfile,'y')
  60. npk = getdim (cfile,'depth',cdtrue=cdep, kstatus=istatus)
  61. IF (istatus /= 0 ) THEN
  62. npk = getdim (cfile,'z',cdtrue=cdep,kstatus=istatus)
  63. IF (istatus /= 0 ) THEN
  64. npk = getdim (cfile,'sigma',cdtrue=cdep,kstatus=istatus)
  65. IF ( istatus /= 0 ) THEN
  66. npk = getdim (cfile,'nav_lev',cdtrue=cdep,kstatus=istatus)
  67. IF ( istatus /= 0 ) THEN
  68. npk = getdim (cfile,'levels',cdtrue=cdep,kstatus=istatus)
  69. IF ( istatus /= 0 ) THEN
  70. PRINT *,' assume file with no depth'
  71. npk=0
  72. ENDIF
  73. ENDIF
  74. ENDIF
  75. ENDIF
  76. ENDIF
  77. PRINT *, 'npiglo=', npiglo
  78. PRINT *, 'npjglo=', npjglo
  79. PRINT *, 'npk =', npk
  80. ALLOCATE( tab(npiglo,npjglo), tab2(npiglo,npjglo), v2d(npiglo,npjglo) )
  81. ALLOCATE( rmean(npiglo,npjglo), rmean2(npiglo,npjglo) )
  82. nvars = getnvar(cfile)
  83. PRINT *,' nvars =', nvars
  84. ALLOCATE (cvarname(nvars), cvarname2(nvars) )
  85. ALLOCATE (typvar(nvars), typvar2(nvars) )
  86. ALLOCATE (id_var(nvars),ipk(nvars),id_varout(nvars), id_varout2(nvars) )
  87. ! get list of variable names and collect attributes in typvar (optional)
  88. cvarname(:)=getvarname(cfile,nvars,typvar)
  89. DO jvar = 1, nvars
  90. ! variables that will not be computed or stored are named 'none'
  91. IF (cvarname(jvar) /= 'vozocrtx' .AND. &
  92. cvarname(jvar) /= 'vomecrty' .AND. &
  93. cvarname(jvar) /= 'vovecrtz' .AND. &
  94. cvarname(jvar) /= 'sossheig' ) THEN
  95. cvarname2(jvar) ='none'
  96. ELSE
  97. cvarname2(jvar)=TRIM(cvarname(jvar))//'_sqd'
  98. typvar2(jvar)%name = TRIM(typvar(jvar)%name)//'_sqd' ! name
  99. typvar2(jvar)%units = '('//TRIM(typvar(jvar)%units)//')^2' ! unit
  100. typvar2(jvar)%missing_value = typvar(jvar)%missing_value ! missing_value
  101. typvar2(jvar)%valid_min = 0. ! valid_min = zero
  102. typvar2(jvar)%valid_max = typvar(jvar)%valid_max**2 ! valid_max *valid_max
  103. typvar2(jvar)%scale_factor= 1.
  104. typvar2(jvar)%add_offset= 0.
  105. typvar2(jvar)%savelog10= 0.
  106. typvar2(jvar)%long_name =TRIM(typvar(jvar)%long_name)//'_Squared' !
  107. typvar2(jvar)%short_name = TRIM(typvar(jvar)%short_name)//'_sqd' !
  108. typvar2(jvar)%online_operation = TRIM(typvar(jvar)%online_operation)
  109. typvar2(jvar)%axis = TRIM(typvar(jvar)%axis)
  110. END IF
  111. END DO
  112. id_var(:) = (/(jv, jv=1,nvars)/)
  113. ! ipk gives the number of level or 0 if not a T[Z]YX variable
  114. ipk(:) = getipk (cfile,nvars,cdep=cdep)
  115. WHERE( ipk == 0 ) cvarname='none'
  116. typvar(:)%name=cvarname
  117. typvar2(:)%name=cvarname2
  118. ! create output fileset
  119. cfileout='cdfmoy.nc'
  120. cfileout2='cdfmoy2.nc'
  121. ! create output file taking the sizes in cfile
  122. ncout =create(cfileout, cfile,npiglo,npjglo,npk,cdep=cdep)
  123. ncout2=create(cfileout2,cfile,npiglo,npjglo,npk,cdep=cdep)
  124. ierr= createvar(ncout , typvar, nvars, ipk, id_varout )
  125. ierr= createvar(ncout2, typvar2, nvars, ipk, id_varout2)
  126. ierr= putheadervar(ncout , cfile, npiglo, npjglo, npk,cdep=cdep)
  127. ierr= putheadervar(ncout2, cfile, npiglo, npjglo, npk,cdep=cdep)
  128. lcaltmean=.TRUE.
  129. DO jvar = 1,nvars
  130. IF (cvarname(jvar) == 'nav_lon' .OR. &
  131. cvarname(jvar) == 'nav_lat' ) THEN
  132. ! skip these variable
  133. ELSE
  134. PRINT *,' Working with ', TRIM(cvarname(jvar)), ipk(jvar)
  135. DO jk = 1, ipk(jvar)
  136. PRINT *,'level ',jk
  137. tab(:,:) = 0.d0 ; tab2(:,:) = 0.d0 ; total_time = 0.; ntframe=0
  138. DO jt = 1, narg
  139. CALL getarg (jt, cfile)
  140. nt = getdim (cfile,'time_counter')
  141. IF ( lcaltmean ) THEN
  142. tim=getvar1d(cfile,'time_counter',nt)
  143. total_time = total_time + SUM(tim(1:nt) )
  144. END IF
  145. DO jtt=1,nt
  146. ntframe=ntframe+1
  147. jkk=jk
  148. ! If forcing fields is without depth dimension
  149. IF (npk==0) jkk=jtt
  150. v2d(:,:)= getvar(cfile, cvarname(jvar), jkk ,npiglo, npjglo,ktime=jtt )
  151. tab(:,:) = tab(:,:) + v2d(:,:)
  152. IF (cvarname2(jvar) /= 'none' ) tab2(:,:) = tab2(:,:) + v2d(:,:)*v2d(:,:)
  153. ENDDO
  154. END DO
  155. ! finish with level jk ; compute mean (assume spval is 0 )
  156. rmean(:,:) = tab(:,:)/ntframe
  157. IF (cvarname2(jvar) /= 'none' ) rmean2(:,:) = tab2(:,:)/ntframe
  158. ! store variable on outputfile
  159. ierr = putvar(ncout, id_varout(jvar) ,rmean, jk, npiglo, npjglo, kwght=ntframe)
  160. IF (cvarname2(jvar) /= 'none' ) ierr = putvar(ncout2,id_varout2(jvar),rmean2, jk,npiglo, npjglo, kwght=ntframe)
  161. IF (lcaltmean ) THEN
  162. timean(1)= total_time/ntframe
  163. ierr=putvar1d(ncout,timean,1,'T')
  164. ierr=putvar1d(ncout2,timean,1,'T')
  165. END IF
  166. lcaltmean=.FALSE. ! tmean already computed
  167. END DO ! loop to next level
  168. END IF
  169. END DO ! loop to next var in file
  170. istatus = closeout(ncout)
  171. istatus = closeout(ncout2)
  172. END PROGRAM cdfmoy