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

Last change on this file since 5214 was 5195, checked in by abarral, 7 days ago

Correct r5192, some lmdz_description cases were missing

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