source: LMDZ6/trunk/libf/phylmd/lmdz_call_cloud_optics_prop.f90 @ 5833

Last change on this file since 5833 was 5828, checked in by rkazeroni, 2 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: 7.4 KB
Line 
1! $Id$
2!$gpum horizontal klon np
3MODULE lmdz_call_cloud_optics_prop
4  PRIVATE
5
6  PUBLIC call_cloud_optics_prop, call_cloud_optics_prop_post
7
8CONTAINS
9
10  SUBROUTINE call_cloud_optics_prop_post(ok_newmicro)
11    USE lmdz_cloud_optics_prop, ONLY : cloud_optics_prop_post
12    IMPLICIT NONE
13    LOGICAL, INTENT(IN) :: ok_newmicro
14
15    IF (ok_newmicro) THEN
16      CALL cloud_optics_prop_post()
17    ENDIF
18
19  END SUBROUTINE call_cloud_optics_prop_post
20
21  SUBROUTINE call_cloud_optics_prop(klon, klev, ok_newmicro,&
22       paprs, pplay, temp, radocond, picefra, pclc, &
23    pcltau, pclemi, pch, pcl, pcm, pct, radocondwp, xflwp, xfiwp, xflwc, xfiwc, ok_aie, &
24    mass_solu_aero, mass_solu_aero_pi, pcldtaupi, distcltop, temp_cltop, re, fl, reliq, reice, &
25    reliq_pi, reice_pi, scdnc, cldncl, reffclwtop, lcc, reffclws, &
26    reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra,  &
27    icefrac_optics, dNovrN, ptconv,rnebcon, ccwcon)
28
29  ! Interface between the LMDZ physics monitor and the cloud properties calculation routines
30  ! 2023/10/02: L. Raillard, M. Coulon--Decorzens, A. Idelkadi, L. Fairhead
31  ! (E. Vignon and J.-B. Madeleine in spirit)
32  ! List of arguments
33  !------------------
34
35  USE lmdz_cloud_optics_prop_ini , ONLY : ok_cdnc
36  USE lmdz_cloud_optics_prop_ini , ONLY : bl95_b0, bl95_b1
37  USE lmdz_cloud_optics_prop_ini , ONLY : iflag_ice_thermo, ok_new_lscp, iflag_t_glace
38  USE lmdz_cloud_optics_prop, ONLY : cloud_optics_prop
39 
40  USE icefrac_lsc_mod ! computes ice fraction (JBM 3/14) 
41  USE lmdz_lscp_tools, only: icefrac_lscp
42  USE nuage_mod, ONLY: nuage
43
44  IMPLICIT NONE
45 
46  ! input:
47  INTEGER, INTENT(IN) :: klon, klev      ! number of horizontal and vertical grid points
48  REAL, INTENT(IN) :: paprs(klon, klev+1)! pressure at bottom interfaces [Pa]
49  REAL, INTENT(IN) :: pplay(klon, klev)  ! pressure at the middle of layers [Pa]
50  REAL, INTENT(IN) :: temp(klon, klev)   ! temperature [K]
51  REAL, INTENT(IN) :: radocond(klon, klev) ! cloud condensed water seen by radiation [kg/kg]
52  REAL, INTENT(IN) :: picefra(klon,klev) ! ice fraction in clouds from large scale condensation scheme [-]
53  REAL, INTENT(IN) :: rnebcon(klon,klev) ! convection cloud fraction [-]
54  REAL, INTENT(IN) :: ccwcon(klon,klev)  ! condensed water from deep convection [kg/kg]
55  ! jq for the aerosol indirect effect
56  ! jq introduced by Johannes Quaas (quaas@lmd.jussieu.fr), 27/11/2003
57  REAL, INTENT(IN) :: mass_solu_aero(klon, klev)    ! total mass concentration for all soluble aerosols [ug m-3]
58  REAL, INTENT(IN) :: mass_solu_aero_pi(klon, klev) ! - (pre-industrial value)
59  REAL, INTENT(IN)  :: dNovrN(klon)         ! enhancement factor for cdnc
60  REAL, INTENT(OUT) :: distcltop(klon,klev) ! distance from large scale cloud top [m]
61  REAL, INTENT(OUT) :: temp_cltop(klon,klev)!temperature at large scale cloud top [K]
62
63  LOGICAL, INTENT(IN) :: ptconv(klon, klev) ! flag for grid points affected by deep convection
64  LOGICAL, INTENT(IN) :: ok_newmicro, ok_aie
65
66  ! inout:
67  REAL, INTENT(INOUT) :: pclc(klon, klev) ! cloud fraction for radiation [-]
68
69  ! out:
70  REAL, INTENT(OUT) :: pct(klon)      ! 2D total cloud cover [-]
71  REAL, INTENT(OUT) :: pcl(klon)      ! 2D low cloud cover [-]
72  REAL, INTENT(OUT) :: pcm(klon)      ! 2D mid cloud cover [-]
73  REAL, INTENT(OUT) :: pch(klon)      ! 2D high cloud cover [-]
74  REAL, INTENT(OUT) :: radocondwp(klon) ! total condensed water path (seen by radiation) [kg/m2]
75  REAL, INTENT(OUT) :: xflwp(klon)    ! liquid water path (seen by radiation) [kg/m2]
76  REAL, INTENT(OUT) :: xfiwp(klon)    ! ice water path (seen by radiation) [kg/m2]
77  REAL, INTENT(OUT) :: xflwc(klon, klev) ! liquid water content seen by radiation [kg/kg]
78  REAL, INTENT(OUT) :: xfiwc(klon, klev) ! ice water content seen by radiation [kg/kg]
79  REAL, INTENT(OUT) :: re(klon, klev) ! cloud droplet effective radius multiplied by fl
80  REAL, INTENT(OUT) :: fl(klon, klev) ! xliq * rneb, denominator to re; fraction of liquid water clouds
81                                      ! introduced to avoid problems in the averaging of the output
82                                      ! water clouds within a grid cell
83
84  REAL, INTENT(OUT) :: pcltau(klon, klev) ! cloud optical depth [m]
85  REAL, INTENT(OUT) :: pclemi(klon, klev) ! cloud emissivity [-]
86  REAL, INTENT(OUT) :: pcldtaupi(klon, klev) ! pre-industrial value of cloud optical thickness, ie.
87                                             ! values of optical thickness that does not account
88                                             ! for aerosol effects on cloud droplet radius [m]
89
90  REAL, INTENT(OUT) :: reliq(klon, klev)   ! liquid droplet effective radius [m]
91  REAL, INTENT(OUT) :: reice(klon, klev)   ! ice effective radius [m]
92  REAL, INTENT(OUT) :: reliq_pi(klon, klev)! liquid droplet effective radius [m], pre-industrial
93  REAL, INTENT(OUT) :: reice_pi(klon, klev)! ice effective radius [m], pre-industrial
94  REAL, INTENT(OUT) :: scdnc(klon, klev)   ! cloud droplet number concentration, mean over the whole mesh [m-3]
95  REAL, INTENT(OUT) :: cldncl(klon)        ! cloud droplet number concentration at top of cloud [m-3]
96  REAL, INTENT(OUT) :: reffclwtop(klon)    ! effective radius of cloud droplet at top of cloud [m]
97  REAL, INTENT(OUT) :: lcc(klon)           ! liquid Cloud Content at top of cloud [kg/kg]
98  REAL, INTENT(OUT) :: reffclws(klon, klev)! stratiform cloud droplet effective radius
99  REAL, INTENT(OUT) :: reffclwc(klon, klev)! convective cloud droplet effective radius
100  REAL, INTENT(OUT) :: cldnvi(klon)        ! column Integrated cloud droplet Number [/m2]
101  REAL, INTENT(OUT) :: lcc3d(klon, klev)   ! cloud fraction for liquid part only [-]
102  REAL, INTENT(OUT) :: lcc3dcon(klon, klev)! cloud fraction for liquid part only, convective clouds [-]
103  REAL, INTENT(OUT) :: lcc3dstra(klon, klev)!cloud fraction for liquid part only, stratiform clouds [-]
104  REAL, INTENT(OUT) :: icc3dcon(klon, klev)! cloud fraction for liquid part only, convective clouds [-]
105  REAL, INTENT(OUT) :: icc3dstra(klon, klev)! cloud fraction for ice part only, stratiform clouds [-]
106  REAL, INTENT(INOUT) :: icefrac_optics(klon, klev)! ice fraction in clouds seen by radiation [-]
107
108  ! Local variables
109  !----------------
110  INTEGER :: k
111  REAL :: dzfice(klon, klev)
112  REAL :: pp_ratio(klon)
113
114  IF (iflag_t_glace .EQ. 0) THEN
115     icefrac_optics(:, :) = 0.
116  ELSE
117     DO k = 1, klev
118        IF (ok_new_lscp) THEN
119          CALL icefrac_lscp(klon,temp(:,k),iflag_ice_thermo,distcltop(:,k),temp_cltop(:,k), &
120   &         icefrac_optics(:,k),dzfice(:,k))
121        ELSE
122          pp_ratio(1:klon) = pplay(1:klon,k)/paprs(1:klon,1)
123          CALL icefrac_lsc(klon,temp(:,k),pp_ratio(:),icefrac_optics(:,k))
124        ENDIF
125     ENDDO
126  ENDIF
127 
128
129
130  IF (ok_newmicro) THEN
131    CALL cloud_optics_prop(klon, klev, paprs, pplay, temp, radocond, picefra, pclc, &
132    pcltau, pclemi, pch, pcl, pcm, pct, radocondwp, xflwp, xfiwp, xflwc, xfiwc, &
133    mass_solu_aero, mass_solu_aero_pi, pcldtaupi, distcltop, temp_cltop, re, fl, reliq, reice, &
134    reliq_pi, reice_pi, scdnc, cldncl, reffclwtop, lcc, reffclws, &
135    reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra,  &
136    icefrac_optics, dNovrN, ptconv,rnebcon, ccwcon)
137  ELSE
138    CALL nuage (paprs, pplay, &
139               temp, radocond, picefra, pclc, pcltau, pclemi, &
140               pch, pcl,pcm, pct, radocondwp, &
141               ok_aie, &
142               mass_solu_aero, mass_solu_aero_pi, &
143               bl95_b0, bl95_b1, distcltop, temp_cltop, &
144               pcldtaupi, re, fl)
145  ENDIF
146  RETURN
147
148END SUBROUTINE call_cloud_optics_prop
149
150END MODULE lmdz_call_cloud_optics_prop
Note: See TracBrowser for help on using the repository browser.