New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 3356 for branches/2012/dev_3352_UKMO8_CICE – NEMO

Ignore:
Timestamp:
2012-04-13T15:48:38+02:00 (12 years ago)
Author:
charris
Message:

#953 Changes to give salinity dependence for freezing temperature (except in the fully coupled case when the UM still requires that freezing temperature is fixed as -1.8). More details in ticket.

Location:
branches/2012/dev_3352_UKMO8_CICE/NEMOGCM/NEMO/OPA_SRC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_3352_UKMO8_CICE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r3355 r3356  
    1616   USE domvvl 
    1717   USE phycst, only : rcp, rau0 
     18   USE eosbn2, only : tfreez 
    1819   USE in_out_manager  ! I/O manager 
    1920   USE lib_mpp         ! distributed memory computing library 
     
    4344                flatn_f,fsurfn_f,fcondtopn_f,                    & 
    4445                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   & 
    45                 swvdr,swvdf,swidr,swidf 
     46                swvdr,swvdf,swidr,swidf,Tf 
    4647   USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf 
    4748   USE ice_atmo, only: calc_strair 
     
    146147      !!--------------------------------------------------------------------- 
    147148 
    148       INTEGER  ::   ji, jj, jl                        ! dummy loop indices 
     149      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices 
     150      REAL(wp), DIMENSION(:,:,:), POINTER :: ztmp 
    149151 
    150152      IF( nn_timing == 1 )  CALL timing_start('cice_sbc_init') 
    151153      ! 
     154      CALL wrk_alloc( jpi,jpj,jpk, ztmp ) 
    152155      IF(lwp) WRITE(numout,*)'cice_sbc_init' 
    153156 
     
    171174      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 
    172175 
     176! Set freezing temperatures and ensure consistency between NEMO and CICE  
     177! (-1.8 for fully coupled, salinity dependence otherwise) 
     178! Setting of Tf here or in cice_sbc_in will over-write anything already done in cice_init 
    173179! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart 
     180 
     181      IF (nsbc == 5) THEN 
     182         ztmp(:,:,:)=-1.8 
     183         CALL nemo2cice(ztmp(:,:,1),Tf,'T', 1. )     ! Set in CICE here as won't be updated in cice_sbc_in   
     184      ELSE 
     185         DO jk=1,jpk 
     186            ztmp(:,:,jk)= tfreez(tsn(:,:,jk,jp_sal),fsdepw(:,:,jk)) 
     187         ENDDO 
     188      ENDIF 
     189 
    174190      IF( .NOT. ln_rstart ) THEN 
    175          tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz) 
     191         tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),ztmp) 
    176192         tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem) 
    177193      ENDIF 
     
    198214      CALL lbc_lnk ( fr_iu , 'U', 1. ) 
    199215      CALL lbc_lnk ( fr_iv , 'V', 1. ) 
     216      ! 
     217      CALL wrk_dealloc( jpi,jpj,jpk, ztmp ) 
    200218      ! 
    201219      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_init') 
     
    354372      CALL nemo2cice(ztmp,frain,'T', 1. )  
    355373 
     374! Recalculate freezing temperature and send to CICE except for fully coupled when 
     375! it remains as -1.8 throughout the run 
     376      IF ( nsbc==5 ) THEN 
     377         ztmp(:,:)=-1.8 
     378      ELSE 
     379         ztmp(:,:)=tfreez(sss_m(:,:)) 
     380         CALL nemo2cice(ztmp,Tf,'T', 1. ) 
     381      ENDIF 
     382 
    356383! Freezing/melting potential 
    357384! Calculated over NEMO leapfrog timestep (hence 2*dt) 
    358       nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:,1)*(Tocnfrz-sst_m(:,:))/(2.0*dt) 
    359  
    360       ztmp(:,:) = nfrzmlt(:,:) 
    361       CALL nemo2cice(ztmp,frzmlt,'T', 1. ) 
     385      nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:,1)*(ztmp(:,:)-sst_m(:,:))/(2.0*dt) 
     386      CALL nemo2cice(nfrzmlt,frzmlt,'T', 1. ) 
    362387 
    363388! SST  and SSS 
  • branches/2012/dev_3352_UKMO8_CICE/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90

    r3294 r3356  
    678678 
    679679 
    680    FUNCTION tfreez( psal ) RESULT( ptf ) 
     680   FUNCTION tfreez( psal, ppress ) RESULT( ptf ) 
    681681      !!---------------------------------------------------------------------- 
    682682      !!                 ***  ROUTINE eos_init  *** 
     
    691691      !!---------------------------------------------------------------------- 
    692692      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   psal   ! salinity             [psu] 
     693      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ), OPTIONAL ::   ppress ! pressure             [dBar] 
    693694      ! Leave result array automatic rather than making explicitly allocated 
    694695      REAL(wp), DIMENSION(jpi,jpj)                ::   ptf    ! freezing temperature [Celcius] 
     696      REAL(wp), DIMENSION(jpi,jpj)                ::   zpress ! pressure [dBar] 
    695697      !!---------------------------------------------------------------------- 
    696698      ! 
    697699      ptf(:,:) = ( - 0.0575_wp + 1.710523e-3_wp * SQRT( psal(:,:) )   & 
    698700         &                     - 2.154996e-4_wp *       psal(:,:)   ) * psal(:,:) 
     701 
     702      IF( PRESENT(ppress) ) THEN 
     703         ptf(:,:) = ptf(:,:) - 7.53e-4_wp * ppress(:,:) 
     704      ENDIF 
     705 
    699706      ! 
    700707   END FUNCTION tfreez 
Note: See TracChangeset for help on using the changeset viewer.