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 14299 for NEMO/branches/UKMO/NEMO_4.0.4_icesheet_and_river_coupling/src/OCE/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2021-01-13T17:30:46+01:00 (3 years ago)
Author:
dancopsey
Message:

Merge in NEMO4.0.3 version of this branch from revision 13777 to 13793

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.4_icesheet_and_river_coupling/src/OCE/SBC/sbccpl.F90

    r14075 r14299  
    3636   USE eosbn2         !  
    3737   USE sbcrnf  , ONLY : l_rnfcpl 
     38   USE cpl_rnf_1d, ONLY: nn_cpl_river, cpl_rnf_1d_init, cpl_rnf_1d_to_2d   ! Variables used in 1D river outflow  
    3839   USE sbcisf  , ONLY : l_isfcpl 
    3940#if defined key_cice 
     
    120121   INTEGER, PARAMETER ::   jpr_tauwy  = 56   ! y component of the ocean stress from waves 
    121122   INTEGER, PARAMETER ::   jpr_ts_ice = 57   ! Sea ice surface temp 
    122  
    123    INTEGER, PARAMETER ::   jprcv      = 57   ! total number of fields received   
     123   INTEGER, PARAMETER ::   jpr_grnm   = 58   ! Greenland ice mass  
     124   INTEGER, PARAMETER ::   jpr_antm   = 59   ! Antarctic ice mass  
     125   INTEGER, PARAMETER ::   jpr_rnf_1d = 60   ! 1D river runoff  
     126   INTEGER, PARAMETER ::   jpr_qtr    = 61   ! Transmitted solar 
     127 
     128   INTEGER, PARAMETER ::   jprcv      = 61   ! total number of fields received 
    124129 
    125130   INTEGER, PARAMETER ::   jps_fice   =  1   ! ice fraction sent to the atmosphere 
     
    186191   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_tauw, sn_rcv_dqnsdt, sn_rcv_qsr,  & 
    187192      &             sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf, sn_rcv_ts_ice 
    188    TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf 
     193   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf,      & 
     194                    sn_rcv_grnm, sn_rcv_antm 
    189195   ! Send to waves  
    190196   TYPE(FLD_C) ::   sn_snd_ifrac, sn_snd_crtw, sn_snd_wlev  
     
    277283         &                  sn_rcv_iceflx, sn_rcv_co2   , sn_rcv_mslp ,                                & 
    278284         &                  sn_rcv_icb   , sn_rcv_isf   , sn_rcv_wfreq, sn_rcv_tauw  ,                 & 
    279          &                  sn_rcv_ts_ice 
     285         &                  sn_rcv_ts_ice, sn_rcv_grnm  , sn_rcv_antm  ,                               & 
     286         &                  nn_coupled_iceshelf_fluxes  , ln_iceshelf_init_atmos ,                     & 
     287         &                  rn_greenland_total_fw_flux  , rn_greenland_calving_fraction  ,             & 
     288         &                  rn_antarctica_total_fw_flux , rn_antarctica_calving_fraction ,             & 
     289         &                  rn_iceshelf_fluxes_tolerance 
     290 
    280291      !!--------------------------------------------------------------------- 
    281292      ! 
     
    316327         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')' 
    317328         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')' 
     329         WRITE(numout,*)'      Greenland ice mass              = ', TRIM(sn_rcv_grnm%cldes  ), ' (', TRIM(sn_rcv_grnm%clcat  ), ')'  
     330         WRITE(numout,*)'      Antarctica ice mass             = ', TRIM(sn_rcv_antm%cldes  ), ' (', TRIM(sn_rcv_antm%clcat  ), ')'  
    318331         WRITE(numout,*)'      iceberg                         = ', TRIM(sn_rcv_icb%cldes   ), ' (', TRIM(sn_rcv_icb%clcat   ), ')' 
    319332         WRITE(numout,*)'      ice shelf                       = ', TRIM(sn_rcv_isf%cldes   ), ' (', TRIM(sn_rcv_isf%clcat   ), ')' 
     
    351364         WRITE(numout,*)'                      - orientation   = ', sn_snd_crtw%clvor  
    352365         WRITE(numout,*)'                      - mesh          = ', sn_snd_crtw%clvgrd  
     366         WRITE(numout,*)'  nn_coupled_iceshelf_fluxes          = ', nn_coupled_iceshelf_fluxes 
     367         WRITE(numout,*)'  ln_iceshelf_init_atmos              = ', ln_iceshelf_init_atmos 
     368         WRITE(numout,*)'  rn_greenland_total_fw_flux          = ', rn_greenland_total_fw_flux 
     369         WRITE(numout,*)'  rn_antarctica_total_fw_flux         = ', rn_antarctica_total_fw_flux 
     370         WRITE(numout,*)'  rn_greenland_calving_fraction       = ', rn_greenland_calving_fraction 
     371         WRITE(numout,*)'  rn_antarctica_calving_fraction      = ', rn_antarctica_calving_fraction 
     372         WRITE(numout,*)'  rn_iceshelf_fluxes_tolerance        = ', rn_iceshelf_fluxes_tolerance 
    353373      ENDIF 
    354374 
     
    366386 
    367387      ! default definitions of srcv 
    368       srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1.   ;   srcv(:)%nct = 1 
     388      srcv(:)%laction = .FALSE.  
     389      srcv(:)%clgrid = 'T'  
     390      srcv(:)%nsgn = 1.  
     391      srcv(:)%nct = 1  
     392      srcv(:)%dimensions = 2  
    369393 
    370394      !                                                      ! ------------------------- ! 
     
    485509      !                                                      ! ------------------------- ! 
    486510      srcv(jpr_rnf   )%clname = 'O_Runoff' 
    487       IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN 
    488          srcv(jpr_rnf)%laction = .TRUE. 
     511      srcv(jpr_rnf_1d   )%clname = 'ORunff1D'  
     512      IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' .OR. TRIM( sn_rcv_rnf%cldes ) == 'coupled1d' ) THEN   
     513         IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) srcv(jpr_rnf)%laction = .TRUE.  
     514         IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled1d' ) THEN  
     515            srcv(jpr_rnf_1d)%laction = .TRUE.  
     516            srcv(jpr_rnf_1d)%dimensions = 1 ! 1D field passed through coupler  
     517         END IF  
    489518         l_rnfcpl              = .TRUE.                      ! -> no need to read runoffs in sbcrnf 
    490519         ln_rnf                = nn_components /= jp_iam_sas ! -> force to go through sbcrnf if not sas 
     
    493522      ENDIF 
    494523      ! 
    495       srcv(jpr_cal)%clname = 'OCalving'   ;  IF( TRIM( sn_rcv_cal%cldes) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE. 
     524      srcv(jpr_cal   )%clname = 'OCalving'     
     525      IF( TRIM( sn_rcv_cal%cldes ) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE.       
     526  
     527      srcv(jpr_grnm  )%clname = 'OGrnmass'   
     528      IF( TRIM( sn_rcv_grnm%cldes ) == 'coupled' ) THEN  
     529         srcv(jpr_grnm)%laction = .TRUE.   
     530         srcv(jpr_grnm)%dimensions = 0 ! Scalar field 
     531      ENDIF  
     532        
     533      srcv(jpr_antm  )%clname = 'OAntmass'  
     534      IF( TRIM( sn_rcv_antm%cldes ) == 'coupled' ) THEN 
     535         srcv(jpr_antm)%laction = .TRUE. 
     536         srcv(jpr_antm)%dimensions = 0 ! Scalar field 
     537      ENDIF 
     538 
    496539      srcv(jpr_isf)%clname = 'OIcshelf'   ;  IF( TRIM( sn_rcv_isf%cldes) == 'coupled' )   srcv(jpr_isf)%laction = .TRUE. 
    497540      srcv(jpr_icb)%clname = 'OIceberg'   ;  IF( TRIM( sn_rcv_icb%cldes) == 'coupled' )   srcv(jpr_icb)%laction = .TRUE. 
     
    744787         ENDIF 
    745788      ENDIF 
    746        
    747       ! =================================================== ! 
    748       ! Allocate all parts of frcv used for received fields ! 
    749       ! =================================================== ! 
    750       DO jn = 1, jprcv 
    751          IF ( srcv(jn)%laction ) ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) ) 
    752       END DO 
    753       ! Allocate taum part of frcv which is used even when not received as coupling field 
    754       IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jpr_taum)%nct) ) 
    755       ! Allocate w10m part of frcv which is used even when not received as coupling field 
    756       IF ( .NOT. srcv(jpr_w10m)%laction ) ALLOCATE( frcv(jpr_w10m)%z3(jpi,jpj,srcv(jpr_w10m)%nct) ) 
    757       ! Allocate jpr_otx1 part of frcv which is used even when not received as coupling field 
    758       IF ( .NOT. srcv(jpr_otx1)%laction ) ALLOCATE( frcv(jpr_otx1)%z3(jpi,jpj,srcv(jpr_otx1)%nct) ) 
    759       IF ( .NOT. srcv(jpr_oty1)%laction ) ALLOCATE( frcv(jpr_oty1)%z3(jpi,jpj,srcv(jpr_oty1)%nct) ) 
    760       ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE. 
    761       IF( k_ice /= 0 ) THEN 
    762          IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jpr_itx1)%nct) ) 
    763          IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jpr_ity1)%nct) ) 
    764       END IF 
    765789 
    766790      ! ================================ ! 
     
    772796       
    773797      ! default definitions of nsnd 
    774       ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1.  ; ssnd(:)%nct = 1 
     798      ssnd(:)%laction = .FALSE.  
     799      ssnd(:)%clgrid = 'T'  
     800      ssnd(:)%nsgn = 1.  
     801      ssnd(:)%nct = 1  
     802      ssnd(:)%dimensions = 2  
    775803          
    776804      !                                                      ! ------------------------- ! 
     
    10551083      ENDIF 
    10561084 
     1085      ! Initialise 1D river outflow scheme  
     1086      nn_cpl_river = 1  
     1087      IF ( TRIM( sn_rcv_rnf%cldes ) == 'coupled1d' ) CALL cpl_rnf_1d_init   ! Coupled runoff using 1D array 
     1088       
     1089      ! =================================================== ! 
     1090      ! Allocate all parts of frcv used for received fields ! 
     1091      ! =================================================== ! 
     1092      DO jn = 1, jprcv 
     1093 
     1094         IF ( srcv(jn)%laction ) THEN  
     1095            SELECT CASE( srcv(jn)%dimensions ) 
     1096            ! 
     1097            CASE( 0 )   ! Scalar field 
     1098               ALLOCATE( frcv(jn)%z3(1,1,1) ) 
     1099                
     1100            CASE( 1 )   ! 1D field 
     1101               ALLOCATE( frcv(jn)%z3(nn_cpl_river,1,1) ) 
     1102                
     1103            CASE DEFAULT  ! 2D (or pseudo 3D) field. 
     1104               ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) ) 
     1105                
     1106            END SELECT 
     1107         END IF 
     1108 
     1109      END DO 
     1110      ! Allocate taum part of frcv which is used even when not received as coupling field 
     1111      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jpr_taum)%nct) ) 
     1112      ! Allocate w10m part of frcv which is used even when not received as coupling field 
     1113      IF ( .NOT. srcv(jpr_w10m)%laction ) ALLOCATE( frcv(jpr_w10m)%z3(jpi,jpj,srcv(jpr_w10m)%nct) ) 
     1114      ! Allocate jpr_otx1 part of frcv which is used even when not received as coupling field 
     1115      IF ( .NOT. srcv(jpr_otx1)%laction ) ALLOCATE( frcv(jpr_otx1)%z3(jpi,jpj,srcv(jpr_otx1)%nct) ) 
     1116      IF ( .NOT. srcv(jpr_oty1)%laction ) ALLOCATE( frcv(jpr_oty1)%z3(jpi,jpj,srcv(jpr_oty1)%nct) ) 
     1117      ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE. 
     1118      IF( k_ice /= 0 ) THEN 
     1119         IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jpr_itx1)%nct) ) 
     1120         IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jpr_ity1)%nct) ) 
     1121      END IF 
     1122 
    10571123      ! 
    10581124      ! ================================ ! 
     
    10721138      ENDIF 
    10731139      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 ) 
     1140      ! 
     1141      IF( nn_coupled_iceshelf_fluxes .gt. 0 ) THEN  
     1142          ! Crude masks to separate the Antarctic and Greenland icesheets. Obviously something  
     1143          ! more complicated could be done if required.  
     1144          greenland_icesheet_mask = 0.0  
     1145          WHERE( gphit >= 0.0 ) greenland_icesheet_mask = 1.0  
     1146          antarctica_icesheet_mask = 0.0  
     1147          WHERE( gphit < 0.0 ) antarctica_icesheet_mask = 1.0  
     1148   
     1149          IF( .not. ln_rstart ) THEN  
     1150             greenland_icesheet_mass = 0.0   
     1151             greenland_icesheet_mass_rate_of_change = 0.0   
     1152             greenland_icesheet_timelapsed = 0.0  
     1153             antarctica_icesheet_mass = 0.0   
     1154             antarctica_icesheet_mass_rate_of_change = 0.0   
     1155             antarctica_icesheet_timelapsed = 0.0  
     1156          ENDIF  
     1157  
     1158      ENDIF  
    10741159      ! 
    10751160   END SUBROUTINE sbc_cpl_init 
     
    11321217      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars      
    11331218      REAL(wp) ::   zcoef                  ! temporary scalar 
     1219      LOGICAL  ::   ll_wrtstp              ! write diagnostics? 
    11341220      REAL(wp) ::   zrhoa  = 1.22          ! Air density kg/m3 
    11351221      REAL(wp) ::   zcdrag = 1.5e-3        ! drag coefficient 
     1222      REAL(wp) ::   zgreenland_icesheet_mass_in, zantarctica_icesheet_mass_in  
     1223      REAL(wp) ::   zgreenland_icesheet_mass_b, zantarctica_icesheet_mass_b  
     1224      REAL(wp) ::   zmask_sum, zepsilon     
    11361225      REAL(wp) ::   zzx, zzy               ! temporary variables 
    11371226      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr, zcloud_fra 
    11381227      !!---------------------------------------------------------------------- 
     1228      ! 
     1229      ll_wrtstp  = (( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )) .AND. (nn_print>0) 
    11391230      ! 
    11401231      IF( kt == nit000 ) THEN 
     
    11531244      isec = ( kt - nit000 ) * NINT( rdt )                      ! date of exchanges 
    11541245      DO jn = 1, jprcv                                          ! received fields sent by the atmosphere 
    1155          IF( srcv(jn)%laction )   CALL cpl_rcv( jn, isec, frcv(jn)%z3, xcplmask(:,:,1:nn_cplmodel), nrcvinfo(jn) ) 
     1246        IF( srcv(jn)%laction ) THEN   
     1247  
     1248          IF ( srcv(jn)%dimensions <= 1 ) THEN  
     1249            CALL cpl_rcv_1d( jn, isec, frcv(jn)%z3, SIZE(frcv(jn)%z3), nrcvinfo(jn) )  
     1250          ELSE  
     1251            CALL cpl_rcv( jn, isec, frcv(jn)%z3, xcplmask(:,:,1:nn_cplmodel), nrcvinfo(jn) )  
     1252          END IF  
     1253 
     1254        END IF  
    11561255      END DO 
    11571256 
     
    14801579         IF( srcv(jpr_fice )%laction )   fr_i(:,:) = frcv(jpr_fice )%z3(:,:,1) 
    14811580         ! 
     1581      ENDIF 
     1582 
     1583      !                                                        ! land ice masses : Greenland 
     1584      zepsilon = rn_iceshelf_fluxes_tolerance 
     1585 
     1586      IF( srcv(jpr_grnm)%laction .AND. nn_coupled_iceshelf_fluxes == 1 ) THEN 
     1587       
     1588         ! This is a zero dimensional, single value field.  
     1589         zgreenland_icesheet_mass_in =  frcv(jpr_grnm)%z3(1,1,1) 
     1590            
     1591         greenland_icesheet_timelapsed = greenland_icesheet_timelapsed + rdt          
     1592 
     1593         IF( ln_iceshelf_init_atmos .AND. kt == 1 ) THEN 
     1594            ! On the first timestep (of an NRUN) force the ocean to ignore the icesheet masses in the ocean restart 
     1595            ! and take them from the atmosphere to avoid problems with using inconsistent ocean and atmosphere restarts. 
     1596            zgreenland_icesheet_mass_b = zgreenland_icesheet_mass_in 
     1597            greenland_icesheet_mass = zgreenland_icesheet_mass_in 
     1598         ENDIF 
     1599 
     1600         IF( ABS( zgreenland_icesheet_mass_in - greenland_icesheet_mass ) > zepsilon ) THEN 
     1601            zgreenland_icesheet_mass_b = greenland_icesheet_mass 
     1602             
     1603            ! Only update the mass if it has increased. 
     1604            IF ( (zgreenland_icesheet_mass_in - greenland_icesheet_mass) > 0.0 ) THEN 
     1605               greenland_icesheet_mass = zgreenland_icesheet_mass_in 
     1606            ENDIF 
     1607             
     1608            IF( zgreenland_icesheet_mass_b /= 0.0 ) & 
     1609           &     greenland_icesheet_mass_rate_of_change = ( greenland_icesheet_mass - zgreenland_icesheet_mass_b ) / greenland_icesheet_timelapsed  
     1610            greenland_icesheet_timelapsed = 0.0_wp        
     1611         ENDIF 
     1612         IF(lwp .AND. ll_wrtstp) THEN 
     1613            WRITE(numout,*) 'Greenland icesheet mass (kg) read in is ', zgreenland_icesheet_mass_in 
     1614            WRITE(numout,*) 'Greenland icesheet mass (kg) used is    ', greenland_icesheet_mass 
     1615            WRITE(numout,*) 'Greenland icesheet mass rate of change (kg/s) is ', greenland_icesheet_mass_rate_of_change 
     1616            WRITE(numout,*) 'Greenland icesheet seconds lapsed since last change is ', greenland_icesheet_timelapsed 
     1617         ENDIF 
     1618      ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN 
     1619         greenland_icesheet_mass_rate_of_change = rn_greenland_total_fw_flux 
     1620      ENDIF 
     1621 
     1622      !                                                        ! land ice masses : Antarctica 
     1623      IF( srcv(jpr_antm)%laction .AND. nn_coupled_iceshelf_fluxes == 1 ) THEN 
     1624          
     1625         ! This is a zero dimensional, single value field.  
     1626         zantarctica_icesheet_mass_in = frcv(jpr_antm)%z3(1,1,1) 
     1627            
     1628         antarctica_icesheet_timelapsed = antarctica_icesheet_timelapsed + rdt          
     1629 
     1630         IF( ln_iceshelf_init_atmos .AND. kt == 1 ) THEN 
     1631            ! On the first timestep (of an NRUN) force the ocean to ignore the icesheet masses in the ocean restart 
     1632            ! and take them from the atmosphere to avoid problems with using inconsistent ocean and atmosphere restarts. 
     1633            zantarctica_icesheet_mass_b = zantarctica_icesheet_mass_in 
     1634            antarctica_icesheet_mass = zantarctica_icesheet_mass_in 
     1635         ENDIF 
     1636 
     1637         IF( ABS( zantarctica_icesheet_mass_in - antarctica_icesheet_mass ) > zepsilon ) THEN 
     1638            zantarctica_icesheet_mass_b = antarctica_icesheet_mass 
     1639             
     1640            ! Only update the mass if it has increased. 
     1641            IF ( (zantarctica_icesheet_mass_in - antarctica_icesheet_mass) > 0.0 ) THEN 
     1642               antarctica_icesheet_mass = zantarctica_icesheet_mass_in 
     1643            END IF 
     1644             
     1645            IF( zantarctica_icesheet_mass_b /= 0.0 ) & 
     1646          &      antarctica_icesheet_mass_rate_of_change = ( antarctica_icesheet_mass - zantarctica_icesheet_mass_b ) / antarctica_icesheet_timelapsed  
     1647            antarctica_icesheet_timelapsed = 0.0_wp        
     1648         ENDIF 
     1649         IF(lwp .AND. ll_wrtstp) THEN 
     1650            WRITE(numout,*) 'Antarctica icesheet mass (kg) read in is ', zantarctica_icesheet_mass_in 
     1651            WRITE(numout,*) 'Antarctica icesheet mass (kg) used is    ', antarctica_icesheet_mass 
     1652            WRITE(numout,*) 'Antarctica icesheet mass rate of change (kg/s) is ', antarctica_icesheet_mass_rate_of_change 
     1653            WRITE(numout,*) 'Antarctica icesheet seconds lapsed since last change is ', antarctica_icesheet_timelapsed 
     1654         ENDIF 
     1655      ELSE IF ( nn_coupled_iceshelf_fluxes == 2 ) THEN 
     1656         antarctica_icesheet_mass_rate_of_change = rn_antarctica_total_fw_flux 
    14821657      ENDIF 
    14831658      ! 
     
    17521927       
    17531928      ! --- Continental fluxes --- ! 
    1754       IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on) 
     1929      IF( srcv(jpr_rnf)%laction ) THEN   ! 2D runoffs (included in emp later on) 
    17551930         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     1931      ENDIF 
     1932      IF( srcv(jpr_rnf_1d)%laction ) THEN ! 1D runoff 
     1933         CALL cpl_rnf_1d_to_2d(frcv(jpr_rnf_1d)%z3(:,:,:)) 
    17561934      ENDIF 
    17571935      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot and emp_oce) 
     
    17921970      zsnw(:,:) = picefr(:,:) 
    17931971      ! --- Continental fluxes --- ! 
    1794       IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on) 
     1972      IF( srcv(jpr_rnf)%laction ) THEN   ! 2D runoffs (included in emp later on) 
    17951973         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     1974      ENDIF 
     1975      IF( srcv(jpr_rnf_1d)%laction ) THEN  ! 1D runoff 
     1976         CALL cpl_rnf_1d_to_2d(frcv(jpr_rnf_1d)%z3(:,:,:))  
    17961977      ENDIF 
    17971978      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot) 
Note: See TracChangeset for help on using the changeset viewer.