source: trunk/LMDZ.MARS/libf/dyn3d/test_period.F @ 1242

Last change on this file since 1242 was 1036, checked in by emillour, 11 years ago

Mars GCM: (a first step towards using parallel dynamics)

  • IMPORTANT CHANGE: Implemented dynamic tracers. It is no longer necessary to compile the model with the '-t #' option, number of tracers is simply read from tracer.def file (as before). Adapted makegcm_* scripts (and co.) accordingly. Technical aspects of the switch to dynamic tracers are:
    • advtrac.h (in dyn3d) removed and replaced by module infotrac.F
    • tracer.h (in phymars) removed and replaced by module tracer_mod.F90 (which contains nqmx, the number of tracers, etc. and can be used anywhere in the physics).
  • Included some side cleanups: removed unused files (in dyn3d) anldoppler2.F, anl_mcdstats.F and anl_stats-diag.F, and all the unecessary dimensions.* files in grid/dimension.
  • Checked that changes are clean and that GCM yields identical results (in debug mode) to previous svn version.

EM

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