source: trunk/LMDZ.PLUTO.old/libf/dyn3d/iniadvtrac.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

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