source: trunk/LMDZ.GENERIC/libf/dyn3d/test_period.F @ 1351

Last change on this file since 1351 was 1216, checked in by emillour, 11 years ago

Generic model:
Major cleanup, in order to ease the use of LMDZ.GENERIC with (parallel) dynamics
in LMDZ.COMMON: (NB: this will break LMDZ.UNIVERSAL, which should be thrashed
in the near future)

  • Updated makegcm_* scripts (and makdim) and added the "-full" (to enforce full recomputation of the model) option
  • In dyn3d: converted control.h to module control_mod.F90 and converted iniadvtrac.F to module infotrac.F90
  • Added module mod_const_mpi.F90 in dyn3d (not used in serial mode)
  • Rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallelism)
  • added created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the max and min of a field over the whole planet. This should be further imroved with computation of means (possibly area weighed), etc.

EM

File size: 2.6 KB
Line 
1      SUBROUTINE test_period ( ucov, vcov, teta, q, p, phis )
2     
3      USE infotrac, ONLY: nqtot
4      IMPLICIT NONE
5c
6c     Auteur : P. Le Van 
7c    ---------
8c  ....  Cette routine teste la periodicite en longitude des champs   ucov,
9c                           teta, q , p et phis                 ..........
10c
11c     IMPLICIT NONE
12c
13#include "dimensions.h"
14#include "paramet.h"
15c
16c    ......  Arguments   ......
17c
18      REAL ucov(ip1jmp1,llm), vcov(ip1jm,llm), teta(ip1jmp1,llm) ,
19     ,      q(ip1jmp1,llm,nqtot), p(ip1jmp1,llmp1), phis(ip1jmp1)
20c
21c   .....  Variables  locales  .....
22c
23      INTEGER ij,l,nq
24c
25      DO l = 1, llm
26         DO ij = 1, ip1jmp1, iip1
27          IF( ucov(ij,l).NE.ucov(ij+iim,l) )  THEN
28          PRINT *,'STOP dans test_period car ---  UCOV  ---  n est pas', 
29     ,  ' periodique en longitude ! '
30          PRINT *,' l,  ij = ', l, ij, ij+iim
31          STOP
32          ENDIF
33          IF( teta(ij,l).NE.teta(ij+iim,l) )  THEN
34          PRINT *,'STOP dans test_period car ---  TETA  ---  n est pas', 
35     ,   ' periodique en longitude ! '
36          PRINT *,' l,  ij = ', l, ij, ij+iim
37          STOP
38          ENDIF
39         ENDDO
40      ENDDO
41
42c
43      DO l = 1, llm
44         DO ij = 1, ip1jm, iip1
45          IF( vcov(ij,l).NE.vcov(ij+iim,l) )  THEN
46          PRINT *,'STOP dans test_period car ---  VCOV  ---  n est pas', 
47     ,   ' periodique en longitude !'
48          PRINT *,' l,  ij = ', l, ij, ij+iim,vcov(ij+iim,l),vcov(ij,l)
49          vcov(ij+iim,l)=vcov(ij,l)
50          STOP
51          ENDIF
52         ENDDO
53      ENDDO
54     
55c
56      DO nq =1, nqtot
57        DO l =1, llm
58          DO ij = 1, ip1jmp1, iip1
59          IF( q(ij,l,nq).NE.q(ij+iim,l,nq) )  THEN
60          PRINT *,'STOP dans test_period car ---  Q  ---  n est pas ', 
61     ,   'periodique en longitude !'
62          PRINT *,' nq , l,  ij, ij+iim = ', nq, l, ij, ij+iim
63        PRINT *,'q(ij,l,nq) q(ij+iim,l,nq) ',q(ij,l,nq),q(ij+iim,l,nq)
64          STOP
65          ENDIF
66          ENDDO
67        ENDDO
68      ENDDO
69c
70       DO l = 1, llm
71         DO ij = 1, ip1jmp1, iip1
72          IF( p(ij,l).NE.p(ij+iim,l) )  THEN
73          PRINT *,'STOP dans test_period car ---  P  ---  n est pas', 
74     ,    ' periodique en longitude !'
75          PRINT *,' l ij = ',l, ij, ij+iim
76          STOP
77          ENDIF
78          IF( phis(ij).NE.phis(ij+iim) )  THEN
79          PRINT *,'STOP dans test_period car ---  PHIS  ---  n est pas', 
80     ,   ' periodique en longitude !  l, IJ = ', l, ij,ij+iim
81          PRINT *,' ij = ', ij, ij+iim
82          STOP
83          ENDIF
84         ENDDO
85       ENDDO
86c
87c
88         RETURN
89         END
Note: See TracBrowser for help on using the repository browser.