source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writedynav_loc.f90 @ 5153

Last change on this file since 5153 was 5136, checked in by abarral, 3 months ago

Put comgeom.h, comgeom2.h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.5 KB
RevLine 
[1632]1! $Id: writedynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
[5099]2
[5114]3SUBROUTINE writedynav_loc(time, vcov, ucov, teta, ppk, phi, q, &
4        masse, ps, phis)
[1632]5
[5105]6  ! This routine needs IOIPSL
7  USE ioipsl
8  USE parallel_lmdz
9  USE misc_mod
10  USE infotrac, ONLY: nqtot
[5117]11  USE com_io_dyn_mod, ONLY: histaveid, histvaveid, histuaveid
[5105]12  USE comconst_mod, ONLY: cpp
13  USE temps_mod, ONLY: itau_dyn
[5114]14  USE lmdz_description, ONLY: descript
[5118]15  USE lmdz_iniprint, ONLY: lunout, prt_level
[5136]16  USE lmdz_comgeom
[1632]17
[5113]18  IMPLICIT NONE
[1632]19
[5105]20  !
21  !   Ecriture du fichier histoire au format IOIPSL
22  !
23  !   Appels succesifs des routines: histwrite
24  !
25  !   Entree:
26  !  histid: ID du fichier histoire
27  !  time: temps de l'ecriture
28  !  vcov: vents v covariants
29  !  ucov: vents u covariants
30  !  teta: temperature potentielle
31  !  phi : geopotentiel instantane
32  !  q   : traceurs
33  !  masse: masse
34  !  ps   :pression au sol
35  !  phis : geopotentiel au sol
36  !
37  !
38  !   Sortie:
39  !  fileid: ID du fichier netcdf cree
40  !
41  !   L. Fairhead, LMD, 03/99
42  !
43  ! =====================================================================
44  !
45  !   Declarations
[5134]46  INCLUDE "dimensions.h"
47  INCLUDE "paramet.h"
[1632]48
[5105]49  !
50  !   Arguments
51  !
[1632]52
[5114]53  REAL :: vcov(ijb_v:ije_v, llm), ucov(ijb_u:ije_u, llm)
54  REAL :: teta(ijb_u:ije_u, llm), phi(ijb_u:ije_u, llm)
55  REAL :: ppk(ijb_u:ije_u, llm)
56  REAL :: ps(ijb_u:ije_u), masse(ijb_u:ije_u, llm)
[5105]57  REAL :: phis(ijb_u:ije_u)
[5114]58  REAL :: q(ijb_u:ije_u, llm, nqtot)
[5116]59  INTEGER :: time
[1632]60
[5105]61
62  ! This routine needs IOIPSL
63  !   Variables locales
64  !
[5114]65  INTEGER, SAVE, ALLOCATABLE :: ndex2d(:), ndexu(:), ndexv(:)
[5105]66  INTEGER :: iq, ii, ll
[5114]67  REAL, SAVE, ALLOCATABLE :: tm(:, :)
68  REAL, SAVE, ALLOCATABLE :: vnat(:, :), unat(:, :)
[5117]69  LOGICAL :: ok_sync
[5116]70  INTEGER :: itau_w
71  INTEGER :: ijb, ije, jjn
[5114]72  LOGICAL, SAVE :: first = .TRUE.
73  !$OMP THREADPRIVATE(first)
[1632]74
[5105]75  !
76  !  Initialisations
77  !
[5117]78  IF (adjust) return
[5103]79
[5105]80  IF (first) THEN
[5114]81    !$OMP BARRIER
82    !$OMP MASTER
83    ALLOCATE(unat(ijb_u:ije_u, llm))
84    ALLOCATE(vnat(ijb_v:ije_v, llm))
85    ALLOCATE(tm(ijb_u:ije_u, llm))
86    ALLOCATE(ndex2d(ijnb_u * llm))
87    ALLOCATE(ndexu(ijnb_u * llm))
88    ALLOCATE(ndexv(ijnb_v * llm))
[5105]89    ndex2d = 0
90    ndexu = 0
91    ndexv = 0
[5114]92    !$OMP END MASTER
93    !$OMP BARRIER
94    first = .FALSE.
[5105]95  ENDIF
[5103]96
[5105]97  ok_sync = .TRUE.
98  itau_w = itau_dyn + time
[1632]99
[5105]100  ! Passage aux composantes naturelles du vent
101  CALL covnat_loc(llm, ucov, vcov, unat, vnat)
[1632]102
[5105]103  !
104  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
105  !
106  !  Vents U
107  !
[1632]108
[5114]109  !$OMP BARRIER
110  !$OMP MASTER
111  ijb = ij_begin
112  ije = ij_end
113  jjn = jj_nb
[5103]114
[5114]115  CALL histwrite(histuaveid, 'u', itau_w, unat(ijb:ije, :), &
116          iip1 * jjn * llm, ndexu)
117  !$OMP END MASTER
[1632]118
[5105]119  !
120  !  Vents V
121  !
[5114]122  ije = ij_end
[5117]123  IF (pole_sud) jjn = jj_nb - 1
124  IF (pole_sud) ije = ij_end - iip1
[5114]125  !$OMP BARRIER
126  !$OMP MASTER
127  CALL histwrite(histvaveid, 'v', itau_w, vnat(ijb:ije, :), &
128          iip1 * jjn * llm, ndexv)
129  !$OMP END MASTER
[1632]130
131
[5105]132  !
133  !  Temperature potentielle moyennee
134  !
[5114]135  ijb = ij_begin
136  ije = ij_end
137  jjn = jj_nb
138  !$OMP MASTER
139  CALL histwrite(histaveid, 'theta', itau_w, teta(ijb:ije, :), &
140          iip1 * jjn * llm, ndexu)
141  !$OMP END MASTER
[1632]142
[5105]143  !
144  !  Temperature moyennee
145  !
[1632]146
[5114]147  !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
148  do ll = 1, llm
[5105]149    do ii = ijb, ije
[5114]150      tm(ii, ll) = teta(ii, ll) * ppk(ii, ll) / cpp
[5105]151    enddo
152  enddo
[5114]153  !$OMP ENDDO
[1632]154
[5114]155  !$OMP MASTER
156  CALL histwrite(histaveid, 'temp', itau_w, tm(ijb:ije, :), &
157          iip1 * jjn * llm, ndexu)
158  !$OMP END MASTER
[1632]159
160
[5105]161  !
162  !  Geopotentiel
163  !
[5114]164  !$OMP MASTER
165  CALL histwrite(histaveid, 'phi', itau_w, phi(ijb:ije, :), &
166          iip1 * jjn * llm, ndexu)
167  !$OMP END MASTER
[1632]168
169
[5105]170  !
171  !  Traceurs
172  !
173  !!$OMP MASTER
174  !    DO iq=1,nqtot
175  !      CALL histwrite(histaveid, tracers(iq)%longName, itau_w, &
176  ! .                   q(ijb:ije,:,iq), iip1*jjn*llm, ndexu)
177  !    enddo
178  !!$OMP END MASTER
[1632]179
180
[5105]181  !
182  !  Masse
183  !
[5114]184  !$OMP MASTER
185  CALL histwrite(histaveid, 'masse', itau_w, masse(ijb:ije, :), &
186          iip1 * jjn * llm, ndexu)
187  !$OMP END MASTER
[1632]188
189
[5105]190  !
191  !  Pression au sol
192  !
[5114]193  !$OMP MASTER
[1632]194
[5114]195  CALL histwrite(histaveid, 'ps', itau_w, ps(ijb:ije), &
196          iip1 * jjn, ndex2d)
197  !$OMP END MASTER
[1632]198
[5105]199  !
200  !  Geopotentiel au sol
201  !
[5114]202  !$OMP MASTER
203  ! CALL histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
[5105]204  ! .                 iip1*jjn, ndex2d)
[5114]205  !$OMP END MASTER
[1632]206
[5105]207  !
208  !  Fin
209  !
[5114]210  !$OMP MASTER
[5117]211  IF (ok_sync) THEN
[5114]212    CALL histsync(histaveid)
213    CALL histsync(histvaveid)
214    CALL histsync(histuaveid)
[5105]215  ENDIF
[5114]216  !$OMP END MASTER
[5116]217END SUBROUTINE writedynav_loc
Note: See TracBrowser for help on using the repository browser.