source: LMDZ4/trunk/libf/phylmd/printflag.F @ 602

Last change on this file since 602 was 524, checked in by lmdzadmin, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.6 KB
Line 
1!
2! $Header$
3!
4       SUBROUTINE  printflag( tabcntr0, radpas, ok_ocean,ok_oasis,
5     ,                        ok_journe,ok_instan,ok_region        )
6c
7
8c
9c      Auteur :  P. Le Van
10
11       IMPLICIT NONE
12
13       REAL tabcntr0( 100 )
14       LOGICAL cycle_diurn0,soil_model0,new_oliq0,ok_orodr0
15       LOGICAL ok_orolf0,ok_limitvr0
16       LOGICAL ok_ocean,ok_oasis,ok_journe,ok_instan,ok_region
17       INTEGER radpas , radpas0
18c
19#include "clesphys.h"
20c
21c
22       PRINT 100
23       PRINT *,' *******************************************************
24     ,************'
25       PRINT *,' ********   Choix  des principales  cles de la physique
26     ,   *********'
27       PRINT *,' *******************************************************
28     ,************'
29       PRINT 100
30       PRINT 10, cycle_diurne,  soil_model 
31       PRINT 100
32
33       IF   (    iflag_con.EQ. 1 )   THEN
34           PRINT *,' *****           Shema  convection   LMD           
35     ,          ******'
36       ELSE IF ( iflag_con.EQ. 2 )   THEN
37           PRINT *,' *****           Shema  convection  Tiedtke 
38     ,          ******'
39       ELSE IF ( iflag_con.EQ. 3 )   THEN
40           PRINT *,' *****           Shema  convection    CCM     
41     ,          ******'
42       ENDIF
43       PRINT 100
44
45       PRINT 11, new_oliq, ok_orodr, ok_orolf   
46       PRINT 100
47
48       PRINT 7,  ok_limitvrai   
49       PRINT 100
50
51       PRINT 12, nbapp_rad
52       PRINT 100
53
54       PRINT 8, radpas
55       PRINT 100
56
57       PRINT 5,  ok_ocean,ok_oasis
58       PRINT 100
59
60       PRINT 4,ok_journe,ok_instan,ok_region
61       PRINT 100
62       PRINT 100
63c
64c
65        cycle_diurn0  = .FALSE.
66        soil_model0   = .FALSE.
67        new_oliq0     = .FALSE.
68        ok_orodr0     = .FALSE.
69        ok_orolf0     = .FALSE.
70        ok_limitvr0   = .FALSE.
71
72        IF( tabcntr0( 7 ).EQ. 1. )   cycle_diurn0 = .TRUE.
73        IF( tabcntr0( 8 ).EQ. 1. )    soil_model0 = .TRUE.
74        IF( tabcntr0( 9 ).EQ. 1. )      new_oliq0 = .TRUE.
75        IF( tabcntr0(10 ).EQ. 1. )      ok_orodr0 = .TRUE.
76        IF( tabcntr0(11 ).EQ. 1. )      ok_orolf0 = .TRUE.
77        IF( tabcntr0(12 ).EQ. 1. )    ok_limitvr0 = .TRUE.
78
79        PRINT *,' $$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$
80     ,$$$$$$$$$$$$$'
81        PRINT 100
82c
83       IF( INT( tabcntr0( 5 ) ) .NE. iflag_con  )   THEN
84        PRINT 20, INT(tabcntr0(5)), iflag_con
85        PRINT 100
86       ENDIF
87
88       IF( INT( tabcntr0( 6 ) ) .NE. nbapp_rad  )   THEN
89        PRINT 21,  INT(tabcntr0(6)), nbapp_rad
90        radpas0  = NINT( 86400./tabcntr0(1)/INT( tabcntr0(6) ) )
91        PRINT 100
92        PRINT 22, radpas0, radpas
93        PRINT 100
94       ENDIF
95
96       IF( cycle_diurn0.AND..NOT.cycle_diurne.OR..NOT.cycle_diurn0.AND.
97     ,        cycle_diurne )     THEN
98        PRINT 13, cycle_diurn0, cycle_diurne
99        PRINT 100
100       ENDIF
101
102       IF( soil_model0.AND..NOT.soil_model.OR..NOT.soil_model0.AND.
103     ,        soil_model )     THEN
104        PRINT 14, soil_model0, soil_model
105        PRINT 100
106       ENDIF
107
108       IF( new_oliq0.AND..NOT.new_oliq.OR..NOT.new_oliq0.AND.
109     ,        new_oliq )     THEN
110        PRINT 16, new_oliq0, new_oliq
111        PRINT 100
112       ENDIF
113
114       IF( ok_orodr0.AND..NOT.ok_orodr.OR..NOT.ok_orodr0.AND.
115     ,        ok_orodr )     THEN
116        PRINT 15, ok_orodr0, ok_orodr
117        PRINT 100
118       ENDIF
119
120       IF( ok_orolf0.AND..NOT.ok_orolf.OR..NOT.ok_orolf0.AND.
121     ,        ok_orolf )     THEN
122        PRINT 17, ok_orolf0, ok_orolf
123        PRINT 100
124       ENDIF
125
126       IF( ok_limitvr0.AND..NOT.ok_limitvrai.OR..NOT.ok_limitvr0.
127     ,     AND.ok_limitvrai )     THEN
128        PRINT 18, ok_limitvr0, ok_limitvrai
129        PRINT 100
130       ENDIF
131
132       PRINT 100
133       PRINT *,' *******************************************************
134     ,************'
135       PRINT 100
136
137 4    FORMAT(2x,5(1H*),'  ok_journe= ',l3,3x,',ok_instan = ',
138     , l3,3x,',ok_region = ',l3,3x,5(1H*) )
139
140 5    FORMAT(2x,5(1H*),'      ok_ocean = ',l3,6x,' , ok_oasis = ',
141     , l3,14x,5(1H*) )
142
143
144 7     FORMAT(2x,5(1H*),15x,'      ok_limitvrai   = ',l3,16x,5(1h*) )
145
146 8     FORMAT(2x,'*****             radpas    =                      ' ,
147     , i4,6x,' *****')
148
149 10    FORMAT(2x,5(1H*),'    Cycle_diurne = ',l3,4x,', Soil_model = ',
150     , l3,12x,6(1H*) )
151
152
153 11    FORMAT(2x,5(1H*),'  new_oliq = ',l3,3x,', Ok_orodr = ',
154     , l3,3x,', Ok_orolf = ',l3,3x,5(1H*) )
155
156
157 12    FORMAT(2x,'*****  Nb d appels /jour des routines de rayonn. = ' ,
158     , i4,6x,' *****')
159
160 13    FORMAT(2x,'$$$$$$$$   Attention !!  cycle_diurne  different  sur',
161     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
162
163 14    FORMAT(2x,'$$$$$$$$   Attention !!    soil_model  different  sur',
164     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
165
166 15    FORMAT(2x,'$$$$$$$$   Attention !!      ok_orodr  different  sur',
167     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
168
169 16    FORMAT(2x,'$$$$$$$$   Attention !!      new_oliq  different  sur',
170     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
171
172 17    FORMAT(2x,'$$$$$$$$   Attention !!      ok_orolf  different  sur',
173     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
174
175 18    FORMAT(2x,'$$$$$$$$   Attention !!  ok_limitvrai  different  sur',
176     , /1x,10x,' startphy = ',l3,2x,' et  run.def = ',l3)
177
178 20    FORMAT(/2x,'$$$$$$$$   Attention !!    iflag_con  different  sur',
179     , /1x,10x,' startphy = ',i3,2x,' et  run.def = ',i3 )
180
181 21    FORMAT(2x,'$$$$$$$$   Attention !!     nbapp_rad  different  sur',
182     , /1x,10x,' startphy = ',i3,2x,' et  run.def = ',i3 )
183
184 22    FORMAT(2x,'$$$$$$$$   Attention !!        radpas  different  sur',
185     , /1x,10x,' startphy = ',i3,2x,' et  run.def = ',i3 )
186
187 100   FORMAT(/)
188
189       RETURN
190       END
Note: See TracBrowser for help on using the repository browser.