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

Last change on this file since 801 was 253, checked in by emillour, 13 years ago

Generic GCM

  • Massive update to version 0.7

EM+RW

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