source: LMDZ6/branches/LMDZ-COSP/libf/phylmd/lmdz_cloud_optics_prop_ini.f90 @ 5926

Last change on this file since 5926 was 5828, checked in by rkazeroni, 3 months ago

For GPU porting of call_cloud_optics_prop routine:

  • Add "horizontal" comment to specify possible names of horizontal variables
  • Put routine into module (speeds up source-to-source transformation)
  • Move declaration of variable with SAVE attribute outside of the compute routine to the module
  • Record event with a 2D "first" array instead of a scalar to enable GPU porting
  • Perform reduction on this "first" array and print (once) outside of the compute routine since this cannot be done on GPU in the current form
File size: 4.1 KB
Line 
1MODULE lmdz_cloud_optics_prop_ini
2  IMPLICIT NONE
3
4  SAVE
5
6  INTEGER, PROTECTED :: prt_level, lunout
7  INTEGER, PROTECTED :: flag_aerosol
8  INTEGER, PROTECTED :: iflag_t_glace=0
9  INTEGER, PROTECTED :: iflag_rei
10  INTEGER, PROTECTED :: novlp, iflag_ice_thermo
11  LOGICAL, PROTECTED :: ok_cdnc
12  LOGICAL, PROTECTED :: ok_icefra_lscp, ok_new_lscp
13  REAL, PROTECTED :: bl95_b0, bl95_b1 ! Parameter in B&L 95-Formula
14  REAL, ALLOCATABLE :: latitude_deg(:)
15  !$OMP THREADPRIVATE(latitude_deg)
16  REAL, PROTECTED :: cdnc_max=-1.
17  REAL, PROTECTED :: cdnc_max_m3=-1.
18  REAL, PROTECTED :: cdnc_min=-1.
19  REAL, PROTECTED :: cdnc_min_m3=-1.
20  REAL, PROTECTED :: rpi, rg, rd
21  REAL, PROTECTED :: rad_chau1, rad_chau2
22  REAL, PROTECTED :: rei_max, rei_min
23  REAL, PROTECTED :: rei_coef, rei_min_temp
24  REAL, PROTECTED :: zepsec
25  REAL, PARAMETER :: thres_tau=0.3, thres_neb=0.001
26  REAL, PARAMETER :: prmhc=440.*100. ! Pressure between medium and high level cloud in Pa
27  REAL, PARAMETER :: prlmc=680.*100. ! Pressure between low and medium level cloud in Pa
28  REAL, PARAMETER :: coef_froi=0.09, coef_chau =0.13
29  REAL, PARAMETER :: seuil_neb=0.001
30! if iflag_t_glace=0, old values are used for liquid/ice partitionning:
31  REAL, PARAMETER :: t_glace_min_old = 258.
32  REAL, PARAMETER :: t_glace_max_old = 273.13
33  REAL, PARAMETER :: k_ice0=0.005 ! units=m2/g
34  REAL, PARAMETER :: df=1.66 ! diffusivity factor
35  LOGICAL, SAVE, ALLOCATABLE :: first(:,:)  ! Test, if the cloud optical depth exceeds the necessary threshold
36!$OMP THREADPRIVATE(first)
37!$OMP THREADPRIVATE(prt_level, lunout, flag_aerosol, iflag_t_glace)
38!$OMP THREADPRIVATE(iflag_rei, novlp, iflag_ice_thermo) 
39!$OMP THREADPRIVATE(ok_cdnc, ok_icefra_lscp, ok_new_lscp)
40!$OMP THREADPRIVATE(bl95_b0, bl95_b1, cdnc_max, cdnc_max_m3)
41!$OMP THREADPRIVATE(cdnc_min, cdnc_min_m3, rpi, rg, rd)
42!$OMP THREADPRIVATE(rad_chau1, rad_chau2, rei_max, rei_min)
43!$OMP THREADPRIVATE(rei_coef, rei_min_temp)
44!$OMP THREADPRIVATE(zepsec)
45
46 
47CONTAINS
48
49  SUBROUTINE cloud_optics_prop_ini(klon, klev, prt_level_in, lunout_in, flag_aerosol_in, &
50       & ok_cdnc_in, bl95_b0_in, &
51       & bl95_b1_in, latitude_deg_in, rpi_in, rg_in, rd_in, zepsec_in, novlp_in, &
52       & iflag_ice_thermo_in, ok_new_lscp_in)
53
54    USE ioipsl_getin_p_mod, ONLY : getin_p
55
56    IMPLICIT NONE
57    INTEGER, INTENT(IN) :: klon, klev
58    INTEGER, INTENT(IN) :: prt_level_in, lunout_in
59    INTEGER, INTENT(IN) :: flag_aerosol_in
60    INTEGER, INTENT(IN) :: novlp_in, iflag_ice_thermo_in
61    LOGICAL, INTENT(IN) :: ok_cdnc_in, ok_new_lscp_in
62    REAL, INTENT(IN) :: bl95_b0_in, bl95_b1_in
63    REAL, INTENT(IN) :: latitude_deg_in(klon)
64    REAL, INTENT(IN) :: rpi_in, rg_in, rd_in
65    REAL, INTENT(IN) :: zepsec_in
66
67    ALLOCATE(latitude_deg(klon))
68    ALLOCATE(first(klon, klev))
69    first(:,:) = .FALSE.
70
71    prt_level = prt_level_in
72    lunout = lunout_in
73    flag_aerosol = flag_aerosol_in
74    ok_cdnc = ok_cdnc_in
75    bl95_b0 = bl95_b0_in
76    bl95_b1 = bl95_b1_in
77    latitude_deg(:) = latitude_deg_in(:)
78    rpi = rpi_in
79    rg = rg_in
80    rd = rd_in
81    zepsec = zepsec_in
82    novlp = novlp_in
83    iflag_ice_thermo = iflag_ice_thermo_in
84    ok_new_lscp = ok_new_lscp_in
85   
86    call getin_p('cdnc_min',cdnc_min)
87    cdnc_min_m3=cdnc_min*1.E6
88    IF (cdnc_min_m3<0.) cdnc_min_m3=20.E6 ! astuce pour retrocompatibilite
89    write(lunout,*)'cdnc_min=', cdnc_min_m3/1.E6
90    call getin_p('cdnc_max',cdnc_max)
91    cdnc_max_m3=cdnc_max*1.E6
92    IF (cdnc_max_m3<0.) cdnc_max_m3=1000.E6 ! astuce pour retrocompatibilite
93    write(lunout,*)'cdnc_max=', cdnc_max_m3/1.E6
94    CALL getin_p('iflag_t_glace',iflag_t_glace)     
95    write(lunout,*)'iflag_t_glace= ',iflag_t_glace
96    CALL getin_p('rad_chau1',rad_chau1)
97    CALL getin_p('rad_chau2',rad_chau2)
98    CALL getin_p('ok_icefra_lscp', ok_icefra_lscp)
99    iflag_rei = 0
100    CALL getin_p('iflag_rei',iflag_rei)
101    rei_min = 3.5
102    CALL getin_p('rei_min',rei_min)
103    rei_max = 61.29
104    CALL getin_p('rei_max',rei_max)
105    rei_coef = 2.4
106    CALL getin_p('rei_coef',rei_coef)
107    rei_min_temp = 175.
108    CALL getin_p('rei_min_temp',rei_min_temp)
109
110   
111  END SUBROUTINE cloud_optics_prop_ini
112
113END MODULE lmdz_cloud_optics_prop_ini
Note: See TracBrowser for help on using the repository browser.