Changeset 2057 for LMDZ5/trunk
- Timestamp:
- Jun 16, 2014, 4:33:38 PM (10 years ago)
- Location:
- LMDZ5/trunk/libf/phylmd
- Files:
-
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phylmd/conf_phys_m.F90
r2008 r2057 53 53 ! type_ocean: type d'ocean (force, slab, couple) 54 54 ! version_ocean: version d'ocean (opa8/nemo pour type_ocean=couple ou 55 ! sicOBS pour type_ocean=slab)55 ! sicOBS,sicINT,sicNO pour type_ocean=slab) 56 56 ! ok_veget: type de modele de vegetation 57 57 ! ok_journe: sorties journalieres … … 1933 1933 IF (type_ocean=='slab' .AND. version_ocean=='xxxxxx') THEN 1934 1934 version_ocean='sicOBS' 1935 ELSE IF (type_ocean=='slab' .AND. version_ocean/='sicOBS') THEN 1935 ELSE IF (type_ocean=='slab' .AND. version_ocean/='sicOBS' & 1936 .AND. version_ocean/='sicINT' .AND. version_ocean/='sicNO') THEN 1936 1937 WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean' 1937 1938 CALL abort_gcm('conf_phys','version_ocean not valid',1) -
LMDZ5/trunk/libf/phylmd/dimphy.F90
r1907 r2057 9 9 INTEGER,SAVE :: klevm1 10 10 INTEGER,SAVE :: kflev 11 INTEGER,SAVE :: nslay 11 12 12 !$OMP THREADPRIVATE(klon,kfdia,kidia,kdlon )13 !$OMP THREADPRIVATE(klon,kfdia,kidia,kdlon,nslay) 13 14 REAL,save,allocatable,dimension(:) :: zmasq 14 15 !$OMP THREADPRIVATE(zmasq) … … 23 24 24 25 klon=klon0 25 26 nslay=1 ! Slab, provisoire (F. Codron) 26 27 kdlon=klon 27 28 kidia=1 -
LMDZ5/trunk/libf/phylmd/limit_slab.F90
r1907 r2057 1 1 ! $Header$ 2 2 3 SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, lmt_foce,diff_sst)3 SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst) 4 4 5 5 USE dimphy … … 20 20 INTEGER, INTENT(IN) :: jour ! jour a lire dans l'annee 21 21 REAL , INTENT(IN) :: dtime ! pas de temps de la physique (en s) 22 REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, lmt_foce,diff_sst22 REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, diff_sst 23 23 24 24 ! Locals variables with attribute SAVE 25 25 !**************************************************************************************** 26 REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, foce_save27 !$OMP THREADPRIVATE(bils_save, foce_save)26 REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, diff_sst_save 27 !$OMP THREADPRIVATE(bils_save, diff_sst_save) 28 28 29 29 ! Locals variables … … 32 32 INTEGER :: nvarid, nid, ierr, i 33 33 INTEGER, DIMENSION(2) :: start, epais 34 REAL, DIMENSION(klon_glo):: bils_glo, foce_glo,sst_l_glo, sst_lp1_glo, diff_sst_glo34 REAL, DIMENSION(klon_glo):: bils_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo 35 35 CHARACTER (len = 20) :: modname = 'limit_slab' 36 LOGICAL :: read_bils,read_sst 36 37 37 38 ! End declaration … … 41 42 lmt_pas = NINT(86400./dtime) 42 43 44 ! F. Codron 5/14: add defaults for bils, diff_sst (0) 43 45 IF (MOD(itime-1, lmt_pas) == 0) THEN ! time to read 44 46 !$OMP MASTER ! Only master thread 45 47 IF (is_mpi_root) THEN ! Only master processus 46 48 print*,'in limit_slab time to read, itime=',itime 49 read_bils=.TRUE. 50 read_sst=.TRUE. 47 51 48 52 ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid) 49 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,& 50 'Pb in opening file limit_slab.nc',1) 53 IF (ierr /= NF90_NOERR) THEN 54 read_bils=.FALSE. 55 read_sst=.FALSE. 56 ELSE ! read file 51 57 52 58 ! La tranche de donnees a lire: … … 57 63 58 64 !**************************************************************************************** 59 ! 2) Read bils and ocean fraction65 ! 2) Read bils and SST tendency 60 66 ! 61 67 !**************************************************************************************** … … 63 69 ! Read bils_glo 64 70 ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid) 65 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <BILS_OCE> is abstent',1) 66 67 ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais) 68 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <BILS_OCE> failed',1) 69 ! 70 ! Read foce_glo 71 ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid) 72 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <FOCE> is abstent',1) 73 74 ierr = NF90_GET_VAR(nid,nvarid,foce_glo,start,epais) 75 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <FOCE> failed',1) 76 ! 71 IF (ierr /= NF90_NOERR) THEN 72 read_bils=.FALSE. 73 ELSE 74 ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais) 75 IF (ierr /= NF90_NOERR) read_bils=.FALSE. 76 END IF 77 77 ! Read sst_glo for this day 78 78 ierr = NF90_INQ_VARID(nid, 'SST', nvarid) 79 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <SST> is abstent',1)80 81 ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)82 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <SST> failed',1)83 79 IF (ierr /= NF90_NOERR) THEN 80 read_sst=.FALSE. 81 ELSE 82 ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais) 83 IF (ierr /= NF90_NOERR) read_sst=.FALSE. 84 84 ! Read sst_glo for one day ahead 85 start(2) = jour + 1 86 IF (start(2) > 360) start(2)=1 87 ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais) 88 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <SST> day+1 failed',1) 89 90 ! Calculate difference in temperature between this day and one ahead 91 DO i=1, klon_glo-1 92 diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i) 93 END DO 94 diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1) 85 start(2) = jour + 1 86 IF (start(2) > 360) start(2)=1 87 ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais) 88 IF (ierr /= NF90_NOERR) read_sst=.FALSE. 89 END IF 95 90 96 91 !**************************************************************************************** 97 ! 5) Close file and distribu ate variables to all processus92 ! 5) Close file and distribute variables to all processus 98 93 ! 99 94 !**************************************************************************************** 100 95 ierr = NF90_CLOSE(nid) 101 96 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1) 97 END IF ! Read File 98 IF (read_sst) THEN 99 ! Calculate difference in temperature between this day and one ahead 100 ! DO i=1, klon_glo-1 101 ! diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i) 102 ! END DO 103 ! diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1) 104 DO i=1, klon_glo 105 diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i) 106 END DO 107 END IF !read_sst 102 108 ENDIF ! is_mpi_root 103 109 … … 105 111 106 112 IF (.NOT. ALLOCATED(bils_save)) THEN 107 ALLOCATE(bils_save(klon), foce_save(klon), stat=ierr)113 ALLOCATE(bils_save(klon), diff_sst_save(klon), stat=ierr) 108 114 IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1) 109 115 END IF 110 116 111 CALL Scatter(bils_glo, bils_save) 112 CALL Scatter(foce_glo, foce_save) 113 CALL Scatter(diff_sst_glo, diff_sst) 117 ! Giveddefault values if needed 118 IF (read_bils) THEN 119 CALL Scatter(bils_glo, bils_save) 120 ELSE 121 bils_save(:)=0. 122 END IF 123 IF (read_sst) THEN 124 CALL Scatter(diff_sst_glo, diff_sst_save) 125 ELSE 126 diff_sst_save(:)=0. 127 END IF 114 128 115 ELSE ! not time to read116 diff_sst(:) = 0.117 129 ENDIF ! time to read 118 130 119 131 lmt_bils(:) = bils_save(:) 120 lmt_foce(:) = foce_save(:)132 diff_sst(:) = diff_sst_save(:) 121 133 122 134 END SUBROUTINE limit_slab -
LMDZ5/trunk/libf/phylmd/ocean_slab_mod.F90
r1907 r2057 5 5 ! "ocean=slab". 6 6 ! 7 8 USE dimphy 9 USE indice_sol_mod 10 7 11 IMPLICIT NONE 8 12 PRIVATE 9 PUBLIC :: ocean_slab_frac, ocean_slab_noice 13 PUBLIC :: ocean_slab_init, ocean_slab_frac, ocean_slab_noice!, ocean_slab_ice 14 15 INTEGER, PRIVATE, SAVE :: cpl_pas 16 !$OMP THREADPRIVATE(cpl_pas) 17 REAL, PRIVATE, SAVE :: cyang 18 !$OMP THREADPRIVATE(cyang) 19 REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: slabh 20 !$OMP THREADPRIVATE(slabh) 21 REAL, ALLOCATABLE, DIMENSION(:,:), PUBLIC, SAVE :: tslab 22 !$OMP THREADPRIVATE(tslab) 23 REAL, ALLOCATABLE, DIMENSION(:,:), PRIVATE, SAVE :: pctsrf 24 !$OMP THREADPRIVATE(pctsrf) 25 REAL, ALLOCATABLE, DIMENSION(:), PUBLIC, SAVE :: slab_bils 26 !$OMP THREADPRIVATE(slab_bils) 27 REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: bils_cum 28 !$OMP THREADPRIVATE(bils_cum) 10 29 11 30 CONTAINS … … 13 32 !**************************************************************************************** 14 33 ! 15 SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified) 16 17 USE dimphy 34 SUBROUTINE ocean_slab_init(dtime, pctsrf_rst) 35 !, seaice_rst etc 36 37 use IOIPSL 38 39 INCLUDE "iniprint.h" 40 ! For ok_xxx vars (Ekman...) 41 INCLUDE "clesphys.h" 42 43 ! Input variables 44 !**************************************************************************************** 45 REAL, INTENT(IN) :: dtime 46 ! Variables read from restart file 47 REAL, DIMENSION(klon, nbsrf), INTENT(IN) :: pctsrf_rst 48 49 ! Local variables 50 !**************************************************************************************** 51 INTEGER :: error 52 CHARACTER (len = 80) :: abort_message 53 CHARACTER (len = 20) :: modname = 'ocean_slab_intit' 54 55 !**************************************************************************************** 56 ! Allocate surface fraction read from restart file 57 !**************************************************************************************** 58 ALLOCATE(pctsrf(klon,nbsrf), stat = error) 59 IF (error /= 0) THEN 60 abort_message='Pb allocation tmp_pctsrf_slab' 61 CALL abort_gcm(modname,abort_message,1) 62 ENDIF 63 pctsrf(:,:) = pctsrf_rst(:,:) 64 65 !**************************************************************************************** 66 ! Allocate local variables 67 !**************************************************************************************** 68 ALLOCATE(slab_bils(klon), stat = error) 69 IF (error /= 0) THEN 70 abort_message='Pb allocation slab_bils' 71 CALL abort_gcm(modname,abort_message,1) 72 ENDIF 73 slab_bils(:) = 0.0 74 ALLOCATE(bils_cum(klon), stat = error) 75 IF (error /= 0) THEN 76 abort_message='Pb allocation slab_bils_cum' 77 CALL abort_gcm(modname,abort_message,1) 78 ENDIF 79 bils_cum(:) = 0.0 80 81 ! Layer thickness 82 ALLOCATE(slabh(nslay), stat = error) 83 IF (error /= 0) THEN 84 abort_message='Pb allocation slabh' 85 CALL abort_gcm(modname,abort_message,1) 86 ENDIF 87 slabh(1)=50. 88 ! cyang = 1/heat capacity of top layer (rho.c.H) 89 cyang=1/(slabh(1)*4.228e+06) 90 91 ! cpl_pas periode de couplage avec slab (update tslab, pctsrf) 92 ! pour un calcul à chaque pas de temps, cpl_pas=1 93 cpl_pas = NINT(86400./dtime * 1.0) ! une fois par jour 94 CALL getin('cpl_pas',cpl_pas) 95 print *,'cpl_pas',cpl_pas 96 END SUBROUTINE ocean_slab_init 97 ! 98 !**************************************************************************************** 99 ! 100 SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf_chg, is_modified) 101 18 102 USE limit_read_mod 19 103 USE surface_data 20 USE indice_sol_mod21 104 22 105 ! INCLUDE "clesphys.h" … … 27 110 INTEGER, INTENT(IN) :: jour ! jour a lire dans l'annee 28 111 REAL , INTENT(IN) :: dtime ! pas de temps de la physique (en s) 29 REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf ! sub-surface fraction112 REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf_chg ! sub-surface fraction 30 113 LOGICAL, INTENT(OUT) :: is_modified ! true if pctsrf is modified at this time step 31 114 32 115 ! Local variables 33 116 !**************************************************************************************** 34 CHARACTER (len = 80) :: abort_message 35 CHARACTER (len = 20) :: modname = 'ocean_slab_frac' 36 37 38 IF (version_ocean == 'sicOBS') THEN 39 CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified) 117 118 IF (version_ocean == 'sicOBS'.OR. version_ocean == 'sicNO') THEN 119 CALL limit_read_frac(itime, dtime, jour, pctsrf_chg, is_modified) 40 120 ELSE 41 abort_message='Ocean slab model without forced sea-ice fractions has to be rewritten!!!' 42 CALL abort_gcm(modname,abort_message,1) 43 ! Here should sea-ice/ocean fraction either be calculated or returned if saved as a module varaiable 44 ! (in the case the new fractions are calculated in ocean_slab_ice or ocean_slab_noice subroutines). 121 pctsrf_chg(:,:)=pctsrf(:,:) 122 is_modified=.TRUE. 45 123 END IF 46 124 … … 57 135 radsol, snow, agesno, & 58 136 qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & 59 tsurf_new, dflux_s, dflux_l, lmt_bils)137 tsurf_new, dflux_s, dflux_l, qflux) 60 138 61 USE dimphy62 139 USE calcul_fluxs_mod 63 USE indice_sol_mod140 USE surface_data 64 141 65 142 INCLUDE "iniprint.h" … … 95 172 REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new 96 173 REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l 97 REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils174 REAL, DIMENSION(klon), INTENT(OUT) :: qflux 98 175 99 176 ! Local variables 100 177 !**************************************************************************************** 101 INTEGER :: i 178 INTEGER :: i,ki 102 179 REAL, DIMENSION(klon) :: cal, beta, dif_grnd 103 REAL, DIMENSION(klon) :: lmt_bils_oce, lmt_foce, diff_sst180 REAL, DIMENSION(klon) :: diff_sst, lmt_bils 104 181 REAL, DIMENSION(klon) :: u0, v0 105 182 REAL, DIMENSION(klon) :: u1_lay, v1_lay 106 REAL :: calc_bils_oce, deltat107 REAL, PARAMETER :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)108 183 109 184 !**************************************************************************************** … … 136 211 flux_u1, flux_v1) 137 212 138 !**************************************************************************************** 139 ! 2) Get global variables lmt_bils and lmt_foce from file limit_slab.nc 140 ! 141 !**************************************************************************************** 142 CALL limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst) ! global pour un processus 143 144 lmt_bils_oce(:) = 0. 145 WHERE (lmt_foce > 0.) 146 lmt_bils_oce = lmt_bils / lmt_foce ! global 147 END WHERE 213 ! Accumulate total fluxes locally 214 slab_bils(:)=0. 215 DO i=1,knon 216 ki=knindex(i) 217 slab_bils(ki)=(fluxlat(i)+fluxsens(i)+radsol(i))*pctsrf(ki,is_oce)/(1.-zmasq(ki)) 218 bils_cum(ki)=bils_cum(ki)+slab_bils(ki) 219 ! Also taux, tauy, saved vars... 220 END DO 221 222 !**************************************************************************************** 223 ! 2) Get global variables lmt_bils and diff_sst from file limit_slab.nc 224 ! 225 !**************************************************************************************** 226 lmt_bils(:)=0. 227 CALL limit_slab(itime, dtime, jour, lmt_bils, diff_sst) ! global pour un processus 228 ! lmt_bils and diff_sst saved by limit_slab 229 qflux(:)=lmt_bils(:)+diff_sst(:)/cyang/86400. 230 ! qflux = total QFlux correction (in W/m2) 148 231 149 232 !**************************************************************************************** 150 233 ! 3) Recalculate new temperature 151 234 ! 152 !**************************************************************************************** 153 DO i = 1, knon 154 calc_bils_oce = radsol(i) + fluxsens(i) + fluxlat(i) 155 deltat = (calc_bils_oce - lmt_bils_oce(knindex(i)))*dtime/cyang +diff_sst(knindex(i)) 156 tsurf_new(i) = tsurf_in(i) + deltat 157 END DO 158 235 !***********************************************o***************************************** 236 tsurf_new=tsurf_in 237 IF (MOD(itime,cpl_pas).EQ.0) THEN ! time to update tslab & fraction 238 ! Compute transport 239 ! Add read QFlux and SST tendency 240 tslab(:,1)=tslab(:,1)+qflux(:)*cyang*dtime*cpl_pas 241 ! Add cumulated surface fluxes 242 tslab(:,1)=tslab(:,1)+bils_cum(:)*cyang*dtime 243 ! Update surface temperature 244 SELECT CASE(version_ocean) 245 CASE('sicNO') 246 DO i=1,knon 247 ki=knindex(i) 248 tsurf_new(i)=tslab(ki,1) 249 END DO 250 CASE('sicOBS') ! check for sea ice or tsurf below freezing 251 DO i=1,knon 252 ki=knindex(i) 253 IF ((tslab(ki,1).LT.t_freeze).OR.(pctsrf(ki,is_sic).GT.epsfra)) THEN 254 tsurf_new(i)=t_freeze 255 tslab(ki,1)=t_freeze 256 ELSE 257 tsurf_new(i)=tslab(ki,1) 258 END IF 259 END DO 260 CASE('sicINT') 261 DO i=1,knon 262 ki=knindex(i) 263 IF (pctsrf(ki,is_sic).LT.epsfra) THEN ! Free of ice 264 IF (tslab(ki,1).GT.t_freeze) THEN 265 tsurf_new(i)=tslab(ki,1) 266 ELSE 267 tsurf_new(i)=t_freeze 268 ! Call new ice routine 269 tslab(ki,1)=t_freeze 270 END IF 271 ELSE ! ice present, tslab update completed in slab_ice 272 tsurf_new(i)=t_freeze 273 END IF !ice free 274 END DO 275 END SELECT 276 bils_cum(:)=0.0! clear cumulated fluxes 277 END IF ! coupling time 159 278 END SUBROUTINE ocean_slab_noice 160 279 ! 161 280 !**************************************************************************************** 162 281 ! 282 ! SUBROUTINE ocean_slab_ice( & 283 ! itime, dtime, jour, knon, knindex, & 284 ! tsurf_in, p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, & 285 ! AcoefH, AcoefQ, BcoefH, BcoefQ, & 286 ! AcoefU, AcoefV, BcoefU, BcoefV, & 287 ! ps, u1, v1, & 288 ! radsol, snow, qsurf, qsol, agesno, tsoil, & 289 ! alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, & 290 ! tsurf_new, dflux_s, dflux_l) 291 ! 292 !**************************************************************************************** 293 ! 1) Flux calculation 294 !**************************************************************************************** 295 ! set beta, cal etc. depends snow / ice surf ? 296 ! calcul_fluxs (sens, lat etc) 297 ! calcul_flux_wind 298 299 !**************************************************************************************** 300 ! 2) Update surface 301 !**************************************************************************************** 302 ! neige, fonte 303 ! flux glace-ocean 304 ! update temperature 305 ! neige precip, evap 306 ! Melt snow & ice from above 307 ! New albedo 308 309 !**************************************************************************************** 310 ! 3) Recalculate new ocean temperature 311 ! Melt / freeze from below 312 !***********************************************o***************************************** 313 314 315 ! END SUBROUTINE ocean_slab_ice 316 ! 317 !**************************************************************************************** 318 ! 319 SUBROUTINE ocean_slab_final 320 !, seaice_rst etc 321 322 ! For ok_xxx vars (Ekman...) 323 INCLUDE "clesphys.h" 324 325 !**************************************************************************************** 326 ! Deallocate module variables 327 ! 328 !**************************************************************************************** 329 IF (ALLOCATED(pctsrf)) DEALLOCATE(pctsrf) 330 IF (ALLOCATED(tslab)) DEALLOCATE(tslab) 331 332 END SUBROUTINE ocean_slab_final 333 163 334 END MODULE ocean_slab_mod -
LMDZ5/trunk/libf/phylmd/phyetat0.F90
r2054 r2057 3 3 SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0) 4 4 5 USE dimphy, only: klon, zmasq, klev 5 USE dimphy, only: klon, zmasq, klev, nslay 6 6 USE iophy, ONLY : init_iophy_new 7 7 USE ocean_cpl_mod, ONLY : ocean_cpl_init … … 21 21 USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl, co2_send 22 22 USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic 23 USE ocean_slab_mod, ONLY: tslab, ocean_slab_init 23 24 24 25 IMPLICIT none … … 40 41 41 42 REAL tsoil(klon, nsoilmx, nbsrf) 42 REAL tslab(klon), seaice(klon)43 43 REAL qsurf(klon, nbsrf) 44 44 REAL qsol(klon) … … 1045 1045 end if 1046 1046 1047 ! Initialize Slab variables 1048 IF ( type_ocean == 'slab' ) THEN 1049 ALLOCATE(tslab(klon,nslay), stat=ierr) 1050 IF (ierr /= 0) CALL abort_gcm & 1051 ('phyetat0', 'pb allocation tslab', 1) 1052 CALL get_field("tslab", tslab, found) 1053 IF (.NOT. found) THEN 1054 PRINT*, "phyetat0: Le champ <tslab> est absent" 1055 PRINT*, "Initialisation a tsol_oce" 1056 DO i=1,nslay 1057 tslab(:,i)=ftsol(:,is_oce) 1058 END DO 1059 END IF 1060 print*, "calling slab_init" 1061 CALL ocean_slab_init(dtime, pctsrf) 1062 END IF ! Slab 1063 1047 1064 ! on ferme le fichier 1048 1065 CALL close_startphy -
LMDZ5/trunk/libf/phylmd/phyredem.F90
r1938 r2057 15 15 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send 16 16 USE indice_sol_mod 17 USE surface_data 18 USE ocean_slab_mod, ONLY : tslab 17 19 18 20 IMPLICIT none … … 33 35 34 36 REAL tsoil(klon, nsoilmx, nbsrf) 35 REAL tslab(klon), seaice(klon)36 37 REAL qsurf(klon, nbsrf) 37 38 REAL qsol(klon) … … 340 341 END IF 341 342 343 ! Restart variables for Slab ocean 344 IF (type_ocean == 'slab') THEN 345 CALL put_field("tslab", "Slab ocean temperature", tslab) 346 END IF 347 342 348 if (ok_gwd_rando) then 343 349 call put_field("du_gwd_rando", & -
LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r2042 r2057 456 456 !(/ ('', i=1, 9) /)) 457 457 TYPE(ctrl_out), SAVE :: o_slab_bils = ctrl_out((/ 1, 1, 10, 10, 10, 10, 11, 11, 11 /), & 458 'slab_bils_oce', 'Bilan au sol sur ocean slab', 'W/m2', (/ ('', i=1, 9) /)) 458 'slab_bils', 'flux atmos - slab ponderes foce', 'W/m2', (/ ('', i=1, 9) /)) 459 TYPE(ctrl_out), SAVE :: o_slab_qflux = ctrl_out((/ 1, 1, 10, 10, 10, 10, 11, 11, 11 /), & 460 'slab_qflux', 'Correction flux slab', 'W/m2', (/ ('', i=1, 9) /)) 461 TYPE(ctrl_out), SAVE :: o_tslab = ctrl_out((/ 1, 1, 10, 10, 10, 10, 11, 11, 11 /), & 462 'tslab', 'Temperature ocean slab', 'K', (/ ('', i=1, 9) /)) 459 463 TYPE(ctrl_out), SAVE :: o_ale_bl = ctrl_out((/ 1, 1, 1, 10, 10, 10, 11, 11, 11 /), & 460 464 'ale_bl', 'ALE BL', 'm2/s2', (/ ('', i=1, 9) /)) -
LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90
r2051 r2057 24 24 ! defined and initialised in phys_output_mod.F90 25 25 26 USE dimphy, only: klon, klev, klevp1 26 USE dimphy, only: klon, klev, klevp1, nslay 27 27 USE control_mod, only: day_step, iphysiq 28 28 USE phys_output_ctrlout_mod, only: o_phis, o_aire, is_ter, is_lic, is_oce, & … … 77 77 o_ale_bl_trig, o_alp_bl_det, & 78 78 o_alp_bl_fluct_m, o_alp_bl_fluct_tke, & 79 o_alp_bl_conv, o_alp_bl_stat, o_slab_bils, & 79 o_alp_bl_conv, o_alp_bl_stat, & 80 o_slab_qflux, o_tslab, o_slab_bils, & 80 81 o_weakinv, o_dthmin, o_cldtau, & 81 82 o_cldemi, o_pr_con_l, o_pr_con_i, & … … 219 220 bils_ec,bils_ech, bils_tke, bils_kinetic, bils_latent, bils_enthalp, & 220 221 itau_con, nfiles, clef_files, nid_files, zvstr_gwd_rando 222 USE ocean_slab_mod, only: tslab, slab_bils 221 223 USE indice_sol_mod, only: nbsrf 222 224 USE infotrac, only: nqtot … … 726 728 ENDIF !(iflag_clos_bl>=1) 727 729 !!! fin nrlmd le 10/04/2012 730 ! Output of slab ocean variables 728 731 IF (type_ocean=='slab ') THEN 729 CALL histwrite_phy(o_slab_bils, slab_wfbils) 732 CALL histwrite_phy(o_slab_qflux, slab_wfbils) 733 CALL histwrite_phy(o_slab_bils, slab_bils) 734 IF (nslay.EQ.1) THEN 735 zx_tmp_fi2d(:)=tslab(:,1) 736 CALL histwrite_phy(o_tslab, zx_tmp_fi2d) 737 ELSE 738 CALL histwrite_phy(o_tslab, tslab) 739 END IF 730 740 ENDIF !type_ocean == force/slab 731 741 CALL histwrite_phy(o_weakinv, weak_inversion) -
LMDZ5/trunk/libf/phylmd/surf_ocean_mod.F90
r1907 r2057 138 138 139 139 !**************************************************************************************** 140 ! fcodron: compute lmt_bils forced case (same as wfbils_oce / 1.-contfracatm) 141 !**************************************************************************************** 142 IF (type_ocean.NE.'slab') THEN 143 lmt_bils(:)=0. 144 DO i=1,knon 145 lmt_bils(knindex(i))=(swnet(i)+lwnet(i)+fluxsens(i)+fluxlat(i)) & 146 *pctsrf(knindex(i),is_oce)/(1.-zmasq(knindex(i))) 147 END DO 148 END IF 149 150 !**************************************************************************************** 140 151 ! Calculate albedo 141 152 ! -
LMDZ5/trunk/libf/phylmd/surf_seaice_mod.F90
r1907 r2057 108 108 tsurf_new, dflux_s, dflux_l) 109 109 110 ELSE IF (type_ocean == 'force' .OR. (type_ocean == 'slab' .AND. version_ocean=='sicOBS')) THEN 110 ! ELSE IF (type_ocean == 'slab'.AND.version_ocean=='sicINT') THEN 111 ! CALL ocean_slab_ice( & 112 ! itime, dtime, jour, knon, knindex, & 113 ! debut, & 114 ! tsurf, p1lay, cdragh, precip_rain, precip_snow, temp_air, spechum,& 115 ! AcoefH, AcoefQ, BcoefH, BcoefQ, & 116 ! ps, u1, v1, & 117 ! radsol, snow, qsurf, qsol, agesno, tsoil, & 118 ! alb1_new, alb2_new, evap, fluxsens, fluxlat, & 119 ! tsurf_new, dflux_s, dflux_l) 120 ! 121 ELSE ! type_ocean=force or slab +sicOBS or sicNO 111 122 CALL ocean_forced_ice( & 112 123 itime, dtime, jour, knon, knindex, & … … 118 129 qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, & 119 130 tsurf_new, dflux_s, dflux_l) 120 121 ELSE IF (type_ocean == 'slab') THEN122 !!$ CALL ocean_slab_ice( &123 !!$ itime, dtime, jour, knon, knindex, &124 !!$ debut, &125 !!$ tsurf, p1lay, cdragh, precip_rain, precip_snow, temp_air, spechum,&126 !!$ AcoefH, AcoefQ, BcoefH, BcoefQ, &127 !!$ ps, u1, v1, pctsrf, &128 !!$ radsol, snow, qsurf, qsol, agesno, tsoil, &129 !!$ alb1_new, alb2_new, evap, fluxsens, fluxlat, &130 !!$ tsurf_new, dflux_s, dflux_l)131 131 132 132 END IF -
LMDZ5/trunk/libf/phylmd/surface_data.F90
r1907 r2057 7 7 REAL, PARAMETER :: tau_gl=86400.*5. 8 8 REAL, PARAMETER :: calsno=1./(2.3867e+06*.15) 9 REAL, PARAMETER :: t_freeze=271.35 10 REAL, PARAMETER :: t_melt=273.15 9 11 10 12 LOGICAL, SAVE :: ok_veget ! true for use of vegetation model ORCHIDEE … … 20 22 21 23 ! if type_ocean=couple : version_ocean=opa8 ou nemo 22 ! if type_ocean=slab : version_ocean=sicOBS 24 ! if type_ocean=slab : version_ocean=sicOBS or sicINT or sicNO 23 25 CHARACTER(len=6), SAVE :: version_ocean 24 26 !$OMP THREADPRIVATE(version_ocean)
Note: See TracChangeset
for help on using the changeset viewer.