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 13334 for NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/src/ICE/icerst.F90 – NEMO

Ignore:
Timestamp:
2020-07-22T16:20:32+02:00 (4 years ago)
Author:
jchanut
Message:

finish bypassing ocean/ice initialization with AGRIF, #2222, #2129

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/src/ICE/icerst.F90

    r13286 r13334  
    2525   USE lib_mpp        ! MPP library 
    2626   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     27 
     28   USE agrif_oce      ! initial state interpolation 
     29   USE agrif_ice_interp   
    2730 
    2831   IMPLICIT NONE 
     
    185188      ENDIF 
    186189 
    187       CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir ) 
    188  
    189       ! test if v_i exists  
    190       id0 = iom_varid( numrir, 'v_i' , ldstop = .FALSE. ) 
    191  
    192       !                    ! ------------------------------ ! 
    193       IF( id0 > 0 ) THEN   ! == case of a normal restart == ! 
    194          !                 ! ------------------------------ ! 
     190#if defined key_agrif 
     191      IF( (.NOT.Agrif_Root()).AND.ln_init_chfrpar ) THEN 
     192         !                 ! -------------------------------- ! 
     193         !                 ! == set ice fields from parent == ! 
     194         !                 ! -------------------------------- ! 
     195         ! 
     196         CALL agrif_istate_ice 
     197         ! 
     198      ELSE 
     199#endif 
     200 
     201         CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir ) 
     202 
     203         ! test if v_i exists  
     204         id0 = iom_varid( numrir, 'v_i' , ldstop = .FALSE. ) 
     205 
     206         !                    ! ------------------------------ ! 
     207         IF( id0 > 0 ) THEN   ! == case of a normal restart == ! 
     208            !                 ! ------------------------------ ! 
    195209          
    196          ! Time info 
    197          CALL iom_get( numrir, 'nn_fsbc', zfice ) 
    198          CALL iom_get( numrir, 'kt_ice' , ziter )     
    199          IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter 
    200          IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1 
    201  
    202          ! Control of date 
    203          IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   & 
    204             &     CALL ctl_stop( 'ice_rst_read ===>>>> : problem with nit000 in ice restart',  & 
    205             &                   '   verify the file or rerun with the value 0 for the',        & 
    206             &                   '   control of time parameter  nrstdt' ) 
    207          IF( NINT(zfice) /= nn_fsbc          .AND. ABS( nrstdt ) == 1 )   & 
    208             &     CALL ctl_stop( 'ice_rst_read ===>>>> : problem with nn_fsbc in ice restart',  & 
    209             &                   '   verify the file or rerun with the value 0 for the',         & 
    210             &                   '   control of time parameter  nrstdt' ) 
    211  
    212          ! --- mandatory fields --- !  
    213          CALL iom_get( numrir, jpdom_auto, 'v_i'  , v_i   ) 
    214          CALL iom_get( numrir, jpdom_auto, 'v_s'  , v_s   ) 
    215          CALL iom_get( numrir, jpdom_auto, 'sv_i' , sv_i  ) 
    216          CALL iom_get( numrir, jpdom_auto, 'a_i'  , a_i   ) 
    217          CALL iom_get( numrir, jpdom_auto, 't_su' , t_su  ) 
    218          CALL iom_get( numrir, jpdom_auto, 'u_ice', u_ice, cd_type = 'U', psgn = -1._wp ) 
    219          CALL iom_get( numrir, jpdom_auto, 'v_ice', v_ice, cd_type = 'V', psgn = -1._wp ) 
    220          ! Snow enthalpy 
    221          DO jk = 1, nlay_s 
    222             WRITE(zchar1,'(I2.2)') jk 
    223             znam = 'e_s'//'_l'//zchar1 
    224             CALL iom_get( numrir, jpdom_auto, znam , z3d ) 
    225             e_s(:,:,jk,:) = z3d(:,:,:) 
    226          END DO 
    227          ! Ice enthalpy 
    228          DO jk = 1, nlay_i 
    229             WRITE(zchar1,'(I2.2)') jk 
    230             znam = 'e_i'//'_l'//zchar1 
    231             CALL iom_get( numrir, jpdom_auto, znam , z3d ) 
    232             e_i(:,:,jk,:) = z3d(:,:,:) 
    233          END DO 
    234          ! -- optional fields -- ! 
    235          ! ice age 
    236          id1 = iom_varid( numrir, 'oa_i' , ldstop = .FALSE. ) 
    237          IF( id1 > 0 ) THEN                       ! fields exist 
    238             CALL iom_get( numrir, jpdom_auto, 'oa_i', oa_i ) 
    239          ELSE                                     ! start from rest 
    240             IF(lwp) WRITE(numout,*) '   ==>>   previous run without ice age output then set it to zero' 
    241             oa_i(:,:,:) = 0._wp 
     210            ! Time info 
     211            CALL iom_get( numrir, 'nn_fsbc', zfice ) 
     212            CALL iom_get( numrir, 'kt_ice' , ziter )     
     213            IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter 
     214            IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1 
     215 
     216            ! Control of date 
     217            IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   & 
     218               &     CALL ctl_stop( 'ice_rst_read ===>>>> : problem with nit000 in ice restart',  & 
     219               &                   '   verify the file or rerun with the value 0 for the',        & 
     220               &                   '   control of time parameter  nrstdt' ) 
     221            IF( NINT(zfice) /= nn_fsbc          .AND. ABS( nrstdt ) == 1 )   & 
     222               &     CALL ctl_stop( 'ice_rst_read ===>>>> : problem with nn_fsbc in ice restart',  & 
     223               &                   '   verify the file or rerun with the value 0 for the',         & 
     224               &                   '   control of time parameter  nrstdt' ) 
     225 
     226            ! --- mandatory fields --- !  
     227            CALL iom_get( numrir, jpdom_auto, 'v_i'  , v_i   ) 
     228            CALL iom_get( numrir, jpdom_auto, 'v_s'  , v_s   ) 
     229            CALL iom_get( numrir, jpdom_auto, 'sv_i' , sv_i  ) 
     230            CALL iom_get( numrir, jpdom_auto, 'a_i'  , a_i   ) 
     231            CALL iom_get( numrir, jpdom_auto, 't_su' , t_su  ) 
     232            CALL iom_get( numrir, jpdom_auto, 'u_ice', u_ice, cd_type = 'U', psgn = -1._wp ) 
     233            CALL iom_get( numrir, jpdom_auto, 'v_ice', v_ice, cd_type = 'V', psgn = -1._wp ) 
     234            ! Snow enthalpy 
     235            DO jk = 1, nlay_s 
     236               WRITE(zchar1,'(I2.2)') jk 
     237               znam = 'e_s'//'_l'//zchar1 
     238               CALL iom_get( numrir, jpdom_auto, znam , z3d ) 
     239               e_s(:,:,jk,:) = z3d(:,:,:) 
     240            END DO 
     241            ! Ice enthalpy 
     242            DO jk = 1, nlay_i 
     243               WRITE(zchar1,'(I2.2)') jk 
     244               znam = 'e_i'//'_l'//zchar1 
     245               CALL iom_get( numrir, jpdom_auto, znam , z3d ) 
     246               e_i(:,:,jk,:) = z3d(:,:,:) 
     247            END DO 
     248            ! -- optional fields -- ! 
     249            ! ice age 
     250            id1 = iom_varid( numrir, 'oa_i' , ldstop = .FALSE. ) 
     251            IF( id1 > 0 ) THEN                       ! fields exist 
     252               CALL iom_get( numrir, jpdom_auto, 'oa_i', oa_i ) 
     253            ELSE                                     ! start from rest 
     254               IF(lwp) WRITE(numout,*) '   ==>>   previous run without ice age output then set it to zero' 
     255               oa_i(:,:,:) = 0._wp 
     256            ENDIF 
     257            ! melt ponds 
     258            id2 = iom_varid( numrir, 'a_ip' , ldstop = .FALSE. ) 
     259            IF( id2 > 0 ) THEN                       ! fields exist 
     260               CALL iom_get( numrir, jpdom_auto, 'a_ip' , a_ip ) 
     261               CALL iom_get( numrir, jpdom_auto, 'v_ip' , v_ip ) 
     262            ELSE                                     ! start from rest 
     263               IF(lwp) WRITE(numout,*) '   ==>>   previous run without melt ponds output then set it to zero' 
     264               a_ip(:,:,:) = 0._wp 
     265               v_ip(:,:,:) = 0._wp 
     266            ENDIF 
     267            ! fields needed for Met Office (Jules) coupling 
     268            IF( ln_cpl ) THEN 
     269               id3 = iom_varid( numrir, 'cnd_ice' , ldstop = .FALSE. ) 
     270               id4 = iom_varid( numrir, 't1_ice'  , ldstop = .FALSE. ) 
     271               IF( id3 > 0 .AND. id4 > 0 ) THEN         ! fields exist 
     272                  CALL iom_get( numrir, jpdom_auto, 'cnd_ice', cnd_ice ) 
     273                  CALL iom_get( numrir, jpdom_auto, 't1_ice' , t1_ice  ) 
     274               ELSE                                     ! start from rest 
     275                  IF(lwp) WRITE(numout,*) '   ==>>   previous run without conductivity output then set it to zero' 
     276                  cnd_ice(:,:,:) = 0._wp 
     277                  t1_ice (:,:,:) = rt0 
     278               ENDIF 
     279            ENDIF 
     280 
     281            CALL iom_delay_rst( 'READ', 'ICE', numrir )   ! read only ice delayed global communication variables 
     282 
     283            !                 ! ---------------------------------- ! 
     284         ELSE                 ! == case of a simplified restart == ! 
     285            !                 ! ---------------------------------- ! 
     286            CALL ctl_warn('ice_rst_read: you are using a simplified ice restart') 
     287            ! 
     288            CALL ice_istate_init 
     289            CALL ice_istate( nit000, Kbb, Kmm, Kaa ) 
     290            ! 
     291            IF( .NOT.ln_iceini .OR. .NOT.ln_iceini_file ) & 
     292               &   CALL ctl_stop('STOP', 'ice_rst_read: you need ln_ice_ini=T and ln_iceini_file=T') 
     293            ! 
    242294         ENDIF 
    243          ! melt ponds 
    244          id2 = iom_varid( numrir, 'a_ip' , ldstop = .FALSE. ) 
    245          IF( id2 > 0 ) THEN                       ! fields exist 
    246             CALL iom_get( numrir, jpdom_auto, 'a_ip' , a_ip ) 
    247             CALL iom_get( numrir, jpdom_auto, 'v_ip' , v_ip ) 
    248          ELSE                                     ! start from rest 
    249             IF(lwp) WRITE(numout,*) '   ==>>   previous run without melt ponds output then set it to zero' 
    250             a_ip(:,:,:) = 0._wp 
    251             v_ip(:,:,:) = 0._wp 
    252          ENDIF 
    253          ! fields needed for Met Office (Jules) coupling 
    254          IF( ln_cpl ) THEN 
    255             id3 = iom_varid( numrir, 'cnd_ice' , ldstop = .FALSE. ) 
    256             id4 = iom_varid( numrir, 't1_ice'  , ldstop = .FALSE. ) 
    257             IF( id3 > 0 .AND. id4 > 0 ) THEN         ! fields exist 
    258                CALL iom_get( numrir, jpdom_auto, 'cnd_ice', cnd_ice ) 
    259                CALL iom_get( numrir, jpdom_auto, 't1_ice' , t1_ice  ) 
    260             ELSE                                     ! start from rest 
    261                IF(lwp) WRITE(numout,*) '   ==>>   previous run without conductivity output then set it to zero' 
    262                cnd_ice(:,:,:) = 0._wp 
    263                t1_ice (:,:,:) = rt0 
    264             ENDIF 
    265          ENDIF 
    266  
    267          CALL iom_delay_rst( 'READ', 'ICE', numrir )   ! read only ice delayed global communication variables 
    268  
    269          !                 ! ---------------------------------- ! 
    270       ELSE                 ! == case of a simplified restart == ! 
    271          !                 ! ---------------------------------- ! 
    272          CALL ctl_warn('ice_rst_read: you are using a simplified ice restart') 
    273          ! 
    274          CALL ice_istate_init 
    275          CALL ice_istate( nit000, Kbb, Kmm, Kaa ) 
    276          ! 
    277          IF( .NOT.ln_iceini .OR. .NOT.ln_iceini_file ) & 
    278             &   CALL ctl_stop('STOP', 'ice_rst_read: you need ln_ice_ini=T and ln_iceini_file=T') 
    279          ! 
    280       ENDIF 
     295#if defined key_agrif 
     296      ENDIF 
     297#endif 
    281298 
    282299   END SUBROUTINE ice_rst_read 
Note: See TracChangeset for help on using the changeset viewer.