source: LMDZ.3.3/tags/IPSL-CM4_v2x0/libf/phylmd/printflag.F @ 464

Last change on this file since 464 was 464, checked in by (none), 21 years ago

This commit was manufactured by cvs2svn to create tag
'IPSL-CM4_v2x0'.

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