source: trunk/LMDZ.MARS/libf/dyn3d/iniadvtrac.F @ 277

Last change on this file since 277 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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