!+ passes climate sea-surface-temperatures to atmosphere !+ $Id: clsst.f90,v 1.12 1999/07/23 08:21:19 m214030 Exp $ SUBROUTINE clsst 5: ! Description: ! ! Passes climate sea-surface-temperatures to atmosphere ! 10: ! Method: ! ! This subroutine calculates the sea-surface-temperatures for ! each time step and updates tsm and tsm1m. ! 15: ! *clsst* is called from *gpc*. ! ! Authors: ! ! U. Schlese, DKRZ, January 1993, original source 20: ! L. Kornblueh, MPI, May 1998, f90 rewrite ! U. Schulzweida, MPI, May 1998, f90 rewrite ! ! for more details see file AUTHORS ! 25: USE mo_memory_g3a, ONLY: auxil1m, auxil2m, slmm, tsm, tsm1m, geospm USE mo_sst, ONLY: sst USE mo_control, ONLY: dtime, lsstadj, ncbase, nrow, ntbase USE mo_start_dataset, ONLY: nstart, nstep 30: USE mo_physc2, ONLY: ctfreez USE mo_rad_switches, ONLY: nmonth USE mo_constants, ONLY: dayl, g, yearl USE mo_year, ONLY: cd2dat, cd2dy USE mo_decomposition, ONLY: dc=>local_decomposition 35: IMPLICIT NONE ! Local scalars: REAL :: zcor, zdayl, zdt, zgam, zmnsec, zmonthl, zsec, zts, zw1, zw2, & 40: & zyearl, zyrsec INTEGER :: id, iday, idayl, im, imm1, imomid, imp1, jrow, iy, & iyearl, jl, jn, nobase, nglon ! Intrinsic functions 45: INTRINSIC MAX, MIN, MOD, NINT ! Executable Statements 50: nglon = dc% nglon ! Set parameters zdayl = dayl zyearl = yearl 55: zmonthl = 30. idayl = NINT(dayl) iyearl = NINT(yearl) zyrsec = yearl*dayl 60: zmnsec = 30*dayl imomid = 15 zdt = 0.01 jrow = nrow(2) 65: !-- 1. Update temperatures !-- 1.1 Annual cycle 70: IF (nmonth==0) THEN ! Determine date within the year CALL cd2dy(ncbase,nobase,iy) 75: iday = ncbase + (ntbase+dtime*nstep)/dayl + 1.E-12 CALL cd2dat(iday,id,im,iy) imp1 = im + 1 80: imm1 = im - 1 zsec = MOD((nobase-1)*idayl+(ntbase+nstep*dtime),zyrsec) zsec = MOD(zsec,zmnsec) 85: ! First half of month IF (id<=imomid) THEN zw1 = zsec/(zmonthl*zdayl) + 0.5 zw2 = 1. - zw1 90: DO jn = 1, nglon zts = zw1*sst(jn,jrow,im) + zw2*sst(jn,jrow,imm1) IF (slmm(jn,jrow)<=0.5) THEN IF (sst(jn,jrow,im)<=ctfreez) THEN tsm(jn,jrow) = MIN(zts,ctfreez-zdt) 95: tsm1m(jn,jrow) = MIN(zts,ctfreez-zdt) ELSE tsm(jn,jrow) = MAX(zts,ctfreez+zdt) tsm1m(jn,jrow) = MAX(zts,ctfreez+zdt) END IF 100: END IF END DO ! Second half of month 105: ELSE zw2 = zsec/(zmonthl*zdayl) - 0.5 zw1 = 1. - zw2 DO jn = 1, nglon zts = zw1*sst(jn,jrow,im) + zw2*sst(jn,jrow,imp1) 110: IF (slmm(jn,jrow)<0.5) THEN IF (sst(jn,jrow,im)<=ctfreez) THEN tsm(jn,jrow) = MIN(zts,ctfreez-zdt) tsm1m(jn,jrow) = MIN(zts,ctfreez-zdt) ELSE 115: tsm(jn,jrow) = MAX(zts,ctfreez+zdt) tsm1m(jn,jrow) = MAX(zts,ctfreez+zdt) END IF END IF END DO 120: END IF ELSE !-- 1.2 Perpetual month 125: im = nmonth DO jn = 1, nglon IF (slmm(jn,jrow)<=0.5) THEN tsm(jn,jrow) = sst(jn,jrow,im) tsm1m(jn,jrow) = tsm(jn,jrow) 130: END IF END DO END IF !-- 1.3 Adjust sst to sea surface "orography". 135: IF (lsstadj) THEN ! Lapse rate: zgam = 1./100. zcor = zgam/g 140: DO jl = 1, nglon IF (slmm(jl,jrow)<0.5 .AND. tsm(jl,jrow)>ctfreez) THEN tsm(jl,jrow) = tsm(jl,jrow) - geospm(jl,jrow)*zcor tsm1m(jl,jrow) = tsm(jl,jrow) 145: END IF END DO END IF !-- 2. Initialisation of seaice skin-temperature 150: IF (nstep==nstart) THEN auxil1m(:,jrow) = tsm(:,jrow) auxil2m(:,jrow) = tsm(:,jrow) 155: END IF RETURN END SUBROUTINE clsstback to top
Info Section uses: mo_constants, mo_control, mo_decomposition, mo_memory_g3a, mo_physc2 mo_rad_switches, mo_sst, mo_start_dataset, mo_year calls: cd2dat, cd2dy
HTML derived from FORTRAN source by f2html.pl v0.3 (C) 1997,98 Beroud Jean-Marc.