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 12394 – NEMO

Changeset 12394


Ignore:
Timestamp:
2020-02-18T10:44:02+01:00 (4 years ago)
Author:
dancopsey
Message:

Fix compile and XIOS errors.

Location:
NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/cfgs/SHARED/field_def_nemo-ice.xml

    r12379 r12394  
    178178          <field id="icettop_cat"  long_name="Ice/snow surface temperature per category"         unit="degC"   grid_ref="grid_T_3D_ncatice" /> 
    179179          <field id="iceapnd_cat"  long_name="Ice melt pond concentration per category"          unit="%"      grid_ref="grid_T_3D_ncatice" />  
     180          <!-- 
    180181          <field id="icehpnd_cat"  long_name="Ice melt pond thickness per category"              unit="m"      grid_ref="grid_T_3D_ncatice" />  
     182          --> 
    181183          <field id="iceafpnd_cat" long_name="Ice melt pond fraction per category"               unit="m"      grid_ref="grid_T_3D_ncatice" />  
    182184          <field id="icehlid_cat"  long_name="Ice melt pond lid thickness per category"          unit="m"      grid_ref="grid_T_3D_ncatice" /> 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icedyn_rdgrft.F90

    r12379 r12394  
    500500      REAL(wp)                  ::   airdg1, oirdg1, aprdg1, virdg1, sirdg1 
    501501      REAL(wp)                  ::   airft1, oirft1, aprft1 
    502       REAL(wp), DIMENSION(jpij) ::   airdg2, oirdg2, aprdg2, virdg2, sirdg2, vsrdg, vprdg  ! area etc of new ridges 
    503       REAL(wp), DIMENSION(jpij) ::   airft2, oirft2, aprft2, virft , sirft , vsrft, vprft  ! area etc of rafted ice 
     502      REAL(wp), DIMENSION(jpij) ::   airdg2, oirdg2, aprdg2, virdg2, sirdg2, vsrdg, vprdg, lhprdg  ! area etc of new ridges 
     503      REAL(wp), DIMENSION(jpij) ::   airft2, oirft2, aprft2, virft , sirft , vsrft, vprft, lhprft  ! area etc of rafted ice 
    504504      ! 
    505505      REAL(wp), DIMENSION(jpij) ::   ersw             ! enth of water trapped into ridges 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icerst.F90

    r12379 r12394  
    219219         lh_ip(:,:,:) = 0._wp 
    220220      ENDIF 
     221      WRITE(numout,*) 'icerst: lh_ip(42,26,1) = ',lh_ip(42,26,1) 
    221222      ! Snow enthalpy 
    222223      DO jk = 1, nlay_s 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icethd_pnd.F90

    r12382 r12394  
    151151 
    152152      ! Define time-independent field for use in refreezing 
    153       omega_dt = 2.0_wp * rcnd_i * rdtice / (rLfus * rhow) 
     153      omega_dt = 2.0_wp * rcnd_i * rdt_ice / (rLfus * rhow) 
    154154 
    155155      DO ji = 1, npti 
     
    167167            h_ip_1d(ji)      = 0._wp 
    168168            lh_ip_1d(ji)     = 0._wp 
     169 
     170            actual_mlt = 0._wp 
     171            actual_frz = 0._wp 
    169172            !                                                     !--------------------------------! 
    170173         ELSE                                                     ! Case ice thickness >= rn_himin ! 
     
    190193                
    191194               ! The following equation is a rearranged form of: 
    192                ! lid_thickness_end - lid_thickness_start = rcnd_i * t_grad * rdtice / (0.5*(lid_thickness_end + lid_thickness_start) * rLfus * rhow) 
     195               ! lid_thickness_end - lid_thickness_start = rcnd_i * t_grad * rdt_ice / (0.5*(lid_thickness_end + lid_thickness_start) * rLfus * rhow) 
    193196               ! where: lid_thickness_start = lh_ip_1d(ji) 
    194197               !        lid_thickness_end = lh_ip_end 
     
    209212            END IF 
    210213 
    211             ! melt pond mass flux diagnostic (melt only) 
    212             zfac = actual_mlt * a_i_1d(ji * rhow * r1_rdtice 
    213             wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - zfac 
    214             ! 
    215             ! adjust ice/snow melting flux to balance melt pond flux (>0) 
    216             zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) ) 
    217             wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) * (1._wp + zdum) 
    218             wfx_sum_1d(ji)     = wfx_sum_1d(ji)     * (1._wp + zdum) 
     214            ! melt pond mass flux (<0) 
     215            IF( zdv_mlt > 0._wp ) THEN 
     216               zfac = actual_mlt * a_i_1d(ji) * rhow * r1_rdtice 
     217               wfx_pnd_1d(ji) = wfx_pnd_1d(ji) - zfac 
     218               ! 
     219               ! adjust ice/snow melting flux to balance melt pond flux (>0) 
     220               zdum = zfac / ( wfx_snw_sum_1d(ji) + wfx_sum_1d(ji) ) 
     221               wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) * (1._wp + zdum) 
     222               wfx_sum_1d(ji)     = wfx_sum_1d(ji)     * (1._wp + zdum) 
     223            ENDIF 
    219224            ! 
    220225            ! Make sure pond volume or lid thickness has not gone negative 
     
    243248            write(numout,*)'icethd_pnd: a_i_1d(ji), v_ip_1d(ji), t_su_1d(ji), zfr_mlt, zdv_mlt = ',a_i_1d(ji), ' ', v_ip_1d(ji), ' ', t_su_1d(ji), ' ', zfr_mlt, ' ', zdv_mlt 
    244249            write(numout,*)'icethd_pnd: meltt = ', -( dh_i_sum(ji)*rhoi + dh_s_mlt(ji)*rhos ) / rhoi 
     250            write(numout,*)'icethd_pnd: lh_ip_1d(ji), actual_mlt, actual_frz, t_su_1d(ji) = ',lh_ip_1d(ji), ' ', actual_mlt, ' ', actual_frz, ' ', t_su_1d(ji) 
    245251         END IF 
    246252 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/iceupdate.F90

    r12382 r12394  
    279279      IF( iom_use('hfxcndbot'  ) )   CALL iom_put( "hfxcndbot"  , SUM( qcn_ice_bot * a_i_b, dim=3 ) )   ! Bottom conduction flux 
    280280      IF( iom_use('hfxcndtop'  ) )   CALL iom_put( "hfxcndtop"  , SUM( qcn_ice_top * a_i_b, dim=3 ) )   ! Surface conduction flux 
    281       IF( iom_use('hfxcndcpl'  ) )   CALL iom_put( "hfxcndcpl"  , SUM( qcn_ice * a_i_b, dim=3 ) )       ! Conduction flux we are giving it 
     281      ! IF( iom_use('hfxcndcpl'  ) )   CALL iom_put( "hfxcndcpl"  , SUM( qcn_ice * a_i_b, dim=3 ) )       ! Conduction flux we are giving it 
    282282 
    283283      ! diags 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/icewri.F90

    r12379 r12394  
    155155      IF( iom_use('iceconc_cat' ) )   CALL iom_put( "iceconc_cat" , a_i * zmsk00l                                              )   ! area for categories 
    156156      IF( iom_use('icethic_cat' ) )   CALL iom_put( "icethic_cat" , h_i * zmsk00l                                              )   ! thickness for categories 
    157       IF( iom_use('icevol_cat'  ) )   CALL iom_put( "icevol_cat" , v_i * zmsk00l                                               )   ! volume for categories 
     157      ! IF( iom_use('icevol_cat'  ) )   CALL iom_put( "icevol_cat" , v_i * zmsk00l                                               )   ! volume for categories 
    158158      IF( iom_use('snwthic_cat' ) )   CALL iom_put( "snwthic_cat" , h_s * zmsksnl                                              )   ! snow depth for categories 
    159159      IF( iom_use('icesalt_cat' ) )   CALL iom_put( "icesalt_cat" , s_i * zmsk00l                                              )   ! salinity for categories 
     
    164164      IF( iom_use('icebrv_cat'  ) )   CALL iom_put( "icebrv_cat"  ,   bv_i * 100.  * zmsk00l                                   )   ! brine volume 
    165165      IF( iom_use('iceapnd_cat' ) )   CALL iom_put( "iceapnd_cat" ,   a_ip         * zmsk00l                                   )   ! melt pond frac for categories 
    166       IF( iom_use('icehpnd_cat' ) )   CALL iom_put( "icehpnd_cat" ,   h_ip         * zmsk00l                                   )   ! melt pond frac for categories 
     166      ! IF( iom_use('icehpnd_cat' ) )   CALL iom_put( "icehpnd_cat" ,   h_ip         * zmsk00l                                   )   ! melt pond frac for categories 
    167167      IF( iom_use('iceafpnd_cat') )   CALL iom_put( "iceafpnd_cat",   a_ip_frac    * zmsk00l                                   )   ! melt pond frac for categories 
    168       IF( iom_uce('icehlid_cat' ) )   CALL iom_put( "icehlid_cat",    lh_ip        * zmsk00l                                   )   ! melt pond lid thickness for categories 
     168      ! IF( iom_use('icehlid_cat' ) )   CALL iom_put( "icehlid_cat",    lh_ip        * zmsk00l                                   )   ! melt pond lid thickness for categories 
    169169 
    170170      !------------------ 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/OCE/BDY/bdyice.F90

    r11081 r12394  
    172172                  a_ip(ji,jj,  jl) = 0._wp                            ! pond concentration 
    173173                  v_ip(ji,jj,  jl) = 0._wp                            ! pond volume 
     174                  lh_ip(ji,jj, jl) = 0._wp                            ! pond lid thickness 
    174175                  t_su(ji,jj,  jl) = rn_ice_tem(jbdy)                 ! temperature surface 
    175176                  t_s (ji,jj,:,jl) = rn_ice_tem(jbdy)                 ! temperature snw 
     
    183184                  a_ip(ji,jj,  jl) = a_ip(ib,jb,  jl) ! pond concentration 
    184185                  v_ip(ji,jj,  jl) = v_ip(ib,jb,  jl) ! pond volume 
     186                  lh_ip(ji,jj, jl) = lh_ip(ib,jb, jl) ! pond lid thickness 
    185187                  t_su(ji,jj,  jl) = t_su(ib,jb,  jl) ! temperature surface 
    186188                  t_s (ji,jj,:,jl) = t_s (ib,jb,:,jl) ! temperature snw 
     
    222224               a_ip(ji,jj,  jl) = 0._wp 
    223225               v_ip(ji,jj,  jl) = 0._wp 
     226               lh_ip(ji,jj, jl) = 0._wp 
    224227               t_su(ji,jj,  jl) = rt0 
    225228               t_s (ji,jj,:,jl) = rt0 
     
    253256      CALL lbc_bdy_lnk( 'bdyice', a_ip(:,:,:)  , 'T', 1., jbdy ) 
    254257      CALL lbc_bdy_lnk( 'bdyice', v_ip(:,:,:)  , 'T', 1., jbdy ) 
     258      CALL lbc_bdy_lnk( 'bdyice', lh_ip(:,:,:) , 'T', 1., jbdy ) 
    255259      CALL lbc_bdy_lnk( 'bdyice', s_i (:,:,:)  , 'T', 1., jbdy ) 
    256260      CALL lbc_bdy_lnk( 'bdyice', t_su(:,:,:)  , 'T', 1., jbdy ) 
  • NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/OCE/SBC/sbccpl.F90

    r12382 r12394  
    23482348            CASE( 'yes' )   
    23492349 
     2350               write(numout,*) 'sbccpl: lh_ip(42,26,1) = ',lh_ip(42,26,1) 
     2351 
    23502352               ! Calculate how much meltpond is exposed (not under a frozen lid) 
    23512353               lfrac_pnd(:,:,1:jpl) = 1.0 
     
    23592361               ztmp3(:,:,1:jpl) =  a_ip_frac(:,:,1:jpl) * lfrac_pnd(:,:,1:jpl) 
    23602362               ztmp4(:,:,1:jpl) =  h_ip(:,:,1:jpl) 
     2363 
     2364               write(numout,*) 'sbccpl: lfrac_pnd(42,26,1), a_ip_frac(42,26,1), ztmp3(42,26,1) = ',lfrac_pnd(42,26,1), a_ip_frac(42,26,1), ztmp3(42,26,1) 
    23612365            CASE( 'no' )   
    23622366               ztmp3(:,:,:) = 0.0   
Note: See TracChangeset for help on using the changeset viewer.