source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/init_print_control_mod.f90 @ 3983

Last change on this file since 3983 was 3831, checked in by ymipsl, 10 years ago

module reorganisation for a cleaner dyn-phys interface
YM

File size: 1.8 KB
Line 
1MODULE init_print_control_mod
2
3! module print_control_mod splitted due to dependency module
4
5CONTAINS
6
7 
8  SUBROUTINE init_print_control
9  USE print_control_mod, ONLY : set_print_control
10  USE ioipsl, ONLY : getin
11  USE mod_phys_lmdz_para
12  IMPLICIT NONE
13    INTEGER :: lunout ! default output file identifier (6==screen)
14    INTEGER :: prt_level ! Output level
15    LOGICAL :: debug ! flag to specify if in "debug mode"
16    LOGICAL :: exist
17    INTEGER :: number
18   
19    !Config  Key  = prt_level
20    !Config  Desc = niveau d'impressions de débogage
21    !Config  Def  = 0
22    !Config  Help = Niveau d'impression pour le débogage
23    !Config         (0 = minimum d'impression)
24    prt_level = 0
25    IF (is_master) CALL getin('prt_level',prt_level)
26    CALL bcast(prt_level)
27
28    !Config  Key  = lunout
29    !Config  Desc = unite de fichier pour les impressions
30    !Config  Def  = 6
31    !Config  Help = unite de fichier pour les impressions
32    !Config         (defaut sortie standard = 6)
33    lunout=6
34    IF (is_master) CALL getin('lunout', lunout)
35    CALL bcast(lunout)
36
37    IF (is_omp_master) THEN
38      IF (lunout /= 5 .and. lunout /= 6) THEN
39         INQUIRE(FILE='lmdz.out_0000',EXIST=exist,NUMBER=number)
40         IF (exist) THEN
41           lunout=number
42         ELSE
43           OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',  &
44                STATUS='unknown',FORM='formatted')
45         ENDIF
46      ENDIF
47    ENDIF
48    CALL bcast_omp(lunout)
49
50    !Config  Key  = debug
51    !Config  Desc = mode debogage
52    !Config  Def  = false
53    !Config  Help = positionne le mode debogage
54
55    debug = .FALSE.
56    IF (is_master) CALL getin('debug',debug)
57    CALL bcast(debug)
58   
59    CALL set_print_control(lunout,prt_level,debug)
60
61  END SUBROUTINE init_print_control
62
63END MODULE init_print_control_mod
Note: See TracBrowser for help on using the repository browser.