source: LMDZ6/trunk/libf/phylmd/iophys.F90 @ 4283

Last change on this file since 4283 was 4117, checked in by Ehouarn Millour, 2 years ago

Enforce the dynamics/physics separation: use data from modules within phylmd rather than try to get the same from the dynamics.
EM

File size: 7.3 KB
Line 
1!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2! Interface pour ecrire en netcdf avec les routines d'enseignement
3! iotd de Frederic Hourdin
4!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5
6      subroutine iophys_ecrit(nom,lllm,titre,unite,px)
7
8      USE mod_phys_lmdz_para, ONLY: klon_omp, is_mpi_root
9      USE mod_phys_lmdz_transfert_para, ONLY: gather
10      USE mod_grid_phy_lmdz, ONLY: klon_glo, nbp_lon, nbp_lat, grid1dto2d_glo
11      IMPLICIT NONE
12
13
14
15!  Ecriture de variables diagnostiques au choix dans la physique
16!  dans un fichier NetCDF nomme  'diagfi'. Ces variables peuvent etre
17!  3d (ex : temperature), 2d (ex : temperature de surface), ou
18!  0d (pour un scalaire qui ne depend que du temps : ex : la longitude
19!  solaire)
20!  (ou encore 1d, dans le cas de testphys1d, pour sortir une colonne)
21!  La periode d'ecriture est donnee par
22!  "ecritphy " regle dans le fichier de controle de run :  run.def
23!
24!    writediagfi peut etre appele de n'importe quelle subroutine
25!    de la physique, plusieurs fois. L'initialisation et la creation du
26!    fichier se fait au tout premier appel.
27!
28! WARNING : les variables dynamique (u,v,t,q,ps)
29!  sauvees par writediagfi avec une
30! date donnee sont legerement differentes que dans le fichier histoire car
31! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
32! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
33! avant l'ecriture dans diagfi (cf. physiq.F)
34
35! Modifs: Aug.2010 Ehouarn: enforce outputs to be real*4
36!
37!  parametres (input) :
38!  ----------
39!      unit : unite logique du fichier de sortie (toujours la meme)
40!      nom  : nom de la variable a sortir (chaine de caracteres)
41!      titre: titre de la variable (chaine de caracteres)
42!      unite : unite de la variable (chaine de caracteres)
43!      px : variable a sortir (real 0, 1, 2, ou 3d)
44!
45!=================================================================
46
47
48! Arguments on input:
49      integer lllm
50      character (len=*) :: nom,titre,unite
51      integer imjmax
52      parameter (imjmax=100000)
53      real px(klon_omp,lllm)
54      real xglo(klon_glo,lllm)
55      real zx(nbp_lon,nbp_lat,lllm)
56
57
58
59      CALL Gather(px,xglo)
60!$OMP MASTER
61      IF (is_mpi_root) THEN       
62        CALL Grid1Dto2D_glo(xglo,zx)
63        call iotd_ecrit(nom,lllm,titre,unite,zx)
64      ENDIF
65!$OMP END MASTER
66
67      return
68      end
69
70!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
71! Version avec reindexation pour appeler depuis les routines internes
72! à la sous surface
73!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
74
75
76    subroutine iophys_ecrit_index(nom,lllm,titre,unite,knon,knindex,px)
77
78    USE mod_phys_lmdz_para, ONLY: klon_omp
79    USE dimphy, ONLY : klon
80    USE mod_grid_phy_lmdz, ONLY: klon_glo
81    IMPLICIT NONE
82
83! This subroutine returns the sea surface temperature already read from limit.nc
84!
85
86! Arguments on input:
87    INTEGER lllm
88    CHARACTER (len=*) :: nom,titre,unite
89    REAL px(klon_omp,lllm)
90    INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
91    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex  ! grid point number for compressed grid
92    REAL, DIMENSION(klon,lllm) :: varout
93
94    INTEGER :: i,l
95
96    IF (klon/=klon_omp) THEN
97      print*,'klon, klon_omp',klon,klon_omp
98      CALL abort_physic('iophys_ecrit','probleme de dimension parallele',1)
99    ENDIF
100
101    varout(1:klon,1:lllm)=0.
102    DO l = 1, lllm
103    DO i = 1, knon
104       varout(knindex(i),l) = px(i,l)
105    END DO
106    END DO
107    CALL iophys_ecrit(nom,lllm,titre,unite,varout)
108
109  END SUBROUTINE iophys_ecrit_index
110
111!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
112      SUBROUTINE iophys_ini(timestep)
113      USE mod_phys_lmdz_para, ONLY: is_mpi_root
114      USE vertical_layers_mod, ONLY: presnivs
115      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
116      USE dimphy, ONLY: klev
117      USE mod_grid_phy_lmdz, ONLY: klon_glo
118      USE time_phylmdz_mod, ONLY : annee_ref, day_ref, day_ini
119      USE phys_cal_mod, ONLY : calend
120
121      IMPLICIT NONE
122
123      include "YOMCST.h"
124!=======================================================================
125!
126!   Auteur:  L. Fairhead  ,  P. Le Van, Y. Wanherdrick, F. Forget
127!   -------
128!
129!   Objet:
130!   ------
131!
132!   'Initialize' the diagfi.nc file: write down dimensions as well
133!   as time-independent fields (e.g: geopotential, mesh area, ...)
134!
135!=======================================================================
136!-----------------------------------------------------------------------
137!   Declarations:
138!   -------------
139
140real pi
141INTEGER nlat_eff
142INTEGER jour0,mois0,an0
143REAL timestep,t0
144CHARACTER(len=20) :: calendrier
145
146!   Arguments:
147!   ----------
148
149
150!$OMP MASTER
151    IF (is_mpi_root) THEN       
152
153! Bidouille pour gerer le fait que lat_reg contient deux latitudes
154! en version uni-dimensionnelle (chose qui pourrait être résolue
155! par ailleurs)
156IF (klon_glo==1) THEN
157   nlat_eff=1
158ELSE
159   nlat_eff=size(lat_reg)
160ENDIF
161pi=2.*asin(1.)
162
163! print*,'day_ini,annee_ref,day_ref',day_ini,annee_ref,day_ref
164! print*,'jD_ref,jH_ref,start_time, calend',jD_ref,jH_ref,start_time, calend
165
166! Attention : les lignes ci dessous supposent un calendrier en 360 jours
167! Pourrait être retravaillé
168
169jour0=day_ref-30*(day_ref/30)
170mois0=day_ref/30+1
171an0=annee_ref
172t0=(day_ini-1)*RDAY
173calendrier=calend
174
175if ( calendrier == "earth_360d" ) calendrier="360d"
176
177call iotd_ini('phys.nc', &
178size(lon_reg),nlat_eff,klev,lon_reg(:)*180./pi,lat_reg*180./pi,presnivs,jour0,mois0,an0,t0,timestep,calendrier)
179    ENDIF
180!$OMP END MASTER
181
182      END
183
184#ifdef und
185      SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
186      IMPLICIT none
187
188!=======================================================================
189      INTEGER nfield,nlon,iim,jjmp1, jjm
190      REAL fi(nlon,nfield), ecrit(iim*jjmp1,nfield)
191
192      INTEGER i, n, ig
193
194      jjm = jjmp1 - 1
195      DO n = 1, nfield
196         DO i=1,iim
197            ecrit(i,n) = fi(1,n)
198            ecrit(i+jjm*iim,n) = fi(nlon,n)
199         ENDDO
200         DO ig = 1, nlon - 2
201           ecrit(iim+ig,n) = fi(1+ig,n)
202         ENDDO
203      ENDDO
204      RETURN
205      END
206
207#endif
208!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
209! Interface pour ecrire en netcdf avec les routines d'enseignement
210! iotd de Frederic Hourdin
211!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
212
213      SUBROUTINE iotd_ecrit_seq(nom,lllm,titre,unite,px)
214
215      IMPLICIT NONE
216
217! px arrive
218
219#include "iotd.h"
220
221
222! Arguments on input:
223      integer lllm
224      character (len=*) :: nom,titre,unite
225      integer imjmax
226      parameter (imjmax=100000)
227      real px(imjmax*lllm)
228      real, allocatable :: zx(:,:,:)
229      integer i,j,l,ijl
230
231      allocate(zx(imax,jmax,lllm))
232
233      ijl=0
234      do l=1,lllm
235         ! Pole nord
236         ijl=ijl+1
237         do i=1,imax
238            zx(i,1,l)=px(ijl)
239         enddo
240         ! Grille normale
241         do j=2,jmax-1
242            do i=1,imax
243               ijl=ijl+1
244               zx(i,j,l)=px(ijl)
245            enddo
246         enddo
247         ! Pole sud
248         if ( jmax > 1 ) then
249            ijl=ijl+1
250            do i=1,imax
251               zx(i,jmax,l)=px(ijl)
252            enddo
253         endif
254      enddo
255
256      call iotd_ecrit(nom,lllm,titre,unite,zx)
257      deallocate(zx)
258
259      return
260      end
261
Note: See TracBrowser for help on using the repository browser.