source: LMDZ6/branches/Ocean_skin/libf/phylmd/printflag.F90 @ 3627

Last change on this file since 3627 was 3317, checked in by musat, 6 years ago

Utilisation de la clef iflag_cycle_diurne ; l'ancienne clef
cycle_diurne n'existe plus.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.5 KB
Line 
1
2! $Header$
3
4SUBROUTINE printflag(tabcntr0, radpas, ok_journe, ok_instan, ok_region)
5
6
7
8  ! Auteur :  P. Le Van
9
10  IMPLICIT NONE
11
12  REAL tabcntr0(100)
13  LOGICAL cycle_diurn0, soil_model0, new_oliq0, ok_orodr0
14  LOGICAL ok_orolf0, ok_limitvr0
15  LOGICAL ok_journe, ok_instan, ok_region
16  INTEGER radpas, radpas0
17
18  include "clesphys.h"
19
20
21  PRINT 100
22  PRINT *, ' ******************************************************* &
23    &                                                         &
24    &  ************'
25  PRINT *, ' ********   Choix  des principales  cles de la physique &
26    &                                                         &
27    &      *********'
28  PRINT *, ' ******************************************************* &
29    &                                                         &
30    &  ************'
31  PRINT 100
32  PRINT 10, iflag_cycle_diurne.GE.1, soil_model
33  PRINT 100
34
35  IF (iflag_con==1) THEN
36    PRINT *, ' *****           Shema  convection   LMD        &
37      &                                                       &
38      &                   ******'
39  ELSE IF (iflag_con==2) THEN
40    PRINT *, ' *****           Shema  convection  Tiedtke     &
41      &                                                       &
42      &                   ******'
43  ELSE IF (iflag_con>=3) THEN
44    PRINT *, ' *****           Shema  convection    Emanuel   &
45      &                                                       &
46      &                   ******'
47  END IF
48  PRINT 100
49
50  PRINT 11, new_oliq, ok_orodr, ok_orolf
51  PRINT 100
52
53  PRINT 7, ok_limitvrai
54  PRINT 100
55
56  PRINT 12, nbapp_rad
57  PRINT 100
58
59  PRINT 8, radpas
60  PRINT 100
61
62  PRINT 4, ok_journe, ok_instan, ok_region
63  PRINT 100
64  PRINT 100
65
66
67  cycle_diurn0 = .FALSE.
68  soil_model0 = .FALSE.
69  new_oliq0 = .FALSE.
70  ok_orodr0 = .FALSE.
71  ok_orolf0 = .FALSE.
72  ok_limitvr0 = .FALSE.
73
74  IF (tabcntr0(7)==1.) cycle_diurn0 = .TRUE.
75  IF (tabcntr0(8)==1.) soil_model0 = .TRUE.
76  IF (tabcntr0(9)==1.) new_oliq0 = .TRUE.
77  IF (tabcntr0(10)==1.) ok_orodr0 = .TRUE.
78  IF (tabcntr0(11)==1.) ok_orolf0 = .TRUE.
79  IF (tabcntr0(12)==1.) ok_limitvr0 = .TRUE.
80
81  PRINT *, ' $$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$ &
82    &                                                         &
83    & $$$$$$$$$$$$$'
84  PRINT 100
85
86  IF (int(tabcntr0(5))/=iflag_con) THEN
87    PRINT 20, int(tabcntr0(5)), iflag_con
88    PRINT 100
89  END IF
90
91  IF (int(tabcntr0(6))/=nbapp_rad) THEN
92    PRINT 21, int(tabcntr0(6)), nbapp_rad
93    ! radpas0  = NINT( 86400./tabcntr0(1)/INT( tabcntr0(6) ) )
94    PRINT 100
95    ! PRINT 22, radpas0, radpas
96    PRINT 100
97  END IF
98
99  IF (cycle_diurn0 .AND. .NOT. (iflag_cycle_diurne.GE.1) .OR. .NOT. cycle_diurn0 .AND. &
100      (iflag_cycle_diurne.GE.1) ) THEN
101    PRINT 13, cycle_diurn0, iflag_cycle_diurne
102    PRINT 100
103  END IF
104
105  IF (soil_model0 .AND. .NOT. soil_model .OR. .NOT. soil_model0 .AND. &
106      soil_model) THEN
107    PRINT 14, soil_model0, soil_model
108    PRINT 100
109  END IF
110
111  IF (new_oliq0 .AND. .NOT. new_oliq .OR. .NOT. new_oliq0 .AND. new_oliq) &
112      THEN
113    PRINT 16, new_oliq0, new_oliq
114    PRINT 100
115  END IF
116
117  IF (ok_orodr0 .AND. .NOT. ok_orodr .OR. .NOT. ok_orodr0 .AND. ok_orodr) &
118      THEN
119    PRINT 15, ok_orodr0, ok_orodr
120    PRINT 100
121  END IF
122
123  IF (ok_orolf0 .AND. .NOT. ok_orolf .OR. .NOT. ok_orolf0 .AND. ok_orolf) &
124      THEN
125    PRINT 17, ok_orolf0, ok_orolf
126    PRINT 100
127  END IF
128
129  IF (ok_limitvr0 .AND. .NOT. ok_limitvrai .OR. .NOT. ok_limitvr0 .AND. &
130      ok_limitvrai) THEN
131    PRINT 18, ok_limitvr0, ok_limitvrai
132    PRINT 100
133  END IF
134
135  PRINT 100
136  PRINT *, ' ******************************************************* &
137    &                                                         &
138    &  ************'
139  PRINT 100
140
1414 FORMAT (2X, 5('*'), '  ok_journe= ', L3, 3X, ',ok_instan = ', L3, 3X, &
142    ',ok_region = ', L3, 3X, 5('*'))
143
1447 FORMAT (2X, 5('*'), 15X, '      ok_limitvrai   = ', L3, 16X, 5('*'))
145
1468 FORMAT (2X, '*****             radpas    =                      ', I4, 6X, &
147    ' *****')
148
14910 FORMAT (2X, 5('*'), '    Cycle_diurne = ', L3, 4X, ', Soil_model = ', L3, &
150    12X, 6('*'))
151
152
15311 FORMAT (2X, 5('*'), '  new_oliq = ', L3, 3X, ', Ok_orodr = ', L3, 3X, &
154    ', Ok_orolf = ', L3, 3X, 5('*'))
155
156
15712 FORMAT (2X, '*****  Nb d appels /jour des routines de rayonn. = ', I4, 6X, &
158    ' *****')
159
16013 FORMAT (2X, '$$$$$$$$   Attention !!  cycle_diurne  different  sur', /1X, &
161    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
162
16314 FORMAT (2X, '$$$$$$$$   Attention !!    soil_model  different  sur', /1X, &
164    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
165
16615 FORMAT (2X, '$$$$$$$$   Attention !!      ok_orodr  different  sur', /1X, &
167    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
168
16916 FORMAT (2X, '$$$$$$$$   Attention !!      new_oliq  different  sur', /1X, &
170    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
171
17217 FORMAT (2X, '$$$$$$$$   Attention !!      ok_orolf  different  sur', /1X, &
173    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
174
17518 FORMAT (2X, '$$$$$$$$   Attention !!  ok_limitvrai  different  sur', /1X, &
176    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
177
17820 FORMAT (/2X, '$$$$$$$$   Attention !!    iflag_con  different  sur', /1X, &
179    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
180
18121 FORMAT (2X, '$$$$$$$$   Attention !!     nbapp_rad  different  sur', /1X, &
182    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
183
18422 FORMAT (2X, '$$$$$$$$   Attention !!        radpas  different  sur', /1X, &
185    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
186
187100 FORMAT (/)
188
189  RETURN
190END SUBROUTINE printflag
Note: See TracBrowser for help on using the repository browser.