source: trunk/LMDZ.GENERIC/libf/dyn3d/iniadvtrac.F @ 1115

Last change on this file since 1115 was 850, checked in by aslmd, 13 years ago

LMDZ.GENERIC. bug fix for start2archive (there was a problem because initracer was not called). also corrected iniadvtrac so that it could be compiled with -t 0. compiler was complaining about lines with iadv(nqmx). those lines are actually not necessary (this could be included in the loop above). added an if statement in iniadvtrac so that traceur.def does not even need to be here when the model is compiled with -t 0

File size: 4.7 KB
Line 
1      subroutine iniadvtrac(nq,numvanle)
2!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3! routine which initializes tracer names and advection schemes
4! reads these infos from file 'traceur.def' but uses default values
5! if that file is not found.
6! Ehouarn Millour. Oct. 2008  (made this LMDZ4-like) for future compatibility
7!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
8      IMPLICIT NONE
9
10#include "dimensions.h"
11#include "advtrac.h"
12#include "control.h"
13
14! routine arguments:
15      INTEGER,INTENT(out) :: nq ! number of tracers
16      INTEGER,INTENT(out) :: numvanle
17
18! local variables:
19      LOGICAL :: first
20      INTEGER :: iq
21      INTEGER :: ierr
22
23
24      if (nqmx > 0) then
25
26! Look for file traceur.def
27      OPEN(90,file='traceur.def',form='formatted',status='old',
28     &        iostat=ierr)
29      IF (ierr.eq.0) THEN
30        write(*,*) "iniadvtrac: Reading file traceur.def"
31        ! read number of tracers:
32        read(90,*,iostat=ierr) nq
33        if (ierr.ne.0) then
34          write(*,*) "iniadvtrac: error reading number of tracers"
35          write(*,*) "   (first line of traceur.def) "
36          stop
37        else
38          ! check that the number of tracers is indeed nqmx
39          if (nq.ne.nqmx) then
40            write(*,*) "iniadvtrac: error, wrong number of tracers:"
41            write(*,*) "nq=",nq," whereas nqmx=",nqmx
42            stop
43          endif
44        endif
45       
46        ! initialize advection schemes to Van-Leer for all tracers
47        do iq=1,nq
48          iadv(iq)=3 ! Van-Leer
49        enddo
50       
51
52
53!     MODIFICATION TO TEST OTHER SCHEMES BY RDW
54!        do iq=1,nq
55!           iadv(iq)=1
56!        enddo
57!        print*,'IADV SET TO 1 IN iniadvtrac!!!!'
58
59        do iq=1,nq
60        ! minimal version, just read in the tracer names, 1 per line
61          read(90,*,iostat=ierr) tnom(iq)
62          if (ierr.ne.0) then
63            write(*,*) 'iniadvtrac: error reading tracer names...'
64            stop
65          endif
66        enddo !of do iq=1,nq
67      ELSE
68        write(*,*) "iniadvtrac: can't find file traceur.def..."
69        stop
70      ENDIF ! of IF (ierr.eq.0)
71
72c  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
73c  ...................................................................
74c
75c     iadv = 1    shema  transport type "humidite specifique LMD" 
76c     iadv = 2    shema   amont
77c     iadv = 3    shema  Van-leer
78c     iadv = 4    schema  Van-leer + humidite specifique
79c                        Modif F.Codron
80c
81c
82      DO  iq = 1, nqmx
83       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
84     * ,' pour le traceur no ', iq
85       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'
86
87     * ,' traceur no ', iq
88       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
89     * ,'le traceur no ', iq
90
91       IF( iadv(iq).EQ.4 )  THEN
92         PRINT *,' Le shema  Van-Leer + humidite specifique ',
93     * ' est  uniquement pour la vapeur d eau .'
94         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
95         CALL ABORT
96       ENDIF
97
98       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
99        PRINT *,' Erreur dans le choix de iadv (nqmx).Corriger et '
100     * ,' repasser car  iadv(iq) = ', iadv(iq)
101         CALL ABORT
102       ENDIF
103      ENDDO
104
105!!!! AS: compiler complains about iadv(nqmx) when there is nqmx=0
106!!!! AS: so I commented those lines and changed nqmx-1 for nqmx above
107!       IF( iadv(nqmx).EQ.1 ) PRINT *,' Choix du shema humidite '
108!     * ,'specifique pour la vapeur d''eau'
109!       IF( iadv(nqmx).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'
110!     * ,' vapeur d''eau '
111!       IF( iadv(nqmx).EQ.3 ) PRINT *,' Choix du shema  Van-Leer '
112!     * ,' pour la vapeur d''eau'
113!       IF( iadv(nqmx).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + '
114!     * ,' humidite specifique pour la vapeur d''eau'
115!
116!c
117!!       IF( (iadv(nqmx).LE.0).OR.(iadv(nqmx).GT.4) )   THEN
118!!     MODIFICATION TO TEST WITHOUT TRACER ADVECTION BY RDW
119!       IF( (iadv(nqmx).LT.0).OR.(iadv(nqmx).GT.4) )   THEN
120!        PRINT *,' Erreur dans le choix de iadv (nqmx).Corriger et '
121!     * ,' repasser car  iadv(nqmx) = ', iadv(nqmx)
122!         CALL ABORT
123!       ENDIF
124
125      first = .TRUE.
126      numvanle = nqmx + 1
127      DO  iq = 1, nqmx
128        IF(((iadv(iq).EQ.3).OR.(iadv(iq).EQ.4)).AND.first ) THEN
129          numvanle = iq
130          first    = .FALSE.
131        ENDIF
132      ENDDO
133c
134      DO  iq = 1, nqmx
135
136      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
137          PRINT *,' Il y a discontinuite dans le choix du shema de ',
138     *    'Van-leer pour les traceurs . Corriger et repasser . '
139           CALL ABORT
140      ENDIF
141
142      ENDDO
143c
144      endif ! of if nqmx > 0
145
146      end
Note: See TracBrowser for help on using the repository browser.