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 7646 for trunk/NEMOGCM/NEMO/OPA_SRC/LBC – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/LBC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/lbcnfd.F90

    r6140 r7646  
    802802            ELSE 
    803803               startloop = 3 
    804                pt2dl(2,ijpj) = psgn * pt2dr(3,ijpjm1) 
     804               pt2dl(2,ijpj) = psgn * pt2dl(3,ijpjm1) 
    805805            ENDIF 
    806806            DO ji = startloop, nlci 
     
    814814            ELSE 
    815815               startloop = 3 
    816                pt2dl(2,ijpj) = psgn * pt2dr(3,ijpjm1) 
     816               pt2dl(2,ijpj) = psgn * pt2dl(3,ijpjm1) 
    817817            ENDIF 
    818818            DO ji = startloop, nlci 
     
    908908               DO ji = startloop , endloop 
    909909                  ijt = jpiglo - ji - nimpp - nfiimpp(isendto(1),jpnj) + 4 
    910                   pt2dl(ji,ijpj)= 0.5 * (pt2dr(ji,ijpjm1) + psgn * pt2dr(ijt,ijpjm1)) 
     910                  pt2dl(ji,ijpj)= 0.5 * (pt2dl(ji,ijpjm1) + psgn * pt2dr(ijt,ijpjm1)) 
    911911               END DO 
    912912 
     
    924924               DO ji = startloop , endloop 
    925925                  ijt = jpiglo - ji - nimpp - nfiimpp(isendto(1),jpnj) + 4 
    926                   pt2dl(ji,ijpj) = pt2dr(ji,ijpjm1) 
     926                  pt2dl(ji,ijpj) = pt2dl(ji,ijpjm1) 
    927927               END DO 
    928928 
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r6918 r7646  
    405405                                         ptab(nlci-jpreci+1:jpi   ,:,:) = zland    ! north 
    406406         ENDIF 
    407          !                                   ! North-South boundaries (always closed) 
    408          IF( .NOT. cd_type == 'F' )   ptab(:,     1       :jprecj,:) = zland       ! south except F-point 
    409                                       ptab(:,nlcj-jprecj+1:jpj   ,:) = zland       ! north 
     407                                          ! North-south cyclic 
     408         IF ( nbondj == 2 .AND. jperio == 7 )    THEN !* cyclic north south only with no mpp split in latitude 
     409            ptab(:,1 , :) = ptab(:, jpjm1,:) 
     410            ptab(:,jpj,:) = ptab(:,     2,:) 
     411         ELSE   !                                   ! North-South boundaries (closed) 
     412            IF( .NOT. cd_type == 'F' )   ptab(:,     1       :jprecj,:) = zland       ! south except F-point 
     413                                         ptab(:,nlcj-jprecj+1:jpj   ,:) = zland       ! north 
     414         ENDIF 
    410415         ! 
    411416      ENDIF 
     
    608613                                                   pt2d_array(ii)%pt2d(nlci-jpreci+1 : jpi   ,:) = zland    ! north 
    609614            ENDIF 
    610             !                                   ! North-South boundaries (always closed) 
     615                                                ! Noth-South boundaries 
     616            IF ( nbondj == 2 .AND. jperio == 7 )    THEN !* cyclic north south 
     617               pt2d_array(ii)%pt2d(:, 1   ) =   pt2d_array(ii)%pt2d(:, jpjm1 ) 
     618               pt2d_array(ii)%pt2d(:, jpj ) =   pt2d_array(ii)%pt2d(:, 2 )           
     619            ELSE   !              
     620               !                                   ! North-South boundaries (closed) 
    611621               IF( .NOT. type_array(ii) == 'F' )   pt2d_array(ii)%pt2d(:,             1:jprecj ) = zland    ! south except F-point 
    612622                                                   pt2d_array(ii)%pt2d(:, nlcj-jprecj+1:jpj    ) = zland    ! north 
    613623            ! 
    614          ENDIF 
     624            ENDIF 
     625          ENDIF 
    615626      END DO 
    616627 
     
    888899                                         pt2d(nlci-jpreci+1:jpi   ,:) = zland    ! north 
    889900         ENDIF 
    890          !                                   ! North-South boundaries (always closed) 
     901                                            ! North-South boudaries 
     902         IF ( nbondj == 2 .AND. jperio == 7 )    THEN !* cyclic north south 
     903            pt2d(:,  1 ) = pt2d(:,jpjm1) 
     904            pt2d(:, jpj) = pt2d(:,    2) 
     905         ELSE     
     906         !                                   ! North-South boundaries (closed) 
    891907            IF( .NOT. cd_type == 'F' )   pt2d(:,     1       :jprecj) = zland    !south except F-point 
    892908                                         pt2d(:,nlcj-jprecj+1:jpj   ) = zland    ! north 
    893          ! 
     909         ENDIF      
    894910      ENDIF 
    895911 
     
    10711087                                       ptab2(nlci-jpreci+1:jpi   ,:,:) = 0.e0 
    10721088      ENDIF 
    1073  
    1074  
    1075       !                                      ! North-South boundaries 
     1089                                            ! North-South boundaries 
     1090      IF ( nbondj == 2 .AND. jperio == 7 )    THEN !* cyclic north south 
     1091         ptab1(:,     1       ,:) = ptab1(: ,  jpjm1 , :) 
     1092         ptab1(:,   jpj       ,:) = ptab1(: ,      2 , :) 
     1093         ptab2(:,     1       ,:) = ptab2(: ,  jpjm1 , :) 
     1094         ptab2(:,   jpj       ,:) = ptab2(: ,      2 , :) 
     1095      ELSE      
     1096      !                                      ! North-South boundaries closed 
    10761097      IF( .NOT. cd_type1 == 'F' )   ptab1(:,     1       :jprecj,:) = 0.e0    ! south except at F-point 
    10771098      IF( .NOT. cd_type2 == 'F' )   ptab2(:,     1       :jprecj,:) = 0.e0 
    10781099                                    ptab1(:,nlcj-jprecj+1:jpj   ,:) = 0.e0    ! north 
    10791100                                    ptab2(:,nlcj-jprecj+1:jpj   ,:) = 0.e0 
    1080  
     1101      ENDIF      
    10811102 
    10821103      ! 2. East and west directions exchange 
     
    12671288      ! Order matters Here !!!! 
    12681289      ! 
    1269       !                                      !* North-South boundaries (always colsed) 
     1290                                           ! North-South cyclic 
     1291      IF ( nbondj == 2 .AND. jperio == 7 )    THEN !* cyclic north south 
     1292         pt2d(:, 1-jprj:  1     ) = pt2d ( :, jpjm1-jprj:jpjm1) 
     1293         pt2d(:, jpj   :jpj+jprj) = pt2d ( :, 2         :2+jprj) 
     1294      ELSE 
     1295         
     1296      !                                      !* North-South boundaries (closed) 
    12701297      IF( .NOT. cd_type == 'F' )   pt2d(:,  1-jprj   :  jprecj  ) = 0.e0    ! south except at F-point 
    12711298                                   pt2d(:,nlcj-jprecj+1:jpj+jprj) = 0.e0    ! north 
    1272  
     1299      ENDIF 
     1300                                 
    12731301      !                                      ! East-West boundaries 
    12741302      !                                           !* Cyclic east-west 
     
    43044332            WRITE(kout,*) 
    43054333         ENDIF 
     4334         CALL FLUSH(kout)  
    43064335         STOP 'ctl_opn bad opening' 
    43074336      ENDIF 
     
    43204349      INTEGER         , INTENT(inout) ::   kios    ! IO status after reading the namelist 
    43214350      CHARACTER(len=*), INTENT(in   ) ::   cdnam   ! group name of namelist for which error occurs 
    4322       CHARACTER(len=4)                ::   clios   ! string to convert iostat in character for print 
     4351      CHARACTER(len=5)                ::   clios   ! string to convert iostat in character for print 
    43234352      LOGICAL         , INTENT(in   ) ::   ldwp    ! boolean term for print 
    43244353      !!---------------------------------------------------------------------- 
    43254354      ! 
    4326       WRITE (clios, '(I4.0)')   kios 
     4355      WRITE (clios, '(I5.0)')   kios 
    43274356      IF( kios < 0 ) THEN          
    43284357         CALL ctl_warn( 'end of record or file while reading namelist '   & 
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r6412 r7646  
    6565         WRITE(numout,*) 
    6666         WRITE(numout,*) 'mpp_init(2) : NO massively parallel processing' 
    67          WRITE(numout,*) '~~~~~~~~~~~: ' 
     67         WRITE(numout,*) '~~~~~~~~~~~ ' 
    6868         WRITE(numout,*) '         nperio = ', nperio 
    6969         WRITE(numout,*) '         npolj  = ', npolj 
     
    7676          &              'the domain is lay out for distributed memory computing! ' ) 
    7777 
     78      IF( jperio == 7 ) CALL ctl_stop( ' jperio = 7 needs distributed memory computing ',   & 
     79          &              ' with 1 process. Add key_mpp_mpi in the list of active cpp keys ' ) 
    7880   END SUBROUTINE mpp_init 
    7981 
     
    265267       
    266268      IF(lwp) WRITE(numout,*) 
    267       IF(lwp) WRITE(numout,*) ' mpp_init: defines mpp subdomains' 
    268       IF(lwp) WRITE(numout,*) ' ~~~~~~  ----------------------' 
    269       IF(lwp) WRITE(numout,*) 
    270       IF(lwp) WRITE(numout,*) 'iresti=',iresti,' irestj=',irestj 
    271       IF(lwp) WRITE(numout,*) 
    272       IF(lwp) WRITE(numout,*) 'jpni=',jpni,' jpnj=',jpnj 
     269      IF(lwp) WRITE(numout,*) '   defines mpp subdomains' 
     270      IF(lwp) WRITE(numout,*) '      jpni=', jpni, ' iresti=', iresti 
     271      IF(lwp) WRITE(numout,*) '      jpnj=', jpnj, ' irestj=', irestj 
    273272      zidom = nreci 
    274273      DO ji = 1, jpni 
     
    276275      END DO 
    277276      IF(lwp) WRITE(numout,*) 
    278       IF(lwp) WRITE(numout,*)' sum ilcit(i,1)=', zidom, ' jpiglo=', jpiglo 
     277      IF(lwp) WRITE(numout,*)'      sum ilcit(i,1)=', zidom, ' jpiglo=', jpiglo 
    279278 
    280279      zjdom = nrecj 
     
    282281         zjdom = zjdom + ilcjt(1,jj) - nrecj 
    283282      END DO 
    284       IF(lwp) WRITE(numout,*)' sum ilcit(1,j)=', zjdom, ' jpjglo=', jpjglo 
    285       IF(lwp) WRITE(numout,*) 
     283      IF(lwp) WRITE(numout,*)'      sum ilcit(1,j)=', zjdom, ' jpjglo=', jpjglo 
    286284 
    287285      IF(lwp) THEN 
     
    360358      njmpp  = njmppt(narea)   
    361359 
    362      ! Save processor layout in layout.dat file  
    363        IF (lwp) THEN 
    364         CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    365         WRITE(inum,'(a)') '   jpnij     jpi     jpj     jpk  jpiglo  jpjglo' 
    366         WRITE(inum,'(6i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo 
    367         WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp' 
    368  
    369         DO jn = 1, jpnij 
    370          WRITE(inum,'(9i5)') jn, nlcit(jn), nlcjt(jn), & 
    371                                       nldit(jn), nldjt(jn), & 
    372                                       nleit(jn), nlejt(jn), & 
    373                                       nimppt(jn), njmppt(jn) 
    374         END DO 
    375         CLOSE(inum)    
     360      ! Save processor layout in layout.dat file  
     361      IF(lwp) THEN 
     362         CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
     363         WRITE(inum,'(a)') '   jpnij     jpi     jpj     jpk  jpiglo  jpjglo' 
     364         WRITE(inum,'(6i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo 
     365         WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp' 
     366         ! 
     367         DO jn = 1, jpnij 
     368            WRITE(inum,'(9i5)') jn, nlcit(jn), nlcjt(jn), & 
     369               &                    nldit(jn), nldjt(jn), & 
     370               &                    nleit(jn), nlejt(jn), & 
     371               &                    nimppt(jn), njmppt(jn) 
     372         END DO 
     373         CLOSE(inum)    
    376374      END IF 
    377375 
    378  
    379376      ! w a r n i n g  narea (zone) /= nproc (processors)! 
    380377 
    381       IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 ) THEN 
     378      IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7 ) THEN 
    382379         IF( jpni == 1 )THEN 
    383380            nbondi = 2 
     
    428425 
    429426      IF(lwp) THEN 
    430          WRITE(numout,*) ' nproc  = ', nproc 
    431          WRITE(numout,*) ' nowe   = ', nowe  , ' noea   =  ', noea 
    432          WRITE(numout,*) ' nono   = ', nono  , ' noso   =  ', noso 
    433          WRITE(numout,*) ' nbondi = ', nbondi 
    434          WRITE(numout,*) ' nbondj = ', nbondj 
    435          WRITE(numout,*) ' npolj  = ', npolj 
    436          WRITE(numout,*) ' nperio = ', nperio 
    437          WRITE(numout,*) ' nlci   = ', nlci 
    438          WRITE(numout,*) ' nlcj   = ', nlcj 
    439          WRITE(numout,*) ' nimpp  = ', nimpp 
    440          WRITE(numout,*) ' njmpp  = ', njmpp 
    441          WRITE(numout,*) ' nreci  = ', nreci  , ' npse   = ', npse 
    442          WRITE(numout,*) ' nrecj  = ', nrecj  , ' npsw   = ', npsw 
    443          WRITE(numout,*) ' jpreci = ', jpreci , ' npne   = ', npne 
    444          WRITE(numout,*) ' jprecj = ', jprecj , ' npnw   = ', npnw 
     427         WRITE(numout,*) '      nproc  = ', nproc 
     428         WRITE(numout,*) '      nowe   = ', nowe  , '      noea   =  ', noea 
     429         WRITE(numout,*) '      nono   = ', nono  , '      noso   =  ', noso 
     430         WRITE(numout,*) '      nbondi = ', nbondi, '      nbondj = ', nbondj 
     431         WRITE(numout,*) '      npolj  = ', npolj 
     432         WRITE(numout,*) '      nperio = ', nperio 
     433         WRITE(numout,*) '      nlci   = ', nlci  , '      nlcj   = ', nlcj 
     434         WRITE(numout,*) '      nimpp  = ', nimpp , '      njmpp  = ', njmpp 
     435         WRITE(numout,*) '      nreci  = ', nreci , '      npse   = ', npse 
     436         WRITE(numout,*) '      nrecj  = ', nrecj , '      npsw   = ', npsw 
     437         WRITE(numout,*) '      jpreci = ', jpreci, '      npne   = ', npne 
     438         WRITE(numout,*) '      jprecj = ', jprecj, '      npnw   = ', npnw 
    445439         WRITE(numout,*) 
    446440      ENDIF 
    447441 
     442      IF( jperio == 7 .AND. ( jpni /= 1 .OR. jpnj /= 1 ) ) & 
     443         &                  CALL ctl_stop( ' mpp_init: error jperio = 7 works only with jpni = jpnj = 1' ) 
    448444      IF( nperio == 1 .AND. jpni /= 1 ) CALL ctl_stop( ' mpp_init: error on cyclicity' ) 
    449445 
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/mppini_2.h90

    r6412 r7646  
    66      !!     FOR USING THIS VERSION, A PREPROCESSING TRAITMENT IS RECOMMENDED 
    77      !!     FOR DEFINING BETTER CUTTING OUT. 
    8       !!       This routine is used with a the bathymetry file. 
     8      !!       This routine requires the presence of the domain configuration file. 
    99      !!       In this version, the land processors are avoided and the adress 
    1010      !!     processor (nproc, narea,noea, ...) are calculated again. 
     
    3232      !!                    nono      : number for local neighboring processor 
    3333      !! 
    34       !! History : 
    35       !!        !  94-11  (M. Guyon)  Original code 
    36       !!        !  95-04  (J. Escobar, M. Imbard) 
    37       !!        !  98-02  (M. Guyon)  FETI method 
    38       !!        !  98-05  (M. Imbard, J. Escobar, L. Colombet )  SHMEM and MPI versions 
    39       !!   9.0  !  04-01  (G. Madec, J.M Molines)  F90 : free form , north fold jpni > 1 
     34      !! History :       !  1994-11  (M. Guyon)  Original code 
     35      !!  OPA            !  1995-04  (J. Escobar, M. Imbard) 
     36      !!                 !  1998-02  (M. Guyon)  FETI method 
     37      !!                 !  1998-05  (M. Imbard, J. Escobar, L. Colombet )  SHMEM and MPI versions 
     38      !!  NEMO      1.0  !  2004-01  (G. Madec, J.M Molines)  F90 : free form , north fold jpni > 1 
     39      !!            4.0  !  2016-06  (G. Madec)  use domain configuration file instead of bathymetry file 
    4040      !!---------------------------------------------------------------------- 
    4141      USE in_out_manager  ! I/O Manager 
    4242      USE iom 
     43      USE bdy_oce 
    4344      !!  
    4445      INTEGER :: ji, jj, jn, jproc, jarea     ! dummy loop indices 
     
    6566         ione  , ionw  , iose  , iosw  ,   &  !    "           " 
    6667         ibne  , ibnw  , ibse  , ibsw         !    "           " 
    67       INTEGER,  DIMENSION(jpiglo,jpjglo) ::   & 
    68          imask                                ! temporary global workspace 
    69       REAL(wp), DIMENSION(jpiglo,jpjglo) ::   & 
    70          zdta, zdtaisf                     ! temporary data workspace 
    71       REAL(wp) ::   zidom , zjdom          ! temporary scalars 
    72  
    73       ! read namelist for ln_zco 
    74       NAMELIST/namzgr/ ln_zco, ln_zps, ln_sco, ln_isfcav, ln_linssh 
    75  
     68      INTEGER,  DIMENSION(jpiglo,jpjglo) ::   imask               ! global workspace 
     69      REAL(wp), DIMENSION(jpiglo,jpjglo) ::   zbot, ztop          ! global workspace 
     70      REAL(wp) ::   zidom , zjdom          ! local scalars 
     71      NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,         & 
     72         &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
     73         &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             &   
     74         &             ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, & 
     75         &             cn_ice_lim, nn_ice_lim_dta,                           & 
     76         &             rn_ice_tem, rn_ice_sal, rn_ice_age,                 & 
     77         &             ln_vol, nn_volctl, nn_rimwidth, nb_jpk_bdy 
    7678      !!---------------------------------------------------------------------- 
    77       !!  OPA 9.0 , LOCEAN-IPSL (2005)  
     79      !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    7880      !! $Id$ 
    79       !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     81      !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    8082      !!---------------------------------------------------------------------- 
    8183 
    82       REWIND( numnam_ref )              ! Namelist namzgr in reference namelist : Vertical coordinate 
    83       READ  ( numnam_ref, namzgr, IOSTAT = ios, ERR = 901) 
    84 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in reference namelist', lwp ) 
    85  
    86       REWIND( numnam_cfg )              ! Namelist namzgr in configuration namelist : Vertical coordinate 
    87       READ  ( numnam_cfg, namzgr, IOSTAT = ios, ERR = 902 ) 
    88 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in configuration namelist', lwp ) 
    89       IF(lwm) WRITE ( numond, namzgr ) 
    90  
    9184      IF(lwp)WRITE(numout,*) 
    92       IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing MPI' 
    93       IF(lwp)WRITE(numout,*) '~~~~~~~~' 
     85      IF(lwp)WRITE(numout,*) 'mpp_init_2 : Message Passing MPI' 
     86      IF(lwp)WRITE(numout,*) '~~~~~~~~~~' 
    9487      IF(lwp)WRITE(numout,*) ' ' 
    9588 
    96       IF( jpni*jpnj < jpnij ) CALL ctl_stop( ' jpnij > jpni x jpnj impossible' ) 
     89      IF( jpni*jpnj < jpnij )   CALL ctl_stop( ' jpnij > jpni x jpnj impossible' ) 
    9790 
    9891      ! 0. initialisation 
    9992      ! ----------------- 
    100  
    101       ! open the file 
    102       ! Remember that at this level in the code, mpp is not yet initialized, so 
    103       ! the file must be open with jpdom_unknown, and kstart and kcount forced  
    104       jstartrow = 1 
    105       IF ( ln_zco ) THEN  
    106          CALL iom_open ( 'bathy_level.nc', inum )   ! Level bathymetry 
    107           ! Optionally use a file attribute (open_ocean_jstart) to set a start row for reading from the global file 
    108           ! This allows the unextended grid bathymetry to be stored in the same file as the under ice-shelf extended bathymetry 
    109          CALL iom_getatt(inum, 'open_ocean_jstart', jstartrow ) ! -999 is returned if the attribute is not found 
    110          jstartrow = MAX(1,jstartrow) 
    111          CALL iom_get ( inum, jpdom_unknown, 'Bathy_level', zdta, kstart=(/jpizoom,jpjzoom+jstartrow-1/), kcount=(/jpiglo,jpjglo/) ) 
    112       ELSE 
    113          CALL iom_open ( 'bathy_meter.nc', inum )   ! Meter bathy in case of partial steps 
    114          IF ( ln_isfcav ) THEN 
    115              CALL iom_get ( inum, jpdom_unknown, 'Bathymetry_isf' , zdta, kstart=(/jpizoom,jpjzoom/), kcount=(/jpiglo,jpjglo/) ) 
    116          ELSE 
    117              ! Optionally use a file attribute (open_ocean_jstart) to set a start row for reading from the global file 
    118              ! This allows the unextended grid bathymetry to be stored in the same file as the under ice-shelf extended bathymetry 
    119              CALL iom_getatt(inum, 'open_ocean_jstart', jstartrow ) ! -999 is returned if the attribute is not found 
    120              jstartrow = MAX(1,jstartrow) 
    121              CALL iom_get ( inum, jpdom_unknown, 'Bathymetry' , zdta, kstart=(/jpizoom,jpjzoom+jstartrow-1/)   & 
    122                 &                                                   , kcount=(/jpiglo,jpjglo/) ) 
    123          ENDIF 
    124       ENDIF 
    125       CALL iom_close (inum) 
    126        
    127       ! used to compute the land processor in case of not masked bathy file. 
    128       zdtaisf(:,:) = 0.0_wp 
    129       IF ( ln_isfcav ) THEN 
    130          CALL iom_open ( 'bathy_meter.nc', inum )   ! Meter bathy in case of partial steps 
    131          CALL iom_get ( inum, jpdom_unknown, 'isf_draft' , zdtaisf, kstart=(/jpizoom,jpjzoom/), kcount=(/jpiglo,jpjglo/) ) 
    132       END IF 
    133       CALL iom_close (inum) 
    134  
    135       ! land/sea mask over the global/zoom domain 
    136  
    137       imask(:,:)=1 
    138       WHERE ( zdta(:,:) - zdtaisf(:,:) <= rn_isfhmin ) imask = 0 
     93      CALL iom_open( cn_domcfg, inum ) 
     94      ! 
     95      !                                   ! ocean top and bottom level 
     96      CALL iom_get( inum, jpdom_data, 'bottom_level' , zbot    )  ! nb of ocean T-points 
     97      CALL iom_get( inum, jpdom_data, 'top_level'    , ztop    )  ! nb of ocean T-points (ISF) 
     98      ! 
     99      CALL iom_close( inum ) 
     100      ! 
     101      ! 2D ocean mask (=1 if at least one level of the water column is ocean, =0 otherwise) 
     102      WHERE( zbot(:,:) - ztop(:,:) + 1 > 0 )   ;   imask(:,:) = 1 
     103      ELSEWHERE                                ;   imask(:,:) = 0 
     104      END WHERE 
     105 
     106      ! Adjust imask with bdy_msk if exists 
     107 
     108      REWIND( numnam_ref )              ! Namelist nambdy in reference namelist : BDY 
     109      READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903) 
     110903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy in reference namelist (mppini_2)', lwp ) 
     111 
     112      REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist : BDY 
     113      READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 904 ) 
     114904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy in configuration namelist (mppini_2)', lwp ) 
     115 
     116      IF( ln_bdy .AND. ln_mask_file ) THEN 
     117         CALL iom_open( cn_mask_file, inum ) 
     118         CALL iom_get ( inum, jpdom_data, 'bdy_msk', bdytmask(:,:) ) 
     119         CALL iom_close( inum ) 
     120         WHERE ( bdytmask(:,:) <= 0. ) imask = 0 
     121      ENDIF 
    139122 
    140123      !  1. Dimension arrays for subdomains 
     
    322305         DO jj = 1, ilj 
    323306            DO  ji = 1, ili 
    324                IF( imask(ji+iimppt(ii,ij)-1, jj+ijmppt(ii,ij)-1) == 1) isurf = isurf+1 
     307               IF( imask(ji+iimppt(ii,ij)-1, jj+ijmppt(ii,ij)-1) == 1)   isurf = isurf+1 
    325308            END DO 
    326309         END DO 
Note: See TracChangeset for help on using the changeset viewer.