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 10047 for branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2018-08-08T17:12:35+02:00 (6 years ago)
Author:
jpalmier
Message:

merge with GO6_package_branch 9385-10020 ; plus debug OMIP_DIC

Location:
branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC
Files:
30 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90

    r6486 r10047  
    150150CONTAINS 
    151151   SUBROUTINE bdy_dyn( kt )      ! Empty routine 
     152   IMPLICIT NONE 
     153      INTEGER, INTENT( in )           :: kt               ! Main time step counter 
    152154      WRITE(*,*) 'bdy_dyn: You should not have seen this print! error?', kt 
    153155   END SUBROUTINE bdy_dyn 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn3d.F90

    r6486 r10047  
    309309CONTAINS 
    310310   SUBROUTINE bdy_dyn3d( kt )      ! Empty routine 
    311       WRITE(*,*) 'bdy_dyn3d: You should not have seen this print! error?', kt 
     311   IMPLICIT NONE 
     312    INTEGER, INTENT( in ) :: kt     ! Main time step counter 
     313    WRITE(*,*) 'bdy_dyn3d: You should not have seen this print! error?', kt 
    312314   END SUBROUTINE bdy_dyn3d 
    313315 
    314316   SUBROUTINE bdy_dyn3d_dmp( kt )      ! Empty routine 
    315       WRITE(*,*) 'bdy_dyn3d_dmp: You should not have seen this print! error?', kt 
     317   IMPLICIT NONE 
     318    INTEGER, INTENT( in ) :: kt     ! Main time step counter 
     319    WRITE(*,*) 'bdy_dyn3d_dmp: You should not have seen this print! error?', kt 
    316320   END SUBROUTINE bdy_dyn3d_dmp 
    317321 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r6487 r10047  
    611611CONTAINS 
    612612   SUBROUTINE bdytide_init             ! Empty routine 
     613   IMPLICIT NONE 
    613614      WRITE(*,*) 'bdytide_init: You should not have seen this print! error?' 
    614615   END SUBROUTINE bdytide_init 
    615616   SUBROUTINE bdytide_update( kt, jit )   ! Empty routine 
     617   IMPLICIT NONE 
     618      INTEGER, INTENT( in )            ::   kt          ! Main timestep counter 
     619      INTEGER,INTENT(in),OPTIONAL      ::   jit         ! Barotropic timestep counter (for timesplitting option) 
    616620      WRITE(*,*) 'bdytide_update: You should not have seen this print! error?', kt, jit 
    617621   END SUBROUTINE bdytide_update 
    618622   SUBROUTINE bdy_dta_tides( kt, kit, time_offset )     ! Empty routine 
     623   IMPLICIT NONE 
    619624      INTEGER, INTENT( in )            ::   kt          ! Dummy argument empty routine       
    620625      INTEGER, INTENT( in ),OPTIONAL   ::   kit         ! Dummy argument empty routine 
    621626      INTEGER, INTENT( in ),OPTIONAL   ::   time_offset ! Dummy argument empty routine 
    622       WRITE(*,*) 'bdy_dta_tides: You should not have seen this print! error?', kt, jit 
     627      WRITE(*,*) 'bdy_dta_tides: You should not have seen this print! error?', kt, kit 
    623628   END SUBROUTINE bdy_dta_tides 
    624629#endif 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90

    r6486 r10047  
    319319CONTAINS 
    320320   SUBROUTINE bdy_tra(kt)      ! Empty routine 
     321   IMPLICIT NONE 
     322      INTEGER, INTENT( in ) :: kt     ! Main time step counter    
    321323      WRITE(*,*) 'bdy_tra: You should not have seen this print! error?', kt 
    322324   END SUBROUTINE bdy_tra 
    323325 
    324326   SUBROUTINE bdy_tra_dmp(kt)      ! Empty routine 
     327   IMPLICIT NONE 
     328      INTEGER, INTENT( in ) :: kt     ! Main time step counter    
    325329      WRITE(*,*) 'bdy_tra_dmp: You should not have seen this print! error?', kt 
    326330   END SUBROUTINE bdy_tra_dmp 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/BDY/bdyvol.F90

    r6487 r10047  
    178178CONTAINS 
    179179   SUBROUTINE bdy_vol( kt )        ! Empty routine 
     180   IMPLICIT NONE 
     181      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    180182      WRITE(*,*) 'bdy_vol: You should not have seen this print! error?', kt 
    181183   END SUBROUTINE bdy_vol 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/C1D/dyncor_c1d.F90

    r6486 r10047  
    116116CONTAINS 
    117117   SUBROUTINE cor_c1d              ! Empty routine 
     118   IMPLICIT NONE 
    118119   END SUBROUTINE cor_c1d    
     120    
    119121   SUBROUTINE dyn_cor_c1d ( kt )      ! Empty routine 
     122   IMPLICIT NONE 
     123      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index    
    120124      WRITE(*,*) 'dyn_cor_c1d: You should not have seen this print! error?', kt 
    121125   END SUBROUTINE dyn_cor_c1d 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/C1D/step_c1d.F90

    r6486 r10047  
    165165   !!---------------------------------------------------------------------- 
    166166CONTAINS 
    167    SUBROUTINE stp_c1d ( kt )      ! dummy routine 
    168       WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt 
     167   SUBROUTINE stp_c1d ( kstp )      ! dummy routine 
     168   IMPLICIT NONE 
     169   INTEGER, INTENT(in) ::   kstp   ! ocean time-step index 
     170      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kstp 
    169171   END SUBROUTINE stp_c1d 
    170172#endif 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    r6486 r10047  
    13021302 
    13031303   SUBROUTINE dia_dct_init          ! Dummy routine 
    1304       WRITE(*,*) 'dia_dct_init: You should not have seen this print! error?', kt 
     1304   IMPLICIT NONE 
     1305      WRITE(*,*) 'dia_dct_init: You should not have seen this print! error?' 
    13051306   END SUBROUTINE dia_dct_init 
    13061307 
    13071308   SUBROUTINE dia_dct( kt )         ! Dummy routine 
     1309   IMPLICIT NONE 
    13081310      INTEGER, INTENT( in ) :: kt   ! ocean time-step index 
    13091311      WRITE(*,*) 'dia_dct: You should not have seen this print! error?', kt 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DIA/diahth.F90

    r6486 r10047  
    343343CONTAINS 
    344344   SUBROUTINE dia_hth( kt )         ! Empty routine 
    345       WRITE(*,*) 'dia_hth: You should not have seen this print! error?', kt 
     345   IMPLICIT NONE 
     346    INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     347    WRITE(*,*) 'dia_hth: You should not have seen this print! error?', kt 
    346348   END SUBROUTINE dia_hth 
    347349#endif 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DIA/diaptr.F90

    r9207 r10047  
    102102 
    103103      ! 
     104      z2d(:,:) = 0._wp 
    104105      z3d(:,:,:) = 0._wp 
    105106      IF( PRESENT( pvtr ) ) THEN 
     
    246247         ! 
    247248         IF( iom_use("zotemglo") ) THEN    ! i-mean i-k-surface  
     249            zmask(:,:,:) = 0._wp 
     250            zts(:,:,:,:) = 0._wp 
    248251            DO jk = 1, jpkm1 
    249252               DO jj = 1, jpj 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r8400 r10047  
    246246            z3d(:,:,jk) = wn(:,:,jk) * z2d(:,:) 
    247247         END DO 
     248         CALL lbc_lnk( z3d(:,:,:), 'W', 1. ) 
    248249         CALL iom_put( "w_masstr" , z3d )   
    249250         IF( iom_use('w_masstr2') )   CALL iom_put( "w_masstr2", z3d(:,:,:) * z3d(:,:,:) ) 
     
    252253      CALL iom_put( "avt" , avt                        )    ! T vert. eddy diff. coef. 
    253254      CALL iom_put( "avm" , avmu                       )    ! T vert. eddy visc. coef. 
     255#if defined key_zdftke 
    254256      IF( lk_zdftke ) THEN    
    255257         CALL iom_put( "tke"      , en                               )    ! TKE budget: Turbulent Kinetic Energy    
    256258         CALL iom_put( "tke_niw"  , e_niw                            )    ! TKE budget: Near-inertial waves    
    257259      ENDIF  
     260#endif 
    258261      CALL iom_put( "avs" , fsavs(:,:,:)               )    ! S vert. eddy diff. coef. (useful only with key_zdfddm) 
    259262                                                            ! Log of eddy diff coef 
     
    334337            z2d(:,:) = z2d(:,:) + z3d(:,:,jk) 
    335338         END DO 
     339         CALL lbc_lnk( z3d(:,:,:), 'U', -1. ) 
    336340         CALL iom_put( "u_masstr", z3d )                  ! mass transport in i-direction 
     341         CALL lbc_lnk( z2d(:,:), 'U', -1. ) 
    337342         CALL iom_put( "u_masstr_vint", z2d )             ! mass transport in i-direction vertical sum 
    338343      ENDIF 
     
    370375            z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * fse3v(:,:,jk) * vmask(:,:,jk) 
    371376         END DO 
     377         CALL lbc_lnk( z3d(:,:,:), 'V', -1. ) 
    372378         CALL iom_put( "v_masstr", z3d )                  ! mass transport in j-direction 
    373379      ENDIF 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r8427 r10047  
    254254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bathy                              !: ocean depth (meters) 
    255255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tmask_i, umask_i, vmask_i, fmask_i !: interior domain T-point mask 
     256   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tmask_i_diag     !: partial mask for use in T diagnostic mask calc.  
     257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: umask_i_diag     !: partial mask for use in U diagnostic mask calc.  
     258   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: vmask_i_diag     !: partial mask for use in V diagnostic mask calc.  
    256259   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bmask                              !: land/ocean mask of barotropic stream function 
    257260 
     
    406409 
    407410      ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk),     &  
    408          &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk), STAT=ierr(11) ) 
     411         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk),     & 
     412                tmask_i_diag(jpi,jpj,jpk),     & 
     413                umask_i_diag(jpi,jpj,jpk),     & 
     414                vmask_i_diag(jpi,jpj,jpk),     & 
     415                STAT=ierr(11) ) 
    409416 
    410417      ALLOCATE( wmask(jpi,jpj,jpk) , wumask(jpi,jpj,jpk), wvmask(jpi,jpj,jpk) , STAT=ierr(12) ) 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r8280 r10047  
     1 
    12MODULE dommsk 
    23   !!====================================================================== 
     
    3031   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient 
    3132   USE wrk_nemo        ! Memory allocation 
     33   USE domwri 
    3234   USE timing          ! Timing 
    3335 
     
    138140      REAL(wp) ::  zphi_drake_passage, zshlat_antarc 
    139141      REAL(wp), POINTER, DIMENSION(:,:) ::  zwf 
     142      REAL(wp) :: uvt(jpi,jpj)   ! dummy array for masking purposes. 
    140143      !! 
    141144      NAMELIST/namlbc/ rn_shlat, ln_vorlat 
     
    223226      ! -------------------- 
    224227      tmask_i(:,:) = ssmask(:,:)            ! (ISH) tmask_i = 1 even on the ice shelf 
     228 
    225229      iif = jpreci                         ! ??? 
    226230      iil = nlci - jpreci + 1 
     
    246250         ENDIF 
    247251      ENDIF 
     252 
     253 
    248254      IF( jperio == 5 .OR. jperio == 6 ) THEN      ! F-point pivot 
    249255         tpol(     1    :jpiglo) = 0._wp 
     
    263269                  &            * tmask(ji,jj+1,jk) * tmask(ji+1,jj+1,jk) 
    264270            END DO 
    265          END DO 
     271         END DO  
    266272      END DO 
    267273      ! (ISF) MIN(1,SUM(umask)) is here to check if you have effectively at least 1 wet u point 
     
    282288      CALL lbc_lnk( vmask_i, 'V', 1._wp ) 
    283289      CALL lbc_lnk( fmask_i, 'F', 1._wp ) 
     290 
     291 
     292      ! Set up mask for diagnostics on T points, to exclude duplicate 
     293      ! data points in wrap and N-fold regions.  
     294      CALL dom_uniq( uvt, 'T' ) 
     295      DO jk = 1, jpk 
     296         tmask_i_diag(:,:,jk) = tmask(:,:,jk) * uvt(:,:) 
     297      END DO 
     298 
     299      ! Set up mask for diagnostics on U points, to exclude duplicate 
     300      ! data points in wrap and N-fold regions.  
     301      umask_i_diag(:,:,:) = 1.0 
     302      umask_i_diag(2:jpim1,:,:) = tmask(2:jpim1,:,:) + tmask(3:jpi,:,:) 
     303      CALL lbc_lnk( umask_i_diag, 'U', 1. ) 
     304 
     305      ! Now mask out any duplicate points 
     306      CALL dom_uniq( uvt, 'U' ) 
     307      DO jk = 1, jpk 
     308         umask_i_diag(:,:,jk) = umask_i_diag(:,:,jk) * uvt(:,:) 
     309      END DO 
     310 
     311 
     312      ! Set up mask for diagnostics on V points, to exclude duplicate 
     313      ! data points in wrap and N-fold regions.  
     314      vmask_i_diag(:,:,:) = 1.0 
     315      vmask_i_diag(:,2:jpjm1,:) = tmask(:,2:jpjm1,:) + tmask(:,3:jpj,:) 
     316      CALL lbc_lnk( vmask_i_diag, 'V', 1. ) 
     317 
     318      ! Now mask out any duplicate points 
     319      CALL dom_uniq( uvt, 'V' ) 
     320      DO jk = 1, jpk 
     321         vmask_i_diag(:,:,jk) = vmask_i_diag(:,:,jk) * uvt(:,:) 
     322      END DO 
     323 
     324 
    284325 
    285326      ! 3. Ocean/land mask at wu-, wv- and w points  
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DOM/domwri.F90

    r9321 r10047  
    2626   PRIVATE 
    2727 
    28    PUBLIC dom_wri        ! routine called by inidom.F90 
     28   PUBLIC dom_wri, dom_uniq  ! routines called by inidom.F90 and iom.F90 
    2929 
    3030   !! * Substitutions 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_exp.F90

    r6486 r10047  
    107107CONTAINS 
    108108   SUBROUTINE dyn_spg_exp( kt )       ! Empty routine 
     109   IMPLICIT NONE 
     110      INTEGER, INTENT(in)  ::   kt   ! ocean time-step index   
    109111      WRITE(*,*) 'dyn_spg_exp: You should not have seen this print! error?', kt 
    110112   END SUBROUTINE dyn_spg_exp 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/FLO/floats.F90

    r6486 r10047  
    146146CONTAINS 
    147147   SUBROUTINE flo_stp( kt )          ! Empty routine 
     148   IMPLICIT NONE 
     149      INTEGER, INTENT( in  ) ::   kt   ! ocean time step    
    148150      WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt 
    149151   END SUBROUTINE flo_stp 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r9321 r10047  
    14001400      IF ( ln_mskland ) THEN 
    14011401         ! mask land points, keep values on coast line -> specific mask for U, V and W points 
     1402 
     1403 
    14021404         SELECT CASE ( cdgrd ) 
    1403          CASE('T')   ;   zmask(:,:,:)       = tmask(:,:,:) 
    1404          CASE('U')   ;   zmask(2:jpim1,:,:) = tmask(2:jpim1,:,:) + tmask(3:jpi,:,:)   ;   CALL lbc_lnk( zmask, 'U', 1. ) 
    1405          CASE('V')   ;   zmask(:,2:jpjm1,:) = tmask(:,2:jpjm1,:) + tmask(:,3:jpj,:)   ;   CALL lbc_lnk( zmask, 'V', 1. ) 
    1406          CASE('W')   ;   zmask(:,:,2:jpk  ) = tmask(:,:,1:jpkm1) + tmask(:,:,2:jpk)   ;   zmask(:,:,1) = tmask(:,:,1) 
    1407          END SELECT 
     1405         ! The masks applied here are specifically used to mask out duplicate  
     1406         ! data points in wrap columns and N-fold rows in order to ensure bit  
     1407         ! reproducibility of diagnostics which have not undergone an explicit 
     1408         ! lbc_lnk prior to writing. Such fields are prone to junk values at  
     1409         ! duplicate points since those points are often excluded from the  
     1410         ! core field computation process.  
     1411         CASE('T')    
     1412            zmask(:,:,:) = tmask_i_diag(:,:,:) 
     1413         CASE('U')       
     1414            zmask(:,:,:) = umask_i_diag(:,:,:) 
     1415    CASE('V')    
     1416            zmask(:,:,:) = vmask_i_diag(:,:,:) 
     1417         CASE('W')    
     1418            zmask(:,:,2:jpk  ) = tmask_i_diag(:,:,1:jpkm1) + tmask_i_diag(:,:,2:jpk)    
     1419            zmask(:,:,1) = tmask_i_diag(:,:,1) 
     1420        END SELECT 
    14081421         ! 
    14091422#if ! defined key_xios2 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn_c3d.h90

    r6486 r10047  
    210210      ! 
    211211      REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   ztemp2d  ! temporary array to read ahmcoef file 
     212      LOGICAL ::  tempmask( jpi,jpj)   ! Temporary mask to avoid Cray compiler bug at cce 8.3.4 
    212213      !!---------------------------------------------------------------------- 
    213214      ! 
     
    252253         zemax = MAXVAL ( e1t(:,:) * e2t(:,:), tmask(:,:,1) .GE. 0.5 ) 
    253254         zemin = MINVAL ( e1t(:,:) * e2t(:,:), tmask(:,:,1) .GE. 0.5 ) 
    254          zeref = MAXVAL ( e1t(:,:) * e2t(:,:),   & 
    255              &   tmask(:,:,1) .GE. 0.5 .AND. ABS(gphit(:,:)) .GT. 50. ) 
     255         tempmask(:,:) = .FALSE. 
     256         ! Pre calculate mask for zeref since embedding the following 
     257         ! term in the MAXVAL operation offends the Cray compiler for no  
     258         ! justifiable reason under certain conditions.  
     259         tempmask(:,:) = (tmask(:,:,1) .GE. 0.5) .AND. (ABS(gphit(:,:)) .GT. 50.) 
     260         zeref = MAXVAL ( e1t(:,:) * e2t(:,:), tempmask(:,:) ) 
    256261  
    257262         DO jj = 1, jpj 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn_smag.F90

    r6486 r10047  
    294294CONTAINS 
    295295   SUBROUTINE ldf_dyn_smag( kt )       ! Empty routine 
     296   IMPLICIT NONE 
     297      INTEGER :: kt                    ! timestep    
    296298      WRITE(*,*) 'ldf_dyn_smag: You should not have seen this print! error? check keys ldf:c3d+smag', kt 
    297299   END SUBROUTINE ldf_dyn_smag 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra_smag.F90

    r6486 r10047  
    204204CONTAINS 
    205205   SUBROUTINE ldf_tra_smag( kt )       ! Empty routine 
    206       WRITE(*,*) 'ldf_dyn_smag: You should not have seen this print! error? check keys ldf:c3d+smag', kt 
     206   IMPLICIT NONE 
     207        INTEGER, INTENT( in ) ::   kt  ! ocean time-step inedx 
     208        WRITE(*,*) 'ldf_dyn_smag: You should not have seen this print! error? check keys ldf:c3d+smag', kt 
    207209   END SUBROUTINE ldf_tra_smag 
    208210#endif 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r8400 r10047  
    167167 
    168168#if defined key_cice 
    169       ALLOCATE( qla_ice(jpi,jpj,ncat) , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
     169      ALLOCATE( qla_ice(jpi,jpj,ncat) , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,jpl)  , & 
    170170                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
    171171                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
     
    180180      IF( ln_cpl )   ALLOCATE( u_ice(jpi,jpj)        , fr1_i0(jpi,jpj)       , tn_ice (jpi,jpj,jpl)  , & 
    181181         &                     v_ice(jpi,jpj)        , fr2_i0(jpi,jpj)       , alb_ice(jpi,jpj,1)    , & 
    182          &                     emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,1)    , dqns_ice(jpi,jpj,1)   , & 
     182         &                     emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,jpl)  , dqns_ice(jpi,jpj,1)   , & 
    183183         &                     a_p(jpi,jpj,jpl)      , ht_p(jpi,jpj,jpl)     , tsfc_ice(jpi,jpj,jpl) , & 
    184184         &                     kn_ice(jpi,jpj,jpl) ,    STAT=ierr(2) ) 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r8400 r10047  
    11781178 
    11791179   SUBROUTINE sbc_ice_cice ( kt, ksbc )     ! Dummy routine 
     1180      IMPLICIT NONE 
     1181      INTEGER, INTENT(in) ::   kt    ! ocean time-step index 
     1182      INTEGER, INTENT(in) ::   ksbc    ! surface forcing type 
    11801183      WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt 
    11811184   END SUBROUTINE sbc_ice_cice 
    11821185 
    11831186   SUBROUTINE cice_sbc_init (ksbc)    ! Dummy routine 
     1187      IMPLICIT NONE 
     1188      INTEGER, INTENT(in) ::   ksbc    ! surface forcing type 
    11841189      WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?' 
    11851190   END SUBROUTINE cice_sbc_init 
    11861191 
    11871192   SUBROUTINE cice_sbc_final     ! Dummy routine 
     1193      IMPLICIT NONE 
    11881194      WRITE(*,*) 'cice_sbc_final: You should not have seen this print! error?' 
    11891195   END SUBROUTINE cice_sbc_final 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r6498 r10047  
    648648CONTAINS 
    649649   SUBROUTINE sbc_ice_lim ( kt, kblk )     ! Dummy routine 
     650   IMPLICIT NONE 
     651      INTEGER, INTENT(in) ::   kt      ! ocean time step 
     652      INTEGER, INTENT(in) ::   kblk    ! type of bulk (=3 CLIO, =4 CORE, =5 COUPLED) 
    650653      WRITE(*,*) 'sbc_ice_lim: You should not have seen this print! error?', kt, kblk 
    651654   END SUBROUTINE sbc_ice_lim 
    652655   SUBROUTINE sbc_lim_init                 ! Dummy routine 
     656   IMPLICIT NONE 
    653657   END SUBROUTINE sbc_lim_init 
    654658#endif 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_tvd.F90

    r7771 r10047  
    3333   USE wrk_nemo       ! Memory Allocation 
    3434   USE timing         ! Timing 
     35   USE phycst         ! Physical constants 
    3536   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    3637   USE iom 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90

    r6486 r10047  
    134134      INTEGER  ::   ierror              ! local integer 
    135135      ! 
    136       TYPE(FLD_N)        ::   sn_qgh    ! informations about the geotherm. field to be read 
    137       CHARACTER(len=256) ::   cn_dir    ! Root directory for location of ssr files 
     136      TYPE(FLD_N), DIMENSION (1)  ::   slf_q     ! array of namelist informations on the fields to read 
     137      TYPE(FLD_N)                 ::   sn_qgh    ! informations about the geotherm. field to be read 
     138      CHARACTER(len=256)          ::   cn_dir    ! Root directory for location of ssr files 
    138139      ! 
    139140      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir  
     
    173174            IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux' 
    174175            ! 
     176            slf_q(1) = sn_qgh 
     177            ! 
    175178            ALLOCATE( sf_qgh(1), STAT=ierror ) 
    176179            IF( ierror > 0 ) THEN 
     
    179182            ENDIF 
    180183            ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1)   ) 
    181             IF( sn_qgh%ln_tint )ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) ) 
     184            IF( slf_q(1)%ln_tint )   ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) ) 
    182185            ! fill sf_chl with sn_chl and control print 
    183             CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init',   & 
     186            CALL fld_fill( sf_qgh, slf_q, cn_dir, 'tra_bbc_init',   & 
    184187               &          'bottom temperature boundary condition', 'nambbc' ) 
    185188 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/TRD/trdken.F90

    r7179 r10047  
    195195                    CALL ken_p2k( kt , zke ) 
    196196                      CALL iom_put( "ketrd_convP2K", zke )     ! conversion -rau*g*w 
     197# if defined key_ldfslp || key_esopa 
    197198        CASE( jpdyn_eivke ) 
    198199            ! CMIP6 diagnostic tknebto = tendency of KE from 
     
    216217            CALL iom_put("ketrd_eiv", zke2d) 
    217218            CALL wrk_dealloc( jpi, jpj, zke2d ) 
     219#endif 
    218220         ! 
    219221      END SELECT 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfgls.F90

    r9321 r10047  
    12311231CONTAINS 
    12321232   SUBROUTINE zdf_gls_init           ! Empty routine 
     1233   IMPLICIT NONE 
    12331234      WRITE(*,*) 'zdf_gls_init: You should not have seen this print! error?' 
    12341235   END SUBROUTINE zdf_gls_init 
     1236    
    12351237   SUBROUTINE zdf_gls( kt )          ! Empty routine 
     1238   IMPLICIT NONE 
     1239      INTEGER, INTENT(in) ::   kt ! ocean time step    
    12361240      WRITE(*,*) 'zdf_gls: You should not have seen this print! error?', kt 
    12371241   END SUBROUTINE zdf_gls 
     1242    
    12381243   SUBROUTINE gls_rst( kt, cdrw )          ! Empty routine 
     1244   IMPLICIT NONE 
    12391245      INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
    12401246      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfkpp.F90

    r6486 r10047  
    15761576CONTAINS 
    15771577   SUBROUTINE zdf_kpp_init           ! Dummy routine 
     1578   IMPLICIT NONE 
    15781579      WRITE(*,*) 'zdf_kpp_init: You should not have seen this print! error?' 
    15791580   END SUBROUTINE zdf_kpp_init 
    15801581   SUBROUTINE zdf_kpp( kt )          ! Dummy routine 
     1582   IMPLICIT NONE 
     1583      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    15811584      WRITE(*,*) 'zdf_kpp: You should not have seen this print! error?', kt 
    15821585   END SUBROUTINE zdf_kpp 
    15831586   SUBROUTINE tra_kpp( kt )          ! Dummy routine 
     1587   IMPLICIT NONE 
     1588      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    15841589      WRITE(*,*) 'tra_kpp: You should not have seen this print! error?', kt 
    15851590   END SUBROUTINE tra_kpp 
    15861591   SUBROUTINE trc_kpp( kt )          ! Dummy routine 
     1592   IMPLICIT NONE 
     1593      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    15871594      WRITE(*,*) 'trc_kpp: You should not have seen this print! error?', kt 
    15881595   END SUBROUTINE trc_kpp 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90

    r6486 r10047  
    307307CONTAINS 
    308308   SUBROUTINE zdf_ric_init         ! Dummy routine 
     309   IMPLICIT NONE 
    309310   END SUBROUTINE zdf_ric_init 
    310311   SUBROUTINE zdf_ric( kt )        ! Dummy routine 
     312   IMPLICIT NONE 
     313      INTEGER, INTENT( in ) ::   kt                           ! ocean time-step 
    311314      WRITE(*,*) 'zdf_ric: You should not have seen this print! error?', kt 
    312315   END SUBROUTINE zdf_ric 
  • branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r8280 r10047  
    101101      INTEGER :: ierr(5) 
    102102      !!---------------------------------------------------------------------- 
     103      ierr(:) = 0 
    103104      ! 
    104105      ALLOCATE( ub   (jpi,jpj,jpk)      , un   (jpi,jpj,jpk)      , ua(jpi,jpj,jpk)       ,     & 
Note: See TracChangeset for help on using the changeset viewer.