Changeset 5712 for LMDZ6/trunk/libf/phylmd/cva_driver.f90
- Timestamp:
- Jun 16, 2025, 7:12:42 PM (6 weeks ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/cva_driver.f90
r5699 r5712 6 6 LOGICAL, SAVE :: debut = .TRUE. 7 7 !$OMP THREADPRIVATE(debut) 8 LOGICAL, SAVE :: never_compress=.FALSE. ! if true, compression is desactivated in convection 9 !$OMP THREADPRIVATE(never_compress) 8 10 9 11 PUBLIC cva_driver_pre, cva_driver_post, cva_driver … … 32 34 ! -- set simulation flags: 33 35 ! (common cvflag) 36 never_compress = .FALSE. 37 CALL getin_p("convection_no_compression",never_compress) 38 IF (s2s_is_initialized()) never_compress = .TRUE. ! for GPU, compression must be disabled 34 39 CALL cv_flag(iflag_ice_thermo) 35 40 … … 624 629 625 630 INTEGER, PARAMETER :: igout=1 631 LOGICAL :: is_convect(len) ! is convection is active on column 626 632 627 633 ! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,nd) … … 878 884 ! gridpoints and the weights "coef_convective" (= 1. for convective gridpoints and = 0. 879 885 ! elsewhere). 880 ncum = 0881 coef_convective(:) = 0.882 886 DO i = 1, len 883 887 IF (iflag1(i)==0) THEN 884 888 coef_convective(i) = 1. 885 ncum = ncum + 1 886 idcum(ncum) = i 889 is_convect(i) = .TRUE. 890 ELSE 891 coef_convective(i) = 0. 892 is_convect(i) = .FALSE. 887 893 END IF 888 894 END DO 889 895 890 ! print*,'len, ncum = ',len,ncum 896 897 IF (never_compress) THEN 898 compress = .FALSE. 899 DO i = 1,len 900 idcum(i) = i 901 ENDDO 902 ncum=len 903 ELSE 904 ncum = 0 905 DO i = 1, len 906 IF (iflag1(i)==0) THEN 907 ncum = ncum + 1 908 idcum(ncum) = i 909 END IF 910 END DO 911 912 IF (ncum>0) THEN 913 ! If the fraction of convective points is larger than comp_threshold, then compression 914 ! is assumed useless. 915 compress = ncum .lt. len*comp_threshold 916 IF (.not. compress) THEN 917 DO i = 1,len 918 idcum(i) = i 919 ENDDO 920 ncum=len 921 ENDIF 922 ENDIF 923 924 ENDIF 891 925 892 926 IF (ncum>0) THEN … … 898 932 899 933 IF (iflag_con==3) THEN 900 ! print*,'ncum tv1 ',ncum,tv1 901 ! print*,'tvp1 ',tvp1 902 !jyg< 903 ! If the fraction of convective points is larger than comp_threshold, then compression 904 ! is assumed useless. 905 ! 906 compress = ncum .lt. len*comp_threshold 907 ! 908 IF (.not. compress) THEN 909 DO i = 1,len 910 idcum(i) = i 911 ENDDO 912 ENDIF 913 ! 914 !>jyg 915 if (prt_level >= 9) & 916 PRINT *, 'cva_driver -> cv3a_compress' 934 if (prt_level >= 9) PRINT *, 'cva_driver -> cv3a_compress' 917 935 CALL cv3a_compress(len, nloc, ncum, nd, ntra, compress, & 918 936 iflag1, nk1, icb1, icbs1, & … … 937 955 Ale, Alp, omega) 938 956 939 ! print*,'tv ',tv940 ! print*,'tvp ',tvp941 957 942 958 END IF 943 959 944 960 IF (iflag_con==4) THEN 945 if (prt_level >= 9) & 946 PRINT *, 'cva_driver -> cv_compress' 961 if (prt_level >= 9) PRINT *, 'cva_driver -> cv_compress' 947 962 CALL cv_compress(len, nloc, ncum, nd, & 948 iflag1, nk1, icb1, &963 iflag1, compress, nk1, icb1, & 949 964 cbmf1, plcl1, tnk1, qnk1, gznk1, & 950 965 t1, q1, qs1, u1, v1, gz1, & … … 1255 1270 if (prt_level >= 9) & 1256 1271 PRINT *, 'cva_driver -> cv3a_uncompress' 1257 CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, compress,&1272 CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, is_convect, compress, & 1258 1273 iflag, icb, inb, & 1259 1274 precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, & … … 1297 1312 if (prt_level >= 9) & 1298 1313 PRINT *, 'cva_driver -> cv_uncompress' 1299 CALL cv_uncompress(nloc, len, ncum, nd, idcum, &1314 CALL cv_uncompress(nloc, len, ncum, nd, idcum, is_convect, compress, & 1300 1315 iflag, & 1301 1316 precip, cbmf, &
Note: See TracChangeset
for help on using the changeset viewer.