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

Changeset 7060


Ignore:
Timestamp:
2016-10-20T16:16:29+02:00 (8 years ago)
Author:
clem
Message:

update agrif+lim3

Location:
branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r6853 r7060  
    108108      ! 1) Read namelist 
    109109      !-------------------------------------------------------------------- 
    110  
    111       CALL lim_istate_init     !  reading the initials parameters of the ice 
    112  
    113       ! surface temperature 
    114       DO jl = 1, jpl ! loop over categories 
     110      CALL lim_istate_init 
     111 
     112      ! init surface temperature 
     113      DO jl = 1, jpl 
    115114         t_su  (:,:,jl) = rt0 * tmask(:,:,1) 
    116115         tn_ice(:,:,jl) = rt0 * tmask(:,:,1) 
    117116      END DO 
    118117 
    119       ! basal temperature (considered at freezing point) 
     118      ! init basal temperature (considered at freezing point) 
    120119      CALL eos_fzp( sss_m(:,:), t_bo(:,:) ) 
    121120      t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1)  
    122121 
    123122 
     123      !-------------------------------------------------------------------- 
     124      ! 2) Initialization of sea ice state variables 
     125      !-------------------------------------------------------------------- 
    124126      IF( ln_limini ) THEN 
    125127 
    126          !-------------------------------------------------------------------- 
    127          ! 2) Basal temperature, ice mask and hemispheric index 
    128          !-------------------------------------------------------------------- 
    129  
    130          DO jj = 1, jpj                                       ! ice if sst <= t-freez + ttest 
    131             DO ji = 1, jpi 
    132                IF( ( sst_m(ji,jj)  - ( t_bo(ji,jj) - rt0 ) ) * tmask(ji,jj,1) >= rn_thres_sst * tmask(ji,jj,1) ) THEN 
    133                   zswitch(ji,jj) = 0._wp                     ! no ice 
    134                ELSE                                                                                    
    135                   zswitch(ji,jj) = 1._wp * tmask(ji,jj,1)    !    ice 
    136                ENDIF 
    137             END DO 
    138          END DO 
    139  
    140          !-------------------------------------------------------------------- 
    141          ! 3) Initialization of sea ice state variables 
    142          !-------------------------------------------------------------------- 
    143128         IF( ln_limini_file )THEN 
    144129 
     
    150135            zsm_i_ini(:,:)  = si(jp_smi)%fnow(:,:,1) 
    151136 
     137            WHERE( zat_i_ini(:,:) > 0._wp ) ; zswitch(:,:) = tmask(:,:,1)  
     138            ELSEWHERE                       ; zswitch(:,:) = 0._wp 
     139            END WHERE 
     140 
    152141         ELSE ! ln_limini_file = F 
     142 
     143            !-------------------------------------------------------------------- 
     144            ! 3) Basal temperature, ice mask 
     145            !-------------------------------------------------------------------- 
     146            ! no ice if sst <= t-freez + ttest 
     147            WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst ) ; zswitch(:,:) = 0._wp  
     148            ELSEWHERE                                                                  ; zswitch(:,:) = tmask(:,:,1) 
     149            END WHERE 
    153150 
    154151            !----------------------------- 
     
    457454!!      ! Output the initial state and forcings 
    458455!!      CALL dia_wri_state( 'output.init', nit000 ) 
    459 !!! 
    460        
     456!!!       
     457 
    461458      CALL wrk_dealloc( jpi, jpj, jpl, zh_i_ini,  za_i_ini ) 
    462459      CALL wrk_dealloc( jpi, jpj,      zht_i_ini, zat_i_ini, zvt_i_ini, zts_u_ini, zht_s_ini, zsm_i_ini, ztm_i_ini ) 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_ice.F90

    r6584 r7060  
    6060   END FUNCTION agrif_ice_alloc 
    6161 
    62 #endif 
    63  
    64 #if defined key_agrif && defined key_lim3 
     62#elif defined key_agrif && defined key_lim3 
    6563   !!---------------------------------------------------------------------- 
    6664   !!   'key_agrif'                                              AGRIF zoom 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_lim3_interp.F90

    r6746 r7060  
    134134      !! put -9999 WHERE the parent grid is masked. The child solution will be found in the 9(?) points around 
    135135      !!----------------------------------------------------------------------- 
     136      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
    136137      INTEGER , INTENT(in) :: i1, i2, j1, j2, k1, k2 
    137       REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) :: ptab 
    138138      LOGICAL , INTENT(in) :: before 
    139139      !! 
     
    142142      ! clem: pkoi on n'utilise pas les quantités intégrées ici => before: * e12t ; after: * r1_e12t / rhox / rhoy 
    143143      ! a priori c'est ok comme ca (cf ce qui est fait dans l'ocean). Je ne sais pas pkoi ceci dit 
     144       
    144145      IF( before ) THEN  ! parent grid 
    145146         jm = 1 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_opa_interp.F90

    r6204 r7060  
    638638      REAL(wp) ::   zalpha4, zalpha5, zalpha6, zalpha7 
    639639      LOGICAL :: western_side, eastern_side,northern_side,southern_side 
    640  
     640       
    641641      IF (before) THEN          
    642642         ptab(i1:i2,j1:j2,k1:k2,n1:n2) = tsn(i1:i2,j1:j2,k1:k2,n1:n2) 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r6584 r7060  
    306306   ! Note that update below is recursive (with lk_agrif_doupd=T): 
    307307   !  
     308!!#if ! defined key_sas2D 
    308309! JC: I am not sure if Agrif_MaxLevel() is the "relative" 
    309310!     or the absolute maximum nesting level...TBC                         
     
    313314      CALL Agrif_Update_dyn() 
    314315   ENDIF 
     316!!#endif    
    315317   ! 
    316318# if defined key_zdftke 
     
    321323   nbcline = 0 
    322324   lk_agrif_doupd = .FALSE. 
     325 
    323326   ! 
    324327END SUBROUTINE Agrif_InitValues_cont 
     
    454457!   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average) 
    455458!   CALL Agrif_Set_Updatetype(sshn_id, update = Agrif_Update_Full_Weighting) 
    456   
     459 
    457460   ! 
    458461END SUBROUTINE agrif_declare_var 
     
    609612   !! ** Purpose :: Declaration of variables to be interpolated for LIM3 
    610613   !!---------------------------------------------------------------------- 
    611    USE agrif_util 
     614   USE Agrif_Util 
     615   USE Agrif_ice  !clem useless ? 
    612616   USE ice 
    613617 
     
    618622   !       agrif_declare_variable(position,1st point index,--,--,dimensions,name) 
    619623   !------------------------------------------------------------------------------------- 
    620    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/), & 
    621       &                        (/jpi,jpj,jpl,jpl*(5+nlay_s+nlay_i)/), tra_ice_id ) 
    622    CALL agrif_declare_variable((/1,2/)    ,(/2,3/)    ,(/'x','y'/)        ,(/1,1/)    ,(/jpi,jpj/)      ,u_ice_id  ) 
    623    CALL agrif_declare_variable((/2,1/)    ,(/3,2/)    ,(/'x','y'/)        ,(/1,1/)    ,(/jpi,jpj/)      ,v_ice_id  ) 
     624   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpl*(5+nlay_s+nlay_i)/),tra_ice_id ) 
     625   CALL agrif_declare_variable((/1,2/)    ,(/2,3/),(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,u_ice_id   ) 
     626   CALL agrif_declare_variable((/2,1/)    ,(/3,2/),(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,v_ice_id   ) 
    624627 
    625628   ! 2. Set interpolations (normal & tangent to the grid cell for velocities) 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r6994 r7060  
    118118      IF( nn_timing == 1 )  CALL timing_start('sbc_ice_lim') 
    119119 
     120      ! clem: it is important to initialize agrif_lim3 variables here and not in sbc_lim_init 
     121# if defined key_agrif 
     122      IF( kt == nit000 ) THEN 
     123         IF( .NOT. Agrif_Root() )   CALL Agrif_InitValues_cont_lim3 
     124      ENDIF 
     125# endif 
     126 
    120127      !-----------------------! 
    121128      ! --- Ice time step --- ! 
     
    189196            ! 
    190197         ENDIF 
     198 
    191199         ! --- 
    192200#if defined key_agrif 
     
    314322      IF( ierr /= 0 )   CALL ctl_stop('STOP', 'sbc_lim_init : unable to allocate ice arrays') 
    315323      ! 
    316       !                                ! adequation jpk versus ice/snow layers/categories 
    317       IF( jpl > jpk .OR. (nlay_i+1) > jpk .OR. nlay_s > jpk )   & 
    318          &      CALL ctl_stop( 'STOP',                          & 
    319          &     'sbc_lim_init: the 3rd dimension of workspace arrays is too small.',   & 
    320          &     'use more ocean levels or less ice/snow layers/categories.' ) 
    321       ! 
    322324      CALL lim_dyn_init                ! set ice dynamics parameters 
    323325      ! 
     
    364366      IF( nstock == 0 )   nstock = nlast + 1 
    365367      ! 
    366 # if defined key_agrif 
    367       IF( .NOT. Agrif_Root() )   CALL Agrif_InitValues_cont_lim3 
    368 # endif 
    369368      ! 
    370369   END SUBROUTINE sbc_lim_init 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6459 r7060  
    111111 
    112112      !                          ! overwrite namelist parameter using CPP key information 
    113       IF( Agrif_Root() ) THEN                ! AGRIF zoom 
    114         IF( lk_lim2 )   nn_ice      = 2 
    115         IF( lk_lim3 )   nn_ice      = 3 
    116         IF( lk_cice )   nn_ice      = 4 
    117       ENDIF 
    118       IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
    119           ln_ana      = .TRUE.    
    120           nn_ice      =   0 
    121       ENDIF 
    122  
     113#if defined key_agrif 
     114      IF( Agrif_Root() ) THEN                ! AGRIF zoom (cf r1242: possibility to run without ice in fine grid) 
     115         IF( lk_lim2 )   nn_ice      = 2 
     116         IF( lk_lim3 )   nn_ice      = 3 
     117         IF( lk_cice )   nn_ice      = 4 
     118      ENDIF 
     119#else 
     120      IF( lk_lim2 )   nn_ice      = 2 
     121      IF( lk_lim3 )   nn_ice      = 3 
     122      IF( lk_cice )   nn_ice      = 4      
     123#endif 
     124 
     125      IF( cp_cfg == 'gyre' )   ln_ana = .TRUE.          ! GYRE configuration 
     126              
    123127      IF(lwp) THEN               ! Control print 
    124128         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
     
    195199 
    196200      !                                            ! restartability    
    197       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) )   & 
    198          &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
    199201      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) )   & 
    200202         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) 
     
    303305      ! 
    304306      IF( nn_ice == 3      )   CALL sbc_lim_init               ! LIM3 initialisation 
    305  
     307      ! 
    306308      IF( nn_ice == 4      )   CALL cice_sbc_init( nsbc )      ! CICE initialisation 
    307309       
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r6584 r7060  
    111111# endif 
    112112# if defined key_lim2 
    113       CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM2 
    114 # endif 
    115 # if defined key_lim3 
    116       CALL Agrif_Declare_Var_lim3  !  "      "   "   "      "  LIM3 
     113      CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
    117114# endif 
    118115#endif 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/SAS_SRC/step.F90

    r5510 r7060  
    4343#endif 
    4444 
     45#if defined key_agrif 
     46   USE agrif_oce, ONLY: lk_agrif_debug  !clem 
     47#endif 
     48    
    4549   IMPLICIT NONE 
    4650   PRIVATE 
     
    7882#if defined key_agrif 
    7983      kstp = nit000 + Agrif_Nb_Step() 
     84      IF ( lk_agrif_debug ) THEN 
     85         IF ( Agrif_Root() .and. lwp) Write(*,*) '---' 
     86         IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp, 'int tstep',Agrif_NbStepint() 
     87      ENDIF 
     88 
     89      IF ( kstp == (nit000 + 1) ) lk_agrif_fstep = .FALSE. 
     90 
    8091# if defined key_iomput 
    8192      IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( cxios_context ) 
    8293# endif    
    8394#endif    
     95                             indic = 0                    ! although indic is not changed in stp_ctl 
     96                                                          ! need to keep the same interface  
    8497      IF( kstp == nit000 )   CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    8598      IF( kstp /= nit000 )   CALL day( kstp )             ! Calendar (day was already called at nit000 in day_init) 
     
    98111                             CALL dia_wri( kstp )         ! ocean model: outputs 
    99112 
    100                              indic = 0                    ! although indic is not changed in stp_ctl 
    101                                                           ! need to keep the same interface  
     113#if defined key_agrif 
     114      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     115      ! AGRIF 
     116      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
     117                             CALL Agrif_Integrate_ChildGrids( stp )   
     118#endif 
     119                              
     120      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     121      ! Control 
     122      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    102123                             CALL stp_ctl( kstp, indic ) 
     124      IF( indic < 0  )  THEN 
     125                             CALL ctl_stop( 'step: indic < 0' ) 
     126                             CALL dia_wri_state( 'output.abort', kstp ) 
     127      ENDIF 
     128      IF( kstp == nit000   ) CALL iom_close( numror )     ! close input  ocean restart file (clem: not sure...) 
     129       
    103130      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    104131      ! Coupled mode 
Note: See TracChangeset for help on using the changeset viewer.