source: LMDZ6/trunk/libf/dyn3dmem/writedynav_loc.F90 @ 5248

Last change on this file since 5248 was 5246, checked in by abarral, 23 hours ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • 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!
2! $Id: writedynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
3!
[5246]4subroutine writedynav_loc( time, vcov, ucov,teta,ppk,phi,q, &
5        masse,ps,phis)
[1632]6
7#ifdef CPP_IOIPSL
[5246]8  ! This routine needs IOIPSL
9  USE ioipsl
[1632]10#endif
[5246]11  USE parallel_lmdz
12  USE misc_mod
13  USE infotrac, ONLY : nqtot
14  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid
15  USE comconst_mod, ONLY: cpp
16  USE temps_mod, ONLY: itau_dyn
[1632]17
[5246]18  implicit none
[1632]19
[5246]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
46  include "dimensions.h"
47  include "paramet.h"
48  include "comgeom.h"
49  include "description.h"
50  include "iniprint.h"
[1632]51
[5246]52  !
53  !   Arguments
54  !
[1632]55
[5246]56  REAL :: vcov(ijb_v:ije_v,llm),ucov(ijb_u:ije_u,llm)
57  REAL :: teta(ijb_u:ije_u,llm),phi(ijb_u:ije_u,llm)
58  REAL :: ppk(ijb_u:ije_u,llm)
59  REAL :: ps(ijb_u:ije_u),masse(ijb_u:ije_u,llm)
60  REAL :: phis(ijb_u:ije_u)
61  REAL :: q(ijb_u:ije_u,llm,nqtot)
62  integer :: time
[1632]63
[5246]64
[1632]65#ifdef CPP_IOIPSL
[5246]66  ! This routine needs IOIPSL
67  !   Variables locales
68  !
69  INTEGER,SAVE,ALLOCATABLE :: ndex2d(:),ndexu(:),ndexv(:)
70  INTEGER :: iq, ii, ll
71  REAL,SAVE,ALLOCATABLE :: tm(:,:)
72  REAL,SAVE,ALLOCATABLE :: vnat(:,:),unat(:,:)
73  logical :: ok_sync
74  integer :: itau_w
75  integer :: ijb,ije,jjn
76  LOGICAL,SAVE :: first=.TRUE.
[1632]77!$OMP THREADPRIVATE(first)
78
[5246]79  !
80  !  Initialisations
81  !
82  if (adjust) return
83
84  IF (first) THEN
[1632]85!$OMP BARRIER
86!$OMP MASTER
[5246]87    ALLOCATE(unat(ijb_u:ije_u,llm))
88    ALLOCATE(vnat(ijb_v:ije_v,llm))
89    ALLOCATE(tm(ijb_u:ije_u,llm))
90    ALLOCATE(ndex2d(ijnb_u*llm))
91    ALLOCATE(ndexu(ijnb_u*llm))
92    ALLOCATE(ndexv(ijnb_v*llm))
93    ndex2d = 0
94    ndexu = 0
95    ndexv = 0
[1632]96!$OMP END MASTER
97!$OMP BARRIER
[5246]98    first=.FALSE.
99  ENDIF
[1632]100
[5246]101  ok_sync = .TRUE.
102  itau_w = itau_dyn + time
[1632]103
[5246]104  ! Passage aux composantes naturelles du vent
105  call covnat_loc(llm, ucov, vcov, unat, vnat)
[1632]106
[5246]107  !
108  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
109  !
110  !  Vents U
111  !
112
113!$OMP BARRIER
[1632]114!$OMP MASTER
[5246]115  ijb=ij_begin
116  ije=ij_end
117  jjn=jj_nb
[1632]118
[5246]119  call histwrite(histuaveid, 'u', itau_w, unat(ijb:ije,:), &
120        iip1*jjn*llm, ndexu)
121!$OMP END MASTER
122
123  !
124  !  Vents V
125  !
126  ije=ij_end
127  if (pole_sud) jjn=jj_nb-1
128  if (pole_sud) ije=ij_end-iip1
[1632]129!$OMP BARRIER
[5246]130!$OMP MASTER
131  call histwrite(histvaveid, 'v', itau_w, vnat(ijb:ije,:), &
132        iip1*jjn*llm, ndexv)
133!$OMP END MASTER
[1632]134
135
[5246]136  !
137  !  Temperature potentielle moyennee
138  !
139  ijb=ij_begin
140  ije=ij_end
141  jjn=jj_nb
142!$OMP MASTER
143  call histwrite(histaveid, 'theta', itau_w, teta(ijb:ije,:), &
144        iip1*jjn*llm, ndexu)
145!$OMP END MASTER
[1632]146
[5246]147  !
148  !  Temperature moyennee
149  !
[1632]150
[5246]151!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
152  do ll=1,llm
153    do ii = ijb, ije
154      tm(ii,ll) = teta(ii,ll) * ppk(ii,ll)/cpp
155    enddo
156  enddo
[1632]157!$OMP ENDDO
158
[5246]159!$OMP MASTER
160  call histwrite(histaveid, 'temp', itau_w, tm(ijb:ije,:), &
161        iip1*jjn*llm, ndexu)
[1632]162!$OMP END MASTER
163
164
[5246]165  !
166  !  Geopotentiel
167  !
168!$OMP MASTER
169  call histwrite(histaveid, 'phi', itau_w, phi(ijb:ije,:), &
170        iip1*jjn*llm, ndexu)
[1632]171!$OMP END MASTER
172
173
[5246]174  !
175  !  Traceurs
176  !
177  !!$OMP MASTER
178  !    DO iq=1,nqtot
179  !      call histwrite(histaveid, tracers(iq)%longName, itau_w, &
180  ! .                   q(ijb:ije,:,iq), iip1*jjn*llm, ndexu)
181  !    enddo
182  !!$OMP END MASTER
[1632]183
184
[5246]185  !
186  !  Masse
187  !
188!$OMP MASTER
189   call histwrite(histaveid, 'masse', itau_w, masse(ijb:ije,:), &
190         iip1*jjn*llm, ndexu)
[1632]191!$OMP END MASTER
192
193
[5246]194  !
195  !  Pression au sol
196  !
197!$OMP MASTER
[1632]198
[5246]199   call histwrite(histaveid, 'ps', itau_w, ps(ijb:ije), &
200         iip1*jjn, ndex2d)
[1632]201!$OMP END MASTER
202
[5246]203  !
204  !  Geopotentiel au sol
205  !
206!$OMP MASTER
207    ! call histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
208  ! .                 iip1*jjn, ndex2d)
[1632]209!$OMP END MASTER
210
[5246]211  !
212  !  Fin
213  !
214!$OMP MASTER
215  if (ok_sync) then
216      call histsync(histaveid)
217      call histsync(histvaveid)
218      call histsync(histuaveid)
219  ENDIF
[1632]220!$OMP END MASTER
221#else
[5246]222  write(lunout,*)'writedynav_loc: Needs IOIPSL to function'
[1632]223#endif
[5246]224  ! #endif of #ifdef CPP_IOIPSL
225end subroutine writedynav_loc
Note: See TracBrowser for help on using the repository browser.