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

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

LMDZ.GENERIC. Corrected problems with allocated arrays in start2archive and newstart. Applied a workaround to make those work without tracers (-cpp NOTRAC -- perhaps there is a better solution). Checked that everything works in debug mode.

File size: 4.5 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#ifdef NOTRAC
24
25! Look for file traceur.def
26      OPEN(90,file='traceur.def',form='formatted',status='old',
27     &        iostat=ierr)
28      IF (ierr.eq.0) THEN
29        write(*,*) "iniadvtrac: Reading file traceur.def"
30        ! read number of tracers:
31        read(90,*,iostat=ierr) nq
32        if (ierr.ne.0) then
33          write(*,*) "iniadvtrac: error reading number of tracers"
34          write(*,*) "   (first line of traceur.def) "
35          stop
36        else
37          ! check that the number of tracers is indeed nqmx
38          if (nq.ne.nqmx) then
39            write(*,*) "iniadvtrac: error, wrong number of tracers:"
40            write(*,*) "nq=",nq," whereas nqmx=",nqmx
41            stop
42          endif
43        endif
44       
45        ! initialize advection schemes to Van-Leer for all tracers
46        do iq=1,nq
47          iadv(iq)=3 ! Van-Leer
48        enddo
49       
50
51
52!     MODIFICATION TO TEST OTHER SCHEMES BY RDW
53!        do iq=1,nq
54!           iadv(iq)=1
55!        enddo
56!        print*,'IADV SET TO 1 IN iniadvtrac!!!!'
57
58        do iq=1,nq
59        ! minimal version, just read in the tracer names, 1 per line
60          read(90,*,iostat=ierr) tnom(iq)
61          if (ierr.ne.0) then
62            write(*,*) 'iniadvtrac: error reading tracer names...'
63            stop
64          endif
65        enddo !of do iq=1,nq
66      ELSE
67        write(*,*) "iniadvtrac: can't find file traceur.def..."
68        stop
69      ENDIF ! of IF (ierr.eq.0)
70
71c  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
72c  ...................................................................
73c
74c     iadv = 1    shema  transport type "humidite specifique LMD" 
75c     iadv = 2    shema   amont
76c     iadv = 3    shema  Van-leer
77c     iadv = 4    schema  Van-leer + humidite specifique
78c                        Modif F.Codron
79c
80c
81      DO  iq = 1, nqmx-1
82       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'
83     * ,' pour le traceur no ', iq
84       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'
85
86     * ,' traceur no ', iq
87       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour'
88     * ,'le traceur no ', iq
89
90       IF( iadv(iq).EQ.4 )  THEN
91         PRINT *,' Le shema  Van-Leer + humidite specifique ',
92     * ' est  uniquement pour la vapeur d eau .'
93         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
94         CALL ABORT
95       ENDIF
96
97       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
98        PRINT *,' Erreur dans le choix de iadv (nqmx).Corriger et '
99     * ,' repasser car  iadv(iq) = ', iadv(iq)
100         CALL ABORT
101       ENDIF
102      ENDDO
103
104       IF( iadv(nqmx).EQ.1 ) PRINT *,' Choix du shema humidite '
105     * ,'specifique pour la vapeur d''eau'
106       IF( iadv(nqmx).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'
107     * ,' vapeur d''eau '
108       IF( iadv(nqmx).EQ.3 ) PRINT *,' Choix du shema  Van-Leer '
109     * ,' pour la vapeur d''eau'
110       IF( iadv(nqmx).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + '
111     * ,' humidite specifique pour la vapeur d''eau'
112c
113!       IF( (iadv(nqmx).LE.0).OR.(iadv(nqmx).GT.4) )   THEN
114!     MODIFICATION TO TEST WITHOUT TRACER ADVECTION BY RDW
115       IF( (iadv(nqmx).LT.0).OR.(iadv(nqmx).GT.4) )   THEN
116        PRINT *,' Erreur dans le choix de iadv (nqmx).Corriger et '
117     * ,' repasser car  iadv(nqmx) = ', iadv(nqmx)
118         CALL ABORT
119       ENDIF
120
121      first = .TRUE.
122      numvanle = nqmx + 1
123      DO  iq = 1, nqmx
124        IF(((iadv(iq).EQ.3).OR.(iadv(iq).EQ.4)).AND.first ) THEN
125          numvanle = iq
126          first    = .FALSE.
127        ENDIF
128      ENDDO
129c
130      DO  iq = 1, nqmx
131
132      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
133          PRINT *,' Il y a discontinuite dans le choix du shema de ',
134     *    'Van-leer pour les traceurs . Corriger et repasser . '
135           CALL ABORT
136      ENDIF
137
138      ENDDO
139c
140
141#endif
142
143      end
Note: See TracBrowser for help on using the repository browser.