source: LMDZ6/branches/Amaury_dev/libf/phylmd/printflag.F90

Last change on this file was 5137, checked in by abarral, 8 weeks ago

Put gradsdef.h, tracstoke.h, clesphys.h into modules

  • 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: 4.9 KB
RevLine 
[1992]1
[524]2! $Header$
3
[1992]4SUBROUTINE printflag(tabcntr0, radpas, ok_journe, ok_instan, ok_region)
[5137]5  ! Auteur :  P. Le Van
[524]6
[5137]7  USE lmdz_clesphys
[524]8
[1992]9  IMPLICIT NONE
[524]10
[1992]11  REAL tabcntr0(100)
12  LOGICAL cycle_diurn0, soil_model0, new_oliq0, ok_orodr0
13  LOGICAL ok_orolf0, ok_limitvr0
14  LOGICAL ok_journe, ok_instan, ok_region
15  INTEGER radpas, radpas0
[524]16
[1992]17  PRINT 100
18  PRINT *, ' ******************************************************* &
[5087]19
20    ************'
[1992]21  PRINT *, ' ********   Choix  des principales  cles de la physique &
[5087]22
23        *********'
[1992]24  PRINT *, ' ******************************************************* &
[5087]25
26    ************'
[1992]27  PRINT 100
[5082]28  PRINT 10, iflag_cycle_diurne>=1, soil_model
[1992]29  PRINT 100
[524]30
[1992]31  IF (iflag_con==1) THEN
32    PRINT *, ' *****           Shema  convection   LMD        &
[5087]33
34                     ******'
[1992]35  ELSE IF (iflag_con==2) THEN
36    PRINT *, ' *****           Shema  convection  Tiedtke     &
[5087]37
38                     ******'
[1992]39  ELSE IF (iflag_con>=3) THEN
40    PRINT *, ' *****           Shema  convection    Emanuel   &
[5087]41
42                     ******'
[1992]43  END IF
44  PRINT 100
[524]45
[1992]46  PRINT 11, new_oliq, ok_orodr, ok_orolf
47  PRINT 100
[524]48
[1992]49  PRINT 7, ok_limitvrai
50  PRINT 100
[524]51
[1992]52  PRINT 12, nbapp_rad
53  PRINT 100
[524]54
[1992]55  PRINT 8, radpas
56  PRINT 100
[524]57
[1992]58  PRINT 4, ok_journe, ok_instan, ok_region
59  PRINT 100
60  PRINT 100
[524]61
62
[1992]63  cycle_diurn0 = .FALSE.
64  soil_model0 = .FALSE.
65  new_oliq0 = .FALSE.
66  ok_orodr0 = .FALSE.
67  ok_orolf0 = .FALSE.
68  ok_limitvr0 = .FALSE.
[524]69
[1992]70  IF (tabcntr0(7)==1.) cycle_diurn0 = .TRUE.
71  IF (tabcntr0(8)==1.) soil_model0 = .TRUE.
72  IF (tabcntr0(9)==1.) new_oliq0 = .TRUE.
73  IF (tabcntr0(10)==1.) ok_orodr0 = .TRUE.
74  IF (tabcntr0(11)==1.) ok_orolf0 = .TRUE.
75  IF (tabcntr0(12)==1.) ok_limitvr0 = .TRUE.
[524]76
[1992]77  PRINT *, ' $$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$ &
[5087]78
79   $$$$$$$$$$$$$'
[1992]80  PRINT 100
[524]81
[1992]82  IF (int(tabcntr0(5))/=iflag_con) THEN
83    PRINT 20, int(tabcntr0(5)), iflag_con
84    PRINT 100
85  END IF
[524]86
[1992]87  IF (int(tabcntr0(6))/=nbapp_rad) THEN
88    PRINT 21, int(tabcntr0(6)), nbapp_rad
89    ! radpas0  = NINT( 86400./tabcntr0(1)/INT( tabcntr0(6) ) )
90    PRINT 100
91    ! PRINT 22, radpas0, radpas
92    PRINT 100
93  END IF
[524]94
[5082]95  IF (cycle_diurn0 .AND. .NOT. (iflag_cycle_diurne>=1) .OR. .NOT. cycle_diurn0 .AND. &
96      (iflag_cycle_diurne>=1) ) THEN
[3317]97    PRINT 13, cycle_diurn0, iflag_cycle_diurne
[1992]98    PRINT 100
99  END IF
[524]100
[1992]101  IF (soil_model0 .AND. .NOT. soil_model .OR. .NOT. soil_model0 .AND. &
102      soil_model) THEN
103    PRINT 14, soil_model0, soil_model
104    PRINT 100
105  END IF
[524]106
[1992]107  IF (new_oliq0 .AND. .NOT. new_oliq .OR. .NOT. new_oliq0 .AND. new_oliq) &
108      THEN
109    PRINT 16, new_oliq0, new_oliq
110    PRINT 100
111  END IF
[524]112
[1992]113  IF (ok_orodr0 .AND. .NOT. ok_orodr .OR. .NOT. ok_orodr0 .AND. ok_orodr) &
114      THEN
115    PRINT 15, ok_orodr0, ok_orodr
116    PRINT 100
117  END IF
[524]118
[1992]119  IF (ok_orolf0 .AND. .NOT. ok_orolf .OR. .NOT. ok_orolf0 .AND. ok_orolf) &
120      THEN
121    PRINT 17, ok_orolf0, ok_orolf
122    PRINT 100
123  END IF
[524]124
[1992]125  IF (ok_limitvr0 .AND. .NOT. ok_limitvrai .OR. .NOT. ok_limitvr0 .AND. &
126      ok_limitvrai) THEN
127    PRINT 18, ok_limitvr0, ok_limitvrai
128    PRINT 100
129  END IF
[524]130
[1992]131  PRINT 100
132  PRINT *, ' ******************************************************* &
[5087]133
134    ************'
[1992]135  PRINT 100
[524]136
[1992]1374 FORMAT (2X, 5('*'), '  ok_journe= ', L3, 3X, ',ok_instan = ', L3, 3X, &
138    ',ok_region = ', L3, 3X, 5('*'))
[524]139
[1992]1407 FORMAT (2X, 5('*'), 15X, '      ok_limitvrai   = ', L3, 16X, 5('*'))
[524]141
[1992]1428 FORMAT (2X, '*****             radpas    =                      ', I4, 6X, &
143    ' *****')
[524]144
[1992]14510 FORMAT (2X, 5('*'), '    Cycle_diurne = ', L3, 4X, ', Soil_model = ', L3, &
146    12X, 6('*'))
[524]147
148
[1992]14911 FORMAT (2X, 5('*'), '  new_oliq = ', L3, 3X, ', Ok_orodr = ', L3, 3X, &
150    ', Ok_orolf = ', L3, 3X, 5('*'))
[524]151
152
[1992]15312 FORMAT (2X, '*****  Nb d appels /jour des routines de rayonn. = ', I4, 6X, &
154    ' *****')
[524]155
[1992]15613 FORMAT (2X, '$$$$$$$$   Attention !!  cycle_diurne  different  sur', /1X, &
157    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
[524]158
[1992]15914 FORMAT (2X, '$$$$$$$$   Attention !!    soil_model  different  sur', /1X, &
160    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
161
16215 FORMAT (2X, '$$$$$$$$   Attention !!      ok_orodr  different  sur', /1X, &
163    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
164
16516 FORMAT (2X, '$$$$$$$$   Attention !!      new_oliq  different  sur', /1X, &
166    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
167
16817 FORMAT (2X, '$$$$$$$$   Attention !!      ok_orolf  different  sur', /1X, &
169    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
170
17118 FORMAT (2X, '$$$$$$$$   Attention !!  ok_limitvrai  different  sur', /1X, &
172    10X, ' startphy = ', L3, 2X, ' et  run.def = ', L3)
173
17420 FORMAT (/2X, '$$$$$$$$   Attention !!    iflag_con  different  sur', /1X, &
175    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
176
17721 FORMAT (2X, '$$$$$$$$   Attention !!     nbapp_rad  different  sur', /1X, &
178    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
179
18022 FORMAT (2X, '$$$$$$$$   Attention !!        radpas  different  sur', /1X, &
181    10X, ' startphy = ', I3, 2X, ' et  run.def = ', I3)
182
183100 FORMAT (/)
184
[5105]185
[1992]186END SUBROUTINE printflag
Note: See TracBrowser for help on using the repository browser.