Changeset 4368 for LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat
- Timestamp:
- Dec 6, 2022, 12:01:16 AM (2 years ago)
- Location:
- LMDZ6/branches/Ocean_skin
- Files:
-
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Ocean_skin
- Property svn:mergeinfo changed
-
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/calfis.F
r2604 r4368 29 29 c Auteur : P. Le Van, F. Hourdin 30 30 c ......... 31 USE infotrac, ONLY: nqtot, niadv, tname31 USE infotrac, ONLY: nqtot, tracers 32 32 USE control_mod, ONLY: planet_type, nsplit_phys 33 33 #ifdef CPP_PHYS … … 135 135 c ----------------- 136 136 137 INTEGER i,j,l,ig0,ig,iq,i iq137 INTEGER i,j,l,ig0,ig,iq,itr 138 138 REAL zpsrf(ngridmx) 139 139 REAL zplev(ngridmx,llm+1),zplay(ngridmx,llm) … … 281 281 c --------------- 282 282 c 283 itr=0 283 284 DO iq=1,nqtot 284 iiq=niadv(iq) 285 IF(.NOT.tracers(iq)%isAdvected) CYCLE 286 itr = itr + 1 285 287 DO l=1,llm 286 zqfi(1,l,i q) = pq(1,1,l,iiq)287 ig0 = 2288 zqfi(1,l,itr) = pq(1,1,l,iq) 289 ig0 = 2 288 290 DO j=2,jjm 289 291 DO i = 1, iim 290 zqfi(ig0,l,i q) = pq(i,j,l,iiq)292 zqfi(ig0,l,itr) = pq(i,j,l,iq) 291 293 ig0 = ig0 + 1 292 294 ENDDO 293 295 ENDDO 294 zqfi(ig0,l,i q) = pq(1,jjp1,l,iiq)296 zqfi(ig0,l,itr) = pq(1,jjp1,l,iq) 295 297 ENDDO 296 298 ENDDO … … 481 483 lafin_split=lafin.and.isplit==nsplit_phys 482 484 483 CALL call_physiq(ngridmx,llm,nqtot,tname, 485 ! if (planet_type=="earth") then 486 CALL call_physiq(ngridmx,llm,nqtot,tracers(:)%name, 484 487 & debut_split,lafin_split, 485 488 & jD_cur,jH_cur_split,zdt_split, … … 490 493 & flxwfi,pducov, 491 494 & zdufi,zdvfi,zdtfi,zdqfi,zdpsrf) 492 493 ! if (planet_type=="earth") then494 !495 ! CALL physiq (ngridmx,496 ! . llm,497 ! . debut_split,498 ! . lafin_split,499 ! . jD_cur,500 ! . jH_cur_split,501 ! . zdt_split,502 ! . zplev,503 ! . zplay,504 ! . zphi,505 ! . zphis,506 ! . presnivs,507 ! . zufi,508 ! . zvfi, zrfi,509 ! . ztfi,510 ! . zqfi,511 ! . flxwfi,512 ! . zdufi,513 ! . zdvfi,514 ! . zdtfi,515 ! . zdqfi,516 ! . zdpsrf,517 ! . pducov)518 495 ! 519 496 ! else if ( planet_type=="generic" ) then … … 522 499 ! . llm, !! nlayer 523 500 ! . nqtot, !! nq 524 ! . t name,!! tracer names from dynamical core (given in infotrac)501 ! . tracers(:)%name,!! tracer names from dynamical core (given in infotrac) 525 502 ! . debut_split, !! firstcall 526 503 ! . lafin_split, !! lastcall … … 622 599 pdqfi(:,:,:,:)=0. 623 600 C 601 itr = 0 624 602 DO iq=1,nqtot 625 iiq=niadv(iq) 603 IF(.NOT.tracers(iq)%isAdvected) CYCLE 604 itr = itr + 1 626 605 DO l=1,llm 627 606 DO i=1,iip1 628 pdqfi(i,1,l,i iq) = zdqfi(1,l,iq)629 pdqfi(i,jjp1,l,i iq) = zdqfi(ngridmx,l,iq)607 pdqfi(i,1,l,iq) = zdqfi(1,l,itr) 608 pdqfi(i,jjp1,l,iq) = zdqfi(ngridmx,l,itr) 630 609 ENDDO 631 610 DO j=2,jjm 632 611 ig0=1+(j-2)*iim 633 612 DO i=1,iim 634 pdqfi(i,j,l,i iq) = zdqfi(ig0+i,l,iq)613 pdqfi(i,j,l,iq) = zdqfi(ig0+i,l,itr) 635 614 ENDDO 636 pdqfi(iip1,j,l,i iq) = pdqfi(1,j,l,iq)615 pdqfi(iip1,j,l,iq) = pdqfi(1,j,l,itr) 637 616 ENDDO 638 617 ENDDO -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/calfis_loc.F
r2604 r4368 45 45 USE Times 46 46 #endif 47 USE infotrac, ONLY: nqtot, niadv, tname47 USE infotrac, ONLY: nqtot, tracers 48 48 USE control_mod, ONLY: planet_type, nsplit_phys 49 49 #ifdef CPP_PHYS … … 154 154 c ----------------- 155 155 156 INTEGER i,j,l,ig0,ig,iq,i iq156 INTEGER i,j,l,ig0,ig,iq,itr 157 157 REAL,ALLOCATABLE,SAVE :: zpsrf(:) 158 158 REAL,ALLOCATABLE,SAVE :: zplev(:,:),zplay(:,:) … … 366 366 c 367 367 368 itr = 0 368 369 DO iq=1,nqtot 369 iiq=niadv(iq) 370 IF(.NOT.tracers(iq)%isAdvected) CYCLE 371 itr = itr + 1 370 372 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 371 373 DO l=1,llm … … 375 377 i=index_i(ig0) 376 378 j=index_j(ig0) 377 zqfi(ig0,l,i q) = pq(i,j,l,iiq)379 zqfi(ig0,l,itr) = pq(i,j,l,iq) 378 380 enddo 379 381 ENDDO … … 731 733 lafin_split=lafin.and.isplit==nsplit_phys 732 734 733 CALL call_physiq(klon,llm,nqtot,t name,735 CALL call_physiq(klon,llm,nqtot,tracers(:)%name, 734 736 & debut_split,lafin_split, 735 737 & jD_cur,jH_cur_split,zdt_split, … … 1069 1071 C 1070 1072 !cdir NODEP 1073 itr = 0 1071 1074 DO iq=1,nqtot 1072 iiq=niadv(iq) 1075 IF(.NOT.tracers(iq)%isAdvected) CYCLE 1076 itr = itr + 1 1073 1077 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1074 1078 DO l=1,llm … … 1079 1083 i=index_i(ig0) 1080 1084 j=index_j(ig0) 1081 pdqfi(i,j,l,i iq) = zdqfi(ig0,l,iq)1082 if (i==1) pdqfi(iip1,j,l,i iq) = zdqfi(ig0,l,iq)1085 pdqfi(i,j,l,iq) = zdqfi(ig0,l,itr) 1086 if (i==1) pdqfi(iip1,j,l,iq) = zdqfi(ig0,l,itr) 1083 1087 ENDDO 1084 1088 1085 1089 IF (is_north_pole_dyn) then 1086 1090 DO i=1,iip1 1087 pdqfi(i,1,l,i iq) = zdqfi(1,l,iq)1091 pdqfi(i,1,l,iq) = zdqfi(1,l,itr) 1088 1092 ENDDO 1089 1093 ENDIF … … 1091 1095 IF (is_south_pole_dyn) then 1092 1096 DO i=1,iip1 1093 pdqfi(i,jjp1,l,i iq) = zdqfi(klon,l,iq)1097 pdqfi(i,jjp1,l,iq) = zdqfi(klon,l,itr) 1094 1098 ENDDO 1095 1099 ENDIF -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/inigeomphy_mod.F90
r4013 r4368 25 25 USE nrtype, ONLY: pi 26 26 USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, & 27 scaleheight, pseudoalt 27 scaleheight, pseudoalt, presinter 28 28 USE vertical_layers_mod, ONLY: init_vertical_layers 29 29 IMPLICIT NONE … … 233 233 ! copy over preff , ap(), bp(), etc 234 234 CALL init_vertical_layers(nlayer,preff,scaleheight, & 235 ap,bp,aps,bps,presnivs,p seudoalt)235 ap,bp,aps,bps,presnivs,presinter,pseudoalt) 236 236 237 237 !$OMP END PARALLEL -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/callphysiq_mod.F90
r2604 r4368 20 20 21 21 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat 22 USE control_mod, ONLY: planet_type 22 USE control_mod, ONLY: planet_type, ok_dyn_xios 23 23 USE physiq_mod, ONLY: physiq 24 #ifdef CPP_XIOS 25 USE mod_xios_dyn3dmem, ONLY : dyn3d_ctx_handle 26 USE xios, ONLY : xios_set_current_context 27 #endif 24 28 IMPLICIT NONE 25 29 … … 90 94 zdpsrf_omp) 91 95 96 ! switching back to LMDZDYN context 97 #ifdef CPP_XIOS 98 !$OMP MASTER 99 if (ok_dyn_xios) then 100 CALL xios_set_current_context(dyn3d_ctx_handle) 101 endif 102 !$OMP END MASTER 103 #endif 104 92 105 93 106 END SUBROUTINE call_physiq -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/ce0l.F90
r3810 r4368 23 23 USE netcdf, ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR, & 24 24 NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR 25 USE infotrac, ONLY: type_trac, in fotrac_init25 USE infotrac, ONLY: type_trac, init_infotrac 26 26 USE dimphy, ONLY: klon 27 27 USE test_disvert_m, ONLY: test_disvert … … 108 108 calnd='gregorian' 109 109 SELECT CASE(calend) 110 CASE('earth_360d');CALL ioconf_calendar('360 d'); calnd='with 360 days/year'110 CASE('earth_360d');CALL ioconf_calendar('360_day'); calnd='with 360 days/year' 111 111 CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd='with no leap year' 112 112 CASE('earth_366d');CALL ioconf_calendar('366d'); calnd='with leap years only' … … 132 132 133 133 !--- Tracers initializations 134 CALL in fotrac_init()134 CALL init_infotrac() 135 135 136 136 CALL inifilr() -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90
r3605 r4368 39 39 USE comvert_mod, ONLY: ap, bp, preff, pressure_exner 40 40 USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itau_phy, start_time 41 USE strings_mod, ONLY: strLower 41 42 42 43 IMPLICIT NONE … … 74 75 USE exner_hyb_m, ONLY: exner_hyb 75 76 USE exner_milieu_m, ONLY: exner_milieu 76 USE infotrac, ONLY: nqtot, t name77 USE infotrac, ONLY: nqtot, tracers 77 78 USE filtreg_mod 78 79 IMPLICIT NONE … … 84 85 ! Local variables: 85 86 CHARACTER(LEN=256) :: modname, fmt 86 INTEGER :: i, j, l, ji, itau, iday 87 INTEGER :: i, j, l, ji, itau, iday, iq 87 88 REAL :: xpn, xps, time, phystep 88 89 REAL, DIMENSION(iip1,jjp1) :: psol … … 145 146 ! Look for ozone tracer: 146 147 #ifndef INCA 147 DO i =1,nqtot; IF(ANY(["O3","o3"]==tname(i))) EXIT; END DO148 IF(i /=nqtot+1) THEN148 DO iq=1,nqtot; IF(strLower(tracers(iq)%name)=="o3") EXIT; END DO 149 IF(iq/=nqtot+1) THEN 149 150 CALL regr_lat_time_coefoz 150 151 CALL press_coefoz 151 CALL regr_pr_o3(p3d, q3d(:,:,:,i ))152 q3d(:,:,:,i )=q3d(:,:,:,i)*48./ 29.!--- Mole->mass fraction152 CALL regr_pr_o3(p3d, q3d(:,:,:,iq)) 153 q3d(:,:,:,iq)=q3d(:,:,:,iq)*48./ 29. !--- Mole->mass fraction 153 154 END IF 154 155 #endif -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90
r4022 r4368 94 94 USE init_ssrf_m, ONLY: start_init_subsurf 95 95 USE phys_state_var_mod, ONLY: beta_aridity, delta_tsurf, awake_dens, cv_gen, & 96 ratqs_inter 96 ratqs_inter, rneb_ancien 97 97 !use ioipsl_getincom 98 98 IMPLICIT NONE … … 130 130 131 131 INCLUDE "compbl.h" 132 INCLUDE " thermcell.h"132 INCLUDE "alpale.h" 133 133 134 134 deg2rad= pi/180.0 … … 286 286 287 287 ratqs_inter = 0.002 288 rneb_ancien = 0. 288 289 CALL phyredem( "startphy.nc" ) 289 290 -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90
r4013 r4368 16 16 USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid) 17 17 USE vertical_layers_mod, ONLY : init_vertical_layers 18 USE infotrac, ONLY: nqtot,nqo,nbtr,nqCO2,tname,ttext,type_trac,& 19 niadv,conv_flg,pbl_flg,solsym,& 20 nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,& 21 ok_isotopes,ok_iso_verif,ok_isotrac,& 22 ok_init_iso,niso_possibles,tnat,& 23 alpha_ideal,use_iso,iqiso,iso_num,& 24 iso_indnum,zone_num,phase_num,& 25 indnum_fn_num,index_trac,& 26 niso,ntraceurs_zone,ntraciso,nqtottr,itr_indice 18 USE infotrac, ONLY: nbtr, type_trac, types_trac 27 19 #ifdef CPP_StratAer 28 USE infotrac , ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &20 USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, & 29 21 id_SO2_strat, id_H2SO4_strat, id_BIN01_strat 30 22 … … 38 30 USE mod_phys_lmdz_omp_data, ONLY: klon_omp 39 31 #endif 40 USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq , config_inca32 USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq 41 33 USE inifis_mod, ONLY: inifis 42 34 USE time_phylmdz_mod, ONLY: init_time … … 116 108 117 109 !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/) 118 !$OMP PARALLEL DEFAULT(SHARED) &119 110 ! Copy all threadprivate variables in temps_mod 120 !$OMP COPYIN(annee_ref, day_ini, day_ref,start_time)111 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(annee_ref,day_ini,day_ref,start_time) 121 112 122 113 ! Initialize physical constants in physics: … … 146 137 147 138 ! Initialize tracer names, numbers, etc. for physics 148 CALL init_infotrac_phy(nqtot,nqo,nbtr,nqtottr,nqCO2,tname,ttext,type_trac,& 149 niadv,conv_flg,pbl_flg,solsym,& 150 nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,& 151 ok_isotopes,ok_iso_verif,ok_isotrac,& 152 ok_init_iso,niso_possibles,tnat,& 153 alpha_ideal,use_iso,iqiso,iso_num,& 154 iso_indnum,zone_num,phase_num,& 155 indnum_fn_num,index_trac,& 156 niso,ntraceurs_zone,ntraciso,itr_indice & 157 #ifdef CPP_StratAer 158 ,nbtr_bin,nbtr_sulgas& 159 ,id_OCS_strat,id_SO2_strat,id_H2SO4_strat,id_BIN01_strat& 160 #endif 161 ) 139 CALL init_infotrac_phy 162 140 163 141 ! Initializations for Reprobus 164 IF ( type_trac == 'repr') THEN142 IF (ANY(types_trac == 'repr')) THEN 165 143 #ifdef REPROBUS 166 144 call Init_chem_rep_phys(klon_omp,nlayer) … … 172 150 !$OMP END PARALLEL 173 151 174 IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN 175 #ifdef INCA 176 call init_const_lmdz( & 177 anneeref,dayref, iphysiq,day_step,nday, & 178 nbsrf, is_oce,is_sic, is_ter,is_lic, calend, & 179 config_inca) 180 call init_inca_para( & 181 nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, & 182 distrib_phys,communicator) 183 #endif 184 END IF 185 IF (type_trac == 'repr') THEN 152 153 IF (ANY(types_trac == 'repr')) THEN 186 154 #ifdef REPROBUS 187 155 call init_reprobus_para( & … … 198 166 END IF 199 167 200 IF ( type_trac == 'inca' .OR. type_trac == 'inco') THEN168 IF (ANY(types_trac == 'inca') .OR. ANY(types_trac == 'inco')) THEN 201 169 #ifdef INCA 202 CALL init_inca_dim (klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &203 rlonudyn, rlatudyn,rlonvdyn,rlatvdyn)170 CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, & 171 rlonudyn, rlatudyn, rlonvdyn, rlatvdyn) 204 172 #endif 205 IF (type_trac == 'repr') THEN206 #ifdef REPROBUS207 CALL Init_chem_rep_phys(klon_omp,nbp_lev)208 #endif209 END IF210 173 END IF 211 174 -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90
r2798 r4368 3 3 !******************************************************************************* 4 4 5 USE indice_sol_mod, ONLY: is_ter, is_oce, is_oce, is_lic, epsfra5 USE indice_sol_mod, ONLY: is_ter, is_oce, is_oce, is_lic, epsfra 6 6 USE dimphy, ONLY: klon, zmasq 7 7 USE phys_state_var_mod, ONLY: pctsrf 8 USE geometry_mod, ONLY : longitude_deg, latitude_deg8 USE geometry_mod, ONLY : longitude_deg, latitude_deg 9 9 USE grid_atob_m, ONLY: grille_m 10 10 USE ioipsl, ONLY: flininfo, flinopen, flinget, flinclo 11 11 USE ioipsl_getin_p_mod, ONLY: getin_p 12 USE comconst_mod, ONLY: im, pi 12 USE comconst_mod, ONLY: im, pi 13 USE surface_data, ONLY: landice_opt 13 14 14 15 CHARACTER(LEN=256), PARAMETER :: icefname="landiceref.nc", icevar="landice" … … 58 59 ! Sub-surfaces initialization 59 60 !******************************************************************************* 60 !--- Read and interpolate on model T-grid soil fraction and soil ice fraction. 61 CALL flininfo(icefname, iml_lic, jml_lic, llm_tmp, ttm_tmp, fid) 62 ALLOCATE(lat_lic(iml_lic,jml_lic),lon_lic(iml_lic,jml_lic)) 63 ALLOCATE(fraclic(iml_lic,jml_lic)) 64 CALL flinopen(icefname, .FALSE., iml_lic, jml_lic, llm_tmp, & 65 & lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt, fid) 66 CALL flinget(fid, icevar, iml_lic, jml_lic, llm_tmp, ttm_tmp, 1,1, fraclic) 67 CALL flinclo(fid) 68 WRITE(lunout,*)'landice dimensions: iml_lic, jml_lic : ',iml_lic,jml_lic 61 IF (landice_opt .LT. 2) THEN 62 ! Continue with reading landice.nc file 63 WRITE(lunout,*)"Read landice.nc file to attribute is_lic fraction" 69 64 70 ALLOCATE(dlon_lic(iml_lic),dlat_lic(jml_lic)) 71 dlon_lic(:)=lon_lic(:,1); IF(MAXVAL(dlon_lic)>pi) dlon_lic=dlon_lic*pi/180. 72 dlat_lic(:)=lat_lic(1,:); IF(MAXVAL(dlat_lic)>pi) dlat_lic=dlat_lic*pi/180. 73 DEALLOCATE(lon_lic,lat_lic); ALLOCATE(flic_tmp(iip1,jjp1)) 74 CALL grille_m(dlon_lic,dlat_lic,fraclic,rlonv(1:iim),rlatu,flic_tmp(1:iim,:)) 75 flic_tmp(iip1,:)=flic_tmp(1,:) 76 77 !--- To the physical grid 78 pctsrf(:,:) = 0. 79 CALL gr_dyn_fi(1, iip1, jjp1, klon, flic_tmp, pctsrf(:,is_lic)) 80 DEALLOCATE(flic_tmp) 81 82 !--- Adequation with soil/sea mask 83 WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0. 84 WHERE(zmasq(:)<EPSFRA) pctsrf(:,is_lic)=0. 85 pctsrf(:,is_ter)=zmasq(:) 86 DO ji=1,klon 87 IF(zmasq(ji)>EPSFRA) THEN 88 IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN 89 pctsrf(ji,is_lic)=zmasq(ji) 90 pctsrf(ji,is_ter)=0. 91 ELSE 92 pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic) 93 IF(pctsrf(ji,is_ter)<EPSFRA) THEN 94 pctsrf(ji,is_ter)=0. 95 pctsrf(ji,is_lic)=zmasq(ji) 96 END IF 97 END IF 98 END IF 99 END DO 100 101 102 !--- Option no_ter_antartique removes all land fractions souther than 60S. 103 !--- Land ice is set instead of the land fractions on these latitudes. 104 !--- The ocean and sea-ice fractions are not changed. 105 no_ter_antartique=.FALSE. 106 CALL getin_p('no_ter_antartique',no_ter_antartique) 107 WRITE(lunout,*)"no_ter_antartique=",no_ter_antartique 108 IF (no_ter_antartique) THEN 109 ! Remove all land fractions souther than 60S and set land-ice instead 110 WRITE(lunout,*) "Remove land fractions souther than 60deg south by increasing" 111 WRITE(lunout,*) "the continental ice fractions. No land can now be found at Antartic." 112 DO ji=1, klon 113 IF (latitude_deg(ji)<-60.0) THEN 114 pctsrf(ji,is_lic) = pctsrf(ji,is_lic) + pctsrf(ji,is_ter) 115 pctsrf(ji,is_ter) = 0 65 !--- Read and interpolate on model T-grid soil fraction and soil ice fraction. 66 CALL flininfo(icefname, iml_lic, jml_lic, llm_tmp, ttm_tmp, fid) 67 ALLOCATE(lat_lic(iml_lic,jml_lic),lon_lic(iml_lic,jml_lic)) 68 ALLOCATE(fraclic(iml_lic,jml_lic)) 69 CALL flinopen(icefname, .FALSE., iml_lic, jml_lic, llm_tmp, & 70 & lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt, fid) 71 CALL flinget(fid, icevar, iml_lic, jml_lic, llm_tmp, ttm_tmp, 1,1, fraclic) 72 CALL flinclo(fid) 73 WRITE(lunout,*)'landice dimensions: iml_lic, jml_lic : ',iml_lic,jml_lic 74 75 ALLOCATE(dlon_lic(iml_lic),dlat_lic(jml_lic)) 76 dlon_lic(:)=lon_lic(:,1); IF(MAXVAL(dlon_lic)>pi) dlon_lic=dlon_lic*pi/180. 77 dlat_lic(:)=lat_lic(1,:); IF(MAXVAL(dlat_lic)>pi) dlat_lic=dlat_lic*pi/180. 78 DEALLOCATE(lon_lic,lat_lic); ALLOCATE(flic_tmp(iip1,jjp1)) 79 CALL grille_m(dlon_lic,dlat_lic,fraclic,rlonv(1:iim),rlatu,flic_tmp(1:iim,:)) 80 flic_tmp(iip1,:)=flic_tmp(1,:) 81 82 !--- To the physical grid 83 pctsrf(:,:) = 0. 84 CALL gr_dyn_fi(1, iip1, jjp1, klon, flic_tmp, pctsrf(:,is_lic)) 85 DEALLOCATE(flic_tmp) 86 87 !--- Adequation with soil/sea mask 88 WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0. 89 WHERE(zmasq(:)<EPSFRA) pctsrf(:,is_lic)=0. 90 pctsrf(:,is_ter)=zmasq(:) 91 DO ji=1,klon 92 IF(zmasq(ji)>EPSFRA) THEN 93 IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN 94 pctsrf(ji,is_lic)=zmasq(ji) 95 pctsrf(ji,is_ter)=0. 96 ELSE 97 pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic) 98 IF(pctsrf(ji,is_ter)<EPSFRA) THEN 99 pctsrf(ji,is_ter)=0. 100 pctsrf(ji,is_lic)=zmasq(ji) 101 END IF 102 END IF 116 103 END IF 117 104 END DO 105 106 107 !--- Option no_ter_antartique removes all land fractions souther than 60S. 108 !--- Land ice is set instead of the land fractions on these latitudes. 109 !--- The ocean and sea-ice fractions are not changed. 110 no_ter_antartique=.FALSE. 111 CALL getin_p('no_ter_antartique',no_ter_antartique) 112 WRITE(lunout,*)"no_ter_antartique=",no_ter_antartique 113 IF (no_ter_antartique) THEN 114 ! Remove all land fractions souther than 60S and set land-ice instead 115 WRITE(lunout,*) "Remove land fractions souther than 60deg south by increasing" 116 WRITE(lunout,*) "the continental ice fractions. No land can now be found at Antartic." 117 DO ji=1, klon 118 IF (latitude_deg(ji)<-60.0) THEN 119 pctsrf(ji,is_lic) = pctsrf(ji,is_lic) + pctsrf(ji,is_ter) 120 pctsrf(ji,is_ter) = 0 121 END IF 122 END DO 123 END IF 124 125 ELSE 126 ! landice_opt=2 and higher 127 WRITE(lunout,*) 'No landice is attributed is_lic sub-surface because landice_opt=2 or higher.' 128 WRITE(lunout,*) 'This means that the land model will handel land ice as well as all other land areas.' 129 pctsrf(:,is_ter) = zmasq(:) 130 pctsrf(:,is_lic) = 0.0 118 131 END IF 119 120 132 121 133 !--- Sub-surface ocean and sea ice (sea ice set to zero for start). -
LMDZ6/branches/Ocean_skin/libf/dynphy_lonlat/phylmd/limit_netcdf.F90
r3811 r4368 424 424 IF(NF90_GET_ATT(ncid, varid, 'calendar', cal_in)/=NF90_NOERR) THEN 425 425 SELECT CASE(mode) 426 CASE('RUG', 'ALB'); cal_in='360 d'426 CASE('RUG', 'ALB'); cal_in='360_day' 427 427 CASE('SIC', 'SST'); cal_in='gregorian' 428 428 END SELECT … … 492 492 !--- DROPPED FOR BCS DATA (FRACTIONS CAN BE HIGHER THAN 1) 493 493 IF(ll.AND.ix_sic/=1.AND.mode=='SIC') & 494 CALL abort_physic(mode,'unrealistic '//TRIM(mode)//' found: '//TRIM(str) )494 CALL abort_physic(mode,'unrealistic '//TRIM(mode)//' found: '//TRIM(str), 1) 495 495 496 496 END IF … … 641 641 ALLOCATE(champo(klon, ndays)) 642 642 DO k=1, ndays 643 CALL gr_dyn_fi(1, iip1, jjp1, klon, champan(1, 1, k), champo( 1, k))643 CALL gr_dyn_fi(1, iip1, jjp1, klon, champan(1, 1, k), champo(:, k)) 644 644 END DO 645 645 DEALLOCATE(champan)
Note: See TracChangeset
for help on using the changeset viewer.