source: LMDZ5/branches/IPSLCM5A2.1_ISO/libf/phyiso/rrtm/yomct0.F90 @ 3331

Last change on this file since 3331 was 3331, checked in by acozic, 6 years ago

Add modification for isotopes

  • Property svn:executable set to *
File size: 20.2 KB
Line 
1MODULE YOMCT0
2
3USE PARKIND1  ,ONLY : JPIM     ,JPRB
4
5IMPLICIT NONE
6
7SAVE
8
9!     ------------------------------------------------------------------
10
11!*    Control variables for the job - constant within job
12
13!========== TECHNICAL SWITCHES ================================================
14
15! ----- configuration:
16! NCONF      : configuration of the job
17
18!                0- 99 : 3-D integration job
19!              100-199 : variational job
20!              200-299 : 2-D integration job
21!              300-349 : KALMAN filter                    (currently obsolete)
22!              350-399 : predictability model             (currently obsolete)
23!              400-499 : test of the adjoint
24!              500-599 : test of the tangent linear model
25!              600-699 : eigenvalue/vector solvers
26!              700-799 : optimal interpolation
27!              800-899 : sensitivity
28!              900-999 : miscellaneous other configurations.
29
30!                    1 : 3-D primitive equation model
31
32!                  131 : incremental 4-D VAR/3-D VAR
33
34!                  201 : shallow-water model
35!                  202 : vorticity equation model
36
37!                  401 : test of adjoint with 3-D P.E. model
38!                  421 : test of adjoint with shallow-water model
39!                  422 : test of adjoint with vorticity equation model
40
41!                  501 : test of tangent linear with 3-D P.E. model
42!                  521 : test of tangent linear with shallow-water model
43!                  522 : test of tangent linear with vorticity equation model
44
45!                  601 : eigenvalue/vector solver for 3-D P.E. model
46
47!                  701 : optimal interpolation with CANARI
48
49!                  801 : sensitivity with 3-D P.E. model
50
51!                  901 : set up initial conditions (CPREP1)
52!                  903 : set up initial conditions (CPREP5)
53!                  911 : computes dilatation matrices for spectral space
54!                  912 : computes rotation matrices for spectral space
55!                  923 : initialisation of climatologic files
56!                  931 : creation of an ARPEGE file containing the NESDIS SST (INCLITC).
57!                  932 : interpolates the sea-ice concentration field from
58!                        satellite data to the ARPEGE grid (CSEAICE).
59!                  940 : corrects the dry surface pressure in an ARPEGE file
60!                        to keep total mass constant compared to a reference
61!                        ARPEGE file (CORMASS)
62!                  951 : difference between 2 model states (CPREP2)
63
64! ----- ???:
65! NTASKS     : ??? (no comment provided, currently used in CANARI only).
66
67! ----- variables linked with diagnostics and outputs:
68! LALLOPR    : .T. = print information about all allocations/deallocations
69! NPRINTLEV  : 0 = "basic prints'; 1 = "more prints"; 2 = "debug prints"
70
71! ----- type of file used:
72! LFDBOP     : .T. = fields data base utilized
73! LGRBOP     : .T. = output in GRIB (not ARPEGE)
74! LFBDAP     : .T. = diagnostics written on trajectory files
75! LARPEGEF   : .T. = use ARPEGE files
76! LARPEGEF_TRAJHR   : .T. = use ARPEGE files for high resolution trajectory
77! LARPEGEF_TRAJBG   : .T. = use ARPEGE files for background
78! LARPEGEF_RDGP_INIT     : .T. = use grid-point ARPEGE files
79! LARPEGEF_RDGP_TRAJHR   : .T. = use grid-point ARPEGE files for HR trajectory
80! LARPEGEF_RDGP_TRAJBG   : .T. = use grid-point ARPEGE files for background
81! CNDISPP    : directory of display files
82
83! ----- variables linked to post-processing:
84! LFPOS      : .T. = use of Full-POS rather than POS
85! CFPNCF     : name of Full-POS control file (pseudo-configuration 927)
86! LFPART2    : .T. = second part of interpolations for changing geometry
87!              (pseudo-configuration 927)
88! CFDIRLST   : path of postprocessing listing file
89! CNPPATH    : directory of postprocessing namelist files
90
91! ----- use of transmission coefficients stored in Fourier or spectral space:
92! LRETCFOU   : .T. = reading Fourier transmission coefficients on file
93!              for simplified physics.
94! LWRTCFOU   : .T. = writing Fourier transmission coefficients on file.
95! LRFOUTCNORM: activates diagnostics on Fourier transmission coefficients.
96!              - LRFOUTCNORM(1)=.T.: global statistics.
97!              - LRFOUTCNORM(2)=.T.: statistics per latitude.
98!              - LRFOUTCNORM(3)=.T.: statistics per layer.
99!              - LRFOUTCNORM(4)=.T.: statistics per wavenumber.
100! LRGPTCNORM : activates diagnostics on grid-point transmission coefficients.
101!              - LRGPTCNORM(1)=.T.: global statistics.
102!              - LRGPTCNORM(2)=.T.: statistics per latitude.
103!              - LRGPTCNORM(3)=.T.: statistics per layer.
104
105! ----- other variables:
106! LNF        : .T. = start, .F. = restart
107! LSMSSIG    : .T. = send signals to SMS (ECMWF supervisor)
108! LOPDIS     : .T. = calls OPDIS
109! NCYCLE     : cycle identifier
110! CNMEXP     : name of the experiment
111!              An experiment is identified by its name (16 characters)
112!              and its cycle (typically same experiment but without a bug)
113! CFCLASS    : class for use by FDB
114! CTYPE      : type for use by FDB
115! LBACKG     : ???
116! LMINIM     : ???
117
118!========== MODEL SWITCHES ====================================================
119! Remark: this section containes some dynamical variables which cannot be
120!         put in NAMDYN because they are used in routines called before SUDYN
121!         and sometimes to allocate some arrays.
122
123! ----- advection scheme, semi-Lagrangian scheme:
124! LSLAG     : .TRUE. = semi-lagrangian on
125! LTWOTL    : .TRUE. if two-time-level semi-Lagrangian scheme will be used
126! LRFRIC    : .TRUE. = Rayleigh friction in zonal wind (for p < 9.9hPa)
127! LVERCOR   : .T./.F.: thin layer hypothesis relaxed/applied.
128
129! ----- vertical discretisation, vertical boundaries:
130! LAPRXPK   : way of computing full-levels pressures in primitive equation
131!             hydrostatic model.
132!             .T.: full levels are computed by PK=(PK+1/2 + PK-1/2)*0.5
133!             .F.: full levels are computed by a more complicated formula
134!                  consistent with "alpha" in geopotential formula.
135! LREGETA   : .T.: for the interlayer L, ETA(L)=L/NFLEVG
136!             .F.: for the interlayer L, ETA(L)=A(L)/P0+B(L)
137! LRUBC     : .T.: if radiational upper boundary condition
138
139! ----- numbering of timesteps:
140! NSTART    : first timestep of model
141! NSTOP     : last timestep of model
142
143! ----- quadrature:
144! NQUAD     : 1 ====> GAUSS
145
146! ----- type of equations:
147! LNHDYN    : .T. if 3-D non-hydrostatic dynamics is active
148
149! ----- way of computing initial state:
150! N2DINI    : 1 initialization for 2D with Haurwitz wave
151!           : 2 initialization for 2D with real fields
152! N3DINI    : 1 initialization for 3D with standard atmosphere
153!             (not available since cycle 12)
154!           : 0 initialization for 3D with real fields
155
156! ----- semi-implicit scheme:
157! LSITRIC   : .T.: if "tridiagonal" solver is used for the vertically
158!             coupled semi-implicit equations
159
160! ----- control of variables which are transformed in spectral space:
161! LSPRT     : .T.: if R*T/Rd "virtual temperature" as spectral variable
162
163! ----- diagnostics and frequencies:
164! NSPPR     : 0: no spectrum printed in spnorm; only global norms averaged
165!             on the vertical are printed
166!           : 1: no spectrum printed in spnorm; only global norms averaged
167!             on the vertical and global norms on each layer are printed
168!           : 2: both total wavenumber spectrum and zonal wavenumber spectrum
169!             are printed
170! NFRPOS    : frequency of post-processing events (time-steps)
171! NFRISP    : frequency of isp (animation !) events (time-steps)
172! NFRCO     : frequency of coupled fields (time-steps)
173! NFRCORM   : mass correction frequency (>0 time-steps, <0 hours, 0 no
174!             correction)
175! NFRHIS    : frequency of history write_ups (time-steps)
176! NFRMASSCON: frequency of mass conservation fixup (time-steps)
177! NFRGDI    : frequency of grid-point space diagnostics
178! NFRSDI    : frequency of spectral space diagnostics
179! NFRDHFG   : write-up frequency of global DDH
180! NFRDHFZ   : write-up frequency of zonal DDH
181! NFRDHFD   : write-up frequency of "limited domain" DDH
182! NFRDHP    : write-up frequency of DDH files
183! NPOSTS    : array containing postprocessing steps
184! NPISPS    : array containing isp (animation !) steps
185! NHISTS    : array containing history write-up steps
186! NMASSCONS : array containing mass conservation fixup steps
187! NGDITS    : array containing grid point diagnostics steps
188! NSDITS    : array containing spectral diagnostics steps
189! NDHFGTS   : array containing write out steps for global DDH
190! NDHFZTS   : array containing write out steps for zonal means DDH
191! NDHFDTS   : array containing write out steps for limited areas DDH
192! NDHPTS    : array containing write out steps for DDH
193! Explanation for N[XXX]TS:
194!             1) if N[XXX]TS(0)=0 action if MOD(JSTEP,NFR[XXX])=0
195!             2) if N[XXX]TS(0)>0 N[XXX]TS(0) significant numbers in
196!                N[XXX]TS are then considered and:
197!                action for JSTEP=N[XXX]TS(.)*NFR[XXX]
198!             3) IF N[XXX]TS(0)<0
199!                action for JSTEP=(N[XXX]TS(.)/DELTAT)*NFR[XXX]
200
201!========== ASSIMILATION SWITCHES =============================================
202
203! LNOBGON : .F. if eq. .T. no stop if unsuccessful reading of CMA files
204! LCANARI : .T. = term to control French OI
205! LCASIG  : .T. = interpolation of the model errors (French OI)
206! LGUESS  : .T. = term of first guess included
207! LOBS    : .T. = term of observations included
208! LSIMOB  : .T. = if simulated observations
209! LOBSC1  : .T. = term of observations included in configuration 1
210! LSCREEN : .T. = observation screening for variational assimilation
211! LSCREEN_OPENMP : .T. = 4DVAR screening runs in OpenMP-parallel mode over timeslots
212! L_SPLIT_SCREEN .T. = to split screenng
213! L_SCREEN_CALL: .T. = call to screening routine SCREEN
214! LOBSREF : .T. = comparison to observation for the trajectory (NCONF=131)
215! LIFSMIN : .T. = if running minimisation
216! LIFSTRAJ: .T. = if running high resolution trajectory integration
217! NCNTVAR : Definition of the control variable of a variational job.
218!           = 1 ===> control variables are model variables
219!           = 2 ===> control variables are normalized departures of
220!                    model variables from the background field
221!           = 3 ===> ..........
222! LOLDPP  : .T. use "old" p.p. of T,Q,U and V
223! NSTEPINI: Initial step in hours for the initial conditions
224!           at the beginning of 4D-Var trajectory (usually 3 hours).
225!           It is used to update the step while saving the FCs along
226!           the first trajectory.
227! NINTERPTRAJ : Interpolation method applied to increments
228! NINTERPINCR : Interpolation method applied to increments
229!           = 1 ===> Bi-linear interpolation (default)
230!           = 2 ===> Bi-cubic Rinterpolation
231!           = 3 ===> Conserving interpolation
232! For Conserving interpolation the style is defined by:
233! NINTERPTRAJORDER : order of interpolation for trajectories
234! NINTERPINCRORDER : order of interpolation for increments
235! NINTERPTRAJLIMIT : 0 if limiter is NOT used (default), 1 if used for trajectory interpolation
236! NINTERPINCRLIMIT : 0 if limiter is NOT used (default), 1 if used for increment interpolation
237
238!========== ALADIN SWITCHES ===================================================
239
240! LELAM   : .T. = limited area model with coupling or fully biperiodic
241!                 model (torus)
242!           .F. = global model (sphere)
243! LRPLANE : .T. = plane cartesian geometry
244!           .F. = spherical geometry
245! LTENC   : TRUE if tendency coupling of surface pressure
246!           FALSE if no tend. coupling of surf. pressure
247! LALLTC  : used together with LTENC when LTENC=.T.
248!          - no meaning for quadratic tendency coupling, where just t1 coupling
249!          is applied at every NEFRCL time step
250!          - for lin. tendency coupling:
251!          TRUE if tendency coupling of surf. pres. at every step
252!          FALSE if tend. coupl., except at every NEFRCL time steps
253!          when just t1 coupling
254! RTENC : multiplier of EALFA in the tendency coupling scheme
255!  for stability reasons (RTENC<=1. close to 1)
256
257!========== AROME SWITCH ======================================================
258
259! LAROME  : .T. = AROME limited area model
260
261!========== ECMWF Single Column Model =========================================
262! LSCMEC  : .T. = ECMWF Single Column Model
263! LSFCFLX : .T. = forcing with surface fluxes (latent and sensible).
264! REXTSHF : externally supplied sensible heat flux [W/m^2]
265! REXTLHF : externally supplied latent   heat flux [W/m^2]
266! LROUGH  : .T. = surface roughness length is externally specified
267! REXTZ0M : externally supplied roughness length for momentum [m]
268! REXTZ0H : externally supplied roughness length for heat [m]
269
270!========== DISTRIBUTED MEMORY SWITCHES =======================================
271
272! LMPOFF  : .T. = switch off the message passing library initialisation
273!                 requested for special cases LMESSP=.T. and NPROC=1
274!         : .F. = (default) full message passing features
275! NPROC   : Total number of processors requested for this run
276! N_REGIONS_NS : Number of regions (LEQ_REGIONS=T) or NPRGPNS (LEQ_REGIONS=F)
277! N_REGIONS_EW : Maximum number of partitions for all regions
278! N_REGIONS : Number of partitions in each region
279! NPRGPNS : Number of processors used during grid-point phase in North-South
280!           direction (previously known as NPROCA)
281! NPRGPEW : Number of processors used during grid-point phase in East-West
282!           direction (previously known as NPROCB)
283! NPRTRNS : Number of processors used during transform phase in North-South
284!           direction (previously the same as NPROCA and now implemented
285!           such that NPRTRNS=NPTRW)
286! NPRTRM  : Number of processors used during spectral computations in
287!           meridional wave direction (previously the same as NPROCA
288!           and now implemented such that NPRTRM=NPTRW)
289! NPRTRN  : Number of processors used during spectral computations in total
290!           wave direction (previously the same as NPROCA and now implemented
291!           such that NPRTRN=NPTRV)
292! NPRTRW  : Number of processors used during transform phase in wave space
293!           (previously the same as NPROCA)
294! NPRTRV  : Number of processors used during transform phase in vertical
295!           direction (previously known as NPROCB)
296! LOUTPUT : .T. = diagnostic output requested on this PE
297! NOUTPUT : 0 = No diagnostic output
298!           1 = Only diagnostic output from PE1 ( default )
299!           2 = Diagnostic output from all PEs into separate files
300! LREFOUT : .T. compare to reference run
301! LREFGEN : .T. to generate reference file
302! LMPDIAG : .T. = extensive message passing diagnostic output requested
303
304!========== PC SCHEMES ========================================================
305!----------------------------------------------
306! PC SCHEMES QUANTITIES CONSTANT DURING INTEGRATION
307!----------------------------------------------
308
309! LPC_FULL - full PC scheme switch (with reiterations of trajectories)
310
311! LPC_OLD - iterative scheme without trajectories recalculations
312!         - with iteration of D3 terms (Bubnova et all., 1995)
313
314! LPC_NESC - non-extrapolating two-time level SL SI scheme
315!          - X(t+dt/2) = X(t) during predictor
316
317!========== FORCING SWITCH ====================================================
318! LSFORC - switch to activate the large scale forcings in setup and cpg
319!==============================================================================
320
321! * Parameters:
322INTEGER(KIND=JPIM), PARAMETER :: JPNPST=240
323
324! * Technical switches:
325INTEGER(KIND=JPIM) :: NCONF
326INTEGER(KIND=JPIM) :: NTASKS ! ??????
327LOGICAL :: LALLOPR
328INTEGER(KIND=JPIM) :: NPRINTLEV
329LOGICAL :: LFDBOP
330LOGICAL :: LGRBOP
331LOGICAL :: LFBDAP
332LOGICAL :: LARPEGEF
333LOGICAL :: LARPEGEF_TRAJHR
334LOGICAL :: LARPEGEF_TRAJBG
335LOGICAL :: LARPEGEF_RDGP_INIT
336LOGICAL :: LARPEGEF_RDGP_TRAJHR
337LOGICAL :: LARPEGEF_RDGP_TRAJBG
338CHARACTER (LEN = 120) ::  CNDISPP
339LOGICAL :: LFPOS
340CHARACTER (LEN = 6) ::  CFPNCF
341LOGICAL :: LFPART2
342CHARACTER (LEN = 120) ::  CFDIRLST
343CHARACTER (LEN = 120) ::  CNPPATH
344LOGICAL :: LRETCFOU
345LOGICAL :: LWRTCFOU
346LOGICAL :: LRFOUTCNORM(4)
347LOGICAL :: LRGPTCNORM(3)
348LOGICAL :: LNF
349LOGICAL :: LSMSSIG
350LOGICAL :: LOPDIS
351INTEGER(KIND=JPIM) :: NCYCLE=128
352CHARACTER (LEN = 16) ::  CNMEXP
353CHARACTER (LEN = 2) ::  CFCLASS
354CHARACTER (LEN = 2) ::  CTYPE
355LOGICAL :: LBACKG
356LOGICAL :: LMINIM
357
358! * Model switches:
359LOGICAL :: LSLAG
360LOGICAL :: LTWOTL
361LOGICAL :: LRFRIC
362LOGICAL :: LVERCOR
363LOGICAL :: LAPRXPK
364LOGICAL :: LREGETA
365LOGICAL :: LRUBC
366INTEGER(KIND=JPIM) :: NSTART
367INTEGER(KIND=JPIM) :: NSTOP
368INTEGER(KIND=JPIM) :: NQUAD
369LOGICAL :: LNHDYN
370INTEGER(KIND=JPIM) :: N2DINI
371INTEGER(KIND=JPIM) :: N3DINI
372LOGICAL :: LSITRIC
373LOGICAL :: LSPRT
374INTEGER(KIND=JPIM) :: NSPPR
375INTEGER(KIND=JPIM) :: NFRPOS
376INTEGER(KIND=JPIM) :: NFRISP
377INTEGER(KIND=JPIM) :: NFRCORM
378INTEGER(KIND=JPIM) :: NFRCO
379INTEGER(KIND=JPIM) :: NFRHIS
380INTEGER(KIND=JPIM) :: NFRMASSCON
381INTEGER(KIND=JPIM) :: NFRGDI
382INTEGER(KIND=JPIM) :: NFRSDI
383INTEGER(KIND=JPIM) :: NFRDHFG
384INTEGER(KIND=JPIM) :: NFRDHFZ
385INTEGER(KIND=JPIM) :: NFRDHFD
386INTEGER(KIND=JPIM) :: NFRDHP
387INTEGER(KIND=JPIM) :: NPOSTS(0:JPNPST)
388INTEGER(KIND=JPIM) :: NPISPS(0:JPNPST)
389INTEGER(KIND=JPIM) :: NHISTS(0:JPNPST)
390INTEGER(KIND=JPIM) :: NMASSCONS(0:JPNPST)
391INTEGER(KIND=JPIM) :: NGDITS(0:JPNPST)
392INTEGER(KIND=JPIM) :: NSDITS(0:JPNPST)
393INTEGER(KIND=JPIM) :: NDHFGTS(0:JPNPST)
394INTEGER(KIND=JPIM) :: NDHFZTS(0:JPNPST)
395INTEGER(KIND=JPIM) :: NDHFDTS(0:JPNPST)
396INTEGER(KIND=JPIM) :: NDHPTS(0:JPNPST)
397
398! * Assimilation:
399LOGICAL :: LNOBGON
400LOGICAL :: LCANARI
401LOGICAL :: LCASIG
402LOGICAL :: LGUESS
403LOGICAL :: LOBS
404LOGICAL :: LSIMOB
405LOGICAL :: LOBSC1
406LOGICAL :: LSCREEN
407LOGICAL :: LSCREEN_OPENMP
408LOGICAL :: L_SPLIT_SCREEN
409LOGICAL :: L_SCREEN_CALL
410LOGICAL :: LOBSREF
411LOGICAL :: LIFSMIN
412LOGICAL :: LIFSTRAJ
413INTEGER(KIND=JPIM) :: NCNTVAR
414LOGICAL :: LOLDPP
415INTEGER(KIND=JPIM) :: NSTEPINI
416INTEGER(KIND=JPIM) :: NINTERPTRAJ
417INTEGER(KIND=JPIM) :: NINTERPINCR
418INTEGER(KIND=JPIM) :: NINTERPTRAJLIMIT
419INTEGER(KIND=JPIM) :: NINTERPINCRLIMIT
420INTEGER(KIND=JPIM) :: NINTERPTRAJORDER
421INTEGER(KIND=JPIM) :: NINTERPINCRORDER
422
423! * ALADIN:
424LOGICAL :: LELAM
425LOGICAL :: LRPLANE
426LOGICAL :: LTENC
427LOGICAL :: LALLTC
428REAL(KIND=JPRB) :: RTENC
429
430! * AROME:
431LOGICAL :: LAROME
432
433! * ECMWF Single Column Model:
434LOGICAL :: LSCMEC
435LOGICAL :: LSFCFLX
436REAL(KIND=JPRB) :: REXTSHF
437REAL(KIND=JPRB) :: REXTLHF
438LOGICAL :: LROUGH
439REAL(KIND=JPRB) :: REXTZ0M
440REAL(KIND=JPRB) :: REXTZ0H
441
442! * Distributed memory:
443LOGICAL :: LMPOFF
444INTEGER(KIND=JPIM) :: NPROC
445INTEGER(KIND=JPIM) :: N_REGIONS_NS
446INTEGER(KIND=JPIM) :: N_REGIONS_EW
447INTEGER(KIND=JPIM),ALLOCATABLE :: N_REGIONS(:)
448INTEGER(KIND=JPIM) :: NPRGPNS
449INTEGER(KIND=JPIM) :: NPRGPEW
450INTEGER(KIND=JPIM) :: NPRTRNS
451INTEGER(KIND=JPIM) :: NPRTRM
452INTEGER(KIND=JPIM) :: NPRTRN
453INTEGER(KIND=JPIM) :: NPRTRW
454INTEGER(KIND=JPIM) :: NPRTRV
455LOGICAL :: LOUTPUT
456INTEGER(KIND=JPIM) :: NOUTPUT
457LOGICAL :: LREFOUT
458LOGICAL :: LREFGEN
459LOGICAL :: LMPDIAG
460
461! * PC schemes.
462LOGICAL ::  LPC_FULL
463LOGICAL ::  LPC_OLD
464LOGICAL ::  LPC_NESC
465!
466! * FORCING
467LOGICAL ::  LSFORC
468!     ------------------------------------------------------------------
469!$OMP THREADPRIVATE(cfclass,cfdirlst,cfpncf,cndispp,cnmexp,cnppath,ctype,l_screen_call,l_split_screen,lallopr,lalltc)
470!$OMP THREADPRIVATE(laprxpk,larome,larpegef,larpegef_rdgp_init,larpegef_rdgp_trajbg,larpegef_rdgp_trajhr)
471!$OMP THREADPRIVATE(larpegef_trajbg,larpegef_trajhr,lbackg,lcanari,lcasig,lelam,lfbdap,lfdbop,lfpart2,lfpos)
472!$OMP THREADPRIVATE(lgrbop,lguess,lifsmin,lifstraj,lminim,lmpdiag,lmpoff,lnf,lnhdyn,lnobgon,lobs,lobsc1,lobsref)
473!$OMP THREADPRIVATE(loldpp,lopdis,loutput,lpc_full,lpc_nesc,lpc_old,lrefgen,lrefout,lregeta,lretcfou,lrfoutcnorm)
474!$OMP THREADPRIVATE(lrfric,lrgptcnorm,lrough,lrplane,lrubc,lscmec,lscreen,lscreen_openmp,lsfcflx,lsforc,lsimob)
475!$OMP THREADPRIVATE(lsitric,lslag,lsmssig,lsprt,ltenc,ltwotl,lvercor,lwrtcfou,n2dini,n3dini,n_regions_ew,n_regions_ns)
476!$OMP THREADPRIVATE(ncntvar,nconf,ncycle,ndhfdts,ndhfgts,ndhfzts,ndhpts,nfrco,nfrcorm,nfrdhfd,nfrdhfg,nfrdhfz,nfrdhp)
477!$OMP THREADPRIVATE(nfrgdi,nfrhis,nfrisp,nfrmasscon,nfrpos,nfrsdi,ngdits,nhists,ninterpincr,ninterpincrlimit)
478!$OMP THREADPRIVATE(ninterpincrorder,ninterptraj,ninterptrajlimit,ninterptrajorder,nmasscons,noutput,npisps,nposts)
479!$OMP THREADPRIVATE(nprgpew,nprgpns,nprintlev,nproc,nprtrm,nprtrn,nprtrns,nprtrv,nprtrw,nquad,nsdits,nsppr,nstart)
480!$OMP THREADPRIVATE(nstepini,nstop,ntasks,rextlhf,rextshf,rextz0h,rextz0m,rtenc)
481!$OMP THREADPRIVATE(n_regions)
482END MODULE YOMCT0
Note: See TracBrowser for help on using the repository browser.