source: trunk/LMDZ.GENERIC/libf/dyn3d/infotrac.F90 @ 1351

Last change on this file since 1351 was 1227, checked in by emillour, 11 years ago

Generic model:

  • Fixed bug in infotrac.F90 which was only an issue when using 0 tracers (unnecessary tests on tracer number nq).
  • Added missing initialization (allocations of comsoil_ arrays) in start2archive.

EM

File size: 4.4 KB
Line 
1MODULE infotrac
2
3IMPLICIT NONE
4! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
5  INTEGER, SAVE :: nqtot
6  INTEGER,allocatable :: iadv(:)   ! tracer advection scheme number
7  CHARACTER(len=20),allocatable ::  tname(:) ! tracer name
8
9CONTAINS
10
11      subroutine iniadvtrac(nq,numvanle)
12!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13! routine which initializes tracer names and advection schemes
14! reads these infos from file 'traceur.def' but uses default values
15! if that file is not found.
16! Ehouarn Millour. Oct. 2008  (made this LMDZ4-like) for future compatibility
17!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18      IMPLICIT NONE
19
20!#include "dimensions.h"
21!#include "advtrac.h"
22!#include "control.h"
23
24! routine arguments:
25      INTEGER,INTENT(out) :: nq ! number of tracers
26      INTEGER,INTENT(out) :: numvanle
27
28! local variables:
29      LOGICAL :: first
30      INTEGER :: iq
31      INTEGER :: ierr
32      CHARACTER(len=3) :: qname
33
34! Look for file traceur.def
35      OPEN(90,file='traceur.def',form='formatted',status='old', &
36              iostat=ierr)
37      IF (ierr.eq.0) THEN
38        write(*,*) "iniadvtrac: Reading file traceur.def"
39        ! read number of tracers:
40        read(90,*,iostat=ierr) nq
41        if (ierr.ne.0) then
42          write(*,*) "iniadvtrac: error reading number of tracers"
43          write(*,*) "   (first line of traceur.def) "
44          stop
45        endif
46       
47        ! allocate arrays:
48        allocate(iadv(nq))
49        allocate(tname(nq))
50       
51        ! initialize advection schemes to Van-Leer for all tracers
52        do iq=1,nq
53          iadv(iq)=3 ! Van-Leer
54        enddo
55       
56        do iq=1,nq
57        ! minimal version, just read in the tracer names, 1 per line
58          read(90,*,iostat=ierr) tname(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        close(90) ! done reading tracer names, close file
65      ENDIF ! of IF (ierr.eq.0)
66
67!  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
68!  ...................................................................
69!
70!     iadv = 1    shema  transport type "humidite specifique LMD" 
71!     iadv = 2    shema   amont
72!     iadv = 3    shema  Van-leer
73!     iadv = 4    schema  Van-leer + humidite specifique
74!                        Modif F.Codron
75!
76!
77      DO  iq = 1, nq-1
78       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'&
79       ,' pour le traceur no ', iq
80       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'  &
81       ,' traceur no ', iq
82       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour' &
83       ,'le traceur no ', iq
84
85       IF( iadv(iq).EQ.4 )  THEN
86         PRINT *,' Le shema  Van-Leer + humidite specifique ',          &
87       ' est  uniquement pour la vapeur d eau .'
88         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
89         CALL ABORT
90       ENDIF
91
92       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
93        PRINT *,' Erreur dans le choix de iadv (nqtot).Corriger et '    &
94       ,' repasser car  iadv(iq) = ', iadv(iq)
95         CALL ABORT
96       ENDIF
97      ENDDO
98
99!       IF( iadv(nq).EQ.1 ) PRINT *,' Choix du shema humidite '          &
100!       ,'specifique pour la vapeur d''eau'
101!       IF( iadv(nq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'  &
102!       ,' vapeur d''eau '
103!       IF( iadv(nq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer '         &
104!       ,' pour la vapeur d''eau'
105!       IF( iadv(nq).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + '       &
106!       ,' humidite specifique pour la vapeur d''eau'
107!
108!       IF( (iadv(nq).LE.0).OR.(iadv(nq).GT.4) )   THEN
109!        PRINT *,' Erreur dans le choix de iadv (nqtot).Corriger et '    &
110!       ,' repasser car  iadv(nqtot) = ', iadv(nqtot)
111!         CALL ABORT
112!       ENDIF
113
114      first = .TRUE.
115      numvanle = nq + 1
116      DO  iq = 1, nq
117        IF(((iadv(iq).EQ.3).OR.(iadv(iq).EQ.4)).AND.first ) THEN
118          numvanle = iq
119          first    = .FALSE.
120        ENDIF
121      ENDDO
122!
123      DO  iq = 1, nq
124
125      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
126          PRINT *,' Il y a discontinuite dans le choix du shema de ',   &
127          'Van-leer pour les traceurs . Corriger et repasser . '
128           CALL ABORT
129      ENDIF
130
131      ENDDO
132!
133      end subroutine iniadvtrac
134
135END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.