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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OFF_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (9 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OFF_SRC/nemogcm.F90

    • Property svn:keywords set to Id
    r4640 r6225  
    1818   USE c1d             ! 1D configuration 
    1919   USE domcfg          ! domain configuration               (dom_cfg routine) 
    20    USE domain          ! domain initialization             (dom_init routine) 
    21    USE istate          ! initial state setting          (istate_init routine) 
     20   USE domain          ! domain initialization from coordinate & bathymetry (dom_init routine) 
     21   USE domrea          ! domain initialization from mesh_mask            (dom_init routine) 
    2222   USE eosbn2          ! equation of state            (eos bn2 routine) 
    2323   !              ! ocean physics 
     
    2626   USE traqsr          ! solar radiation penetration    (tra_qsr_init routine) 
    2727   USE trabbl          ! bottom boundary layer          (tra_bbl_init routine) 
     28   USE traldf          ! lateral physics                (tra_ldf_init routine) 
    2829   USE zdfini          ! vertical physics: initialization 
    2930   USE sbcmod          ! surface boundary condition       (sbc_init     routine) 
     
    3435   USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
    3536   USE dtadyn          ! Lecture and interpolation of the dynamical fields 
    36    USE stpctl          ! time stepping control            (stp_ctl routine) 
    3737   !              ! I/O & MPP 
    3838   USE iom             ! I/O library 
     
    4646   USE timing          ! Timing 
    4747   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    48    USE lbcnfd, ONLY: isendto, nsndto 
     48   USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges 
    4949 
    5050   USE trc 
    5151   USE trcnam 
    5252   USE trcrst 
     53   USE diaptr         ! Need to initialise this as some variables are used in if statements later 
     54   USE sbc_oce, ONLY: ln_rnf 
     55   USE sbcrnf 
    5356 
    5457   IMPLICIT NONE 
     
    6164   !!---------------------------------------------------------------------- 
    6265   !! NEMO/OFF 3.3 , NEMO Consortium (2010) 
    63    !! $Id: nemogcm.F90 2528 2010-12-27 17:33:53Z rblod $ 
     66   !! $Id$ 
    6467   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    6568   !!---------------------------------------------------------------------- 
     
    9396      !                            !-----------------------! 
    9497      istp = nit000 
     98      ! 
     99      ! Initialize arrays of runoffs structures and read data from the namelist 
     100      IF ( ln_rnf ) CALL sbc_rnf(istp) 
    95101      !  
    96       CALL iom_init( "nemo" )            ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
     102      CALL iom_init( cxios_context )            ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    97103      !  
    98104      DO WHILE ( istp <= nitend .AND. nstop == 0 )    ! time stepping 
     
    107113      END DO 
    108114#if defined key_iomput 
    109       CALL iom_context_finalize( "nemo" ) ! needed for XIOS+AGRIF 
     115      CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 
    110116#endif 
    111117 
     
    142148      INTEGER ::   ilocal_comm   ! local integer 
    143149      INTEGER ::   ios 
     150      LOGICAL ::   llexist 
    144151      CHARACTER(len=80), DIMENSION(16) ::   cltxt 
    145152      !! 
    146153      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
    147154         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    148          &             nn_bench, nn_timing 
     155         &             nn_bench, nn_timing, nn_diacfl 
    149156      NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    150          &             jpizoom, jpjzoom, jperio 
     157         &             jpizoom, jpjzoom, jperio, ln_use_jattr 
    151158      !!---------------------------------------------------------------------- 
    152159      cltxt = '' 
     160      cxios_context = 'nemo' 
    153161      ! 
    154162      !                             ! Open reference namelist and configuration namelist files 
     
    180188      !                             !--------------------------------------------! 
    181189#if defined key_iomput 
    182       CALL  xios_initialize( "nemo",return_comm=ilocal_comm ) 
    183       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
     190      CALL  xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm ) 
     191      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
    184192#else 
    185193      ilocal_comm = 0 
    186       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
     194      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
    187195#endif 
    188196 
     
    232240         WRITE(numout,*) '                       NEMO team' 
    233241         WRITE(numout,*) '            Ocean General Circulation Model' 
    234          WRITE(numout,*) '                  version 3.5  (2012) ' 
     242         WRITE(numout,*) '                  version 3.6  (2015) ' 
    235243         WRITE(numout,*) 
    236244         WRITE(numout,*) 
     
    267275      IF( lk_c1d        )   CALL     c1d_init   ! 1D column configuration 
    268276                            CALL     dom_cfg    ! Domain configuration 
    269                             CALL     dom_init   ! Domain 
     277      ! 
     278      INQUIRE( FILE='coordinates.nc', EXIST = llexist )   ! Check if coordinate file exist 
     279      ! 
     280      IF( llexist )  THEN  ;  CALL  dom_init   !  compute the grid from coordinates and bathymetry 
     281      ELSE                 ;  CALL  dom_rea    !  read grid from the meskmask 
     282      ENDIF 
    270283                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    271284 
     
    274287      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
    275288 
    276       !                                     ! Ocean physics 
    277289                            CALL     sbc_init   ! Forcings : surface module 
    278 #if ! defined key_degrad 
     290 
    279291                            CALL ldf_tra_init   ! Lateral ocean tracer physics 
    280 #endif 
    281       IF( lk_ldfslp )       CALL ldf_slp_init   ! slope of lateral mixing 
    282  
    283       !                                     ! Active tracers 
     292                            CALL ldf_eiv_init   ! Eddy induced velocity param 
     293                            CALL tra_ldf_init   ! lateral mixing 
     294      IF( l_ldfslp )        CALL ldf_slp_init   ! slope of lateral mixing 
     295 
    284296                            CALL tra_qsr_init   ! penetrative solar radiation qsr 
    285297      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    286298 
    287                             CALL trc_nam_run  ! Needed to get restart parameters for passive tracers 
    288       IF( ln_rsttr ) THEN 
    289         neuler = 1   ! Set time-step indicator at nit000 (leap-frog) 
    290         CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    291       ELSE 
    292         neuler = 0                  ! Set time-step indicator at nit000 (euler) 
    293         CALL day_init               ! set calendar 
    294       ENDIF 
    295       !                                     ! Dynamics 
     299                            CALL trc_nam_run    ! Needed to get restart parameters for passive tracers 
     300                            CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    296301                            CALL dta_dyn_init   ! Initialization for the dynamics 
    297302 
    298       !                                     ! Passive tracers 
    299303                            CALL     trc_init   ! Passive tracers initialization 
    300  
    301       IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA 
     304                            CALL dia_ptr_init   ! Initialise diaptr as some variables are used  
     305      !                                         ! in various advection and diffusion routines 
     306      IF(lwp) WRITE(numout,cform_aaa)           ! Flag AAAAAAA 
    302307      ! 
    303308      IF( nn_timing == 1 )  CALL timing_stop( 'nemo_init') 
     
    354359         WRITE(numout,*) '      left bottom j index of the zoom (in data domain) jpizoom = ', jpjzoom 
    355360         WRITE(numout,*) '      lateral cond. type (between 0 and 6) jperio = ', jperio    
     361         WRITE(numout,*) '      use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr 
    356362      ENDIF 
    357363      !                             ! Parameter control 
     
    444450      USE dom_oce,      ONLY: dom_oce_alloc 
    445451      USE zdf_oce,      ONLY: zdf_oce_alloc 
    446       USE ldftra_oce,   ONLY: ldftra_oce_alloc 
    447452      USE trc_oce,      ONLY: trc_oce_alloc 
    448453      ! 
     
    453458      ierr = ierr + dia_wri_alloc   () 
    454459      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
    455       ierr = ierr + ldftra_oce_alloc()          ! ocean lateral  physics : tracers 
    456460      ierr = ierr + zdf_oce_alloc   ()          ! ocean vertical physics 
    457461      ! 
     
    589593      !!---------------------------------------------------------------------- 
    590594      !!    1.0  ! 2011-10  (A. C. Coward, NOCS & J. Donners, PRACE) 
    591       !!    2.0  ! 2013-06 Setup avoiding MPI communication (I. Epicoco, S. Mocavero, CMCC)  
     595      !!    2.0  ! 2013-06 Setup avoiding MPI communication (I. Epicoco, S. 
     596      !Mocavero, CMCC)  
    592597      !!---------------------------------------------------------------------- 
    593598 
     
    612617          !loop over the other north-fold processes to find the processes 
    613618          !managing the points belonging to the sxT-dxT range 
    614           DO jn = jpnij - jpni +1, jpnij 
    615              IF ( njmppt(jn) == njmppmax ) THEN 
     619 
     620          DO jn = 1, jpni 
    616621                !sxT is the first point (in the global domain) of the jn 
    617622                !process 
    618                 sxT = nimppt(jn) 
     623                sxT = nfiimpp(jn, jpnj) 
    619624                !dxT is the last point (in the global domain) of the jn 
    620625                !process 
    621                 dxT = nimppt(jn) + nlcit(jn) - 1 
     626                dxT = nfiimpp(jn, jpnj) + nfilcit(jn, jpnj) - 1 
    622627                IF ((sxM .gt. sxT) .AND. (sxM .lt. dxT)) THEN 
    623628                   nsndto = nsndto + 1 
    624                    isendto(nsndto) = jn 
    625                 ELSEIF ((sxM .le. sxT) .AND. (dxM .gt. dxT)) THEN 
     629                     isendto(nsndto) = jn 
     630                ELSEIF ((sxM .le. sxT) .AND. (dxM .ge. dxT)) THEN 
    626631                   nsndto = nsndto + 1 
    627                    isendto(nsndto) = jn 
     632                     isendto(nsndto) = jn 
    628633                ELSEIF ((dxM .lt. dxT) .AND. (sxT .lt. dxM)) THEN 
    629634                   nsndto = nsndto + 1 
    630                    isendto(nsndto) = jn 
     635                     isendto(nsndto) = jn 
    631636                END IF 
    632              END IF 
    633637          END DO 
     638          nfsloop = 1 
     639          nfeloop = nlci 
     640          DO jn = 2,jpni-1 
     641           IF(nfipproc(jn,jpnj) .eq. (narea - 1)) THEN 
     642              IF (nfipproc(jn - 1 ,jpnj) .eq. -1) THEN 
     643                 nfsloop = nldi 
     644              ENDIF 
     645              IF (nfipproc(jn + 1,jpnj) .eq. -1) THEN 
     646                 nfeloop = nlei 
     647              ENDIF 
     648           ENDIF 
     649        END DO 
     650 
    634651      ENDIF 
    635652      l_north_nogather = .TRUE. 
    636  
    637653   END SUBROUTINE nemo_northcomms 
    638654#else 
     
    641657   END SUBROUTINE nemo_northcomms 
    642658#endif 
     659 
     660   SUBROUTINE istate_init 
     661      !!---------------------------------------------------------------------- 
     662      !!                   ***  ROUTINE istate_init  *** 
     663      !! 
     664      !! ** Purpose :   Initialization to zero of the dynamics and tracers. 
     665      !!---------------------------------------------------------------------- 
     666      ! 
     667      !     now fields         !     after fields      ! 
     668      un   (:,:,:)   = 0._wp   ;   ua(:,:,:) = 0._wp   ! 
     669      vn   (:,:,:)   = 0._wp   ;   va(:,:,:) = 0._wp   ! 
     670      wn   (:,:,:)   = 0._wp   !                       ! 
     671      hdivn(:,:,:)   = 0._wp   !                       ! 
     672      tsn  (:,:,:,:) = 0._wp   !                       ! 
     673      ! 
     674      rhd  (:,:,:) = 0.e0 
     675      rhop (:,:,:) = 0.e0 
     676      rn2  (:,:,:) = 0.e0 
     677      ! 
     678   END SUBROUTINE istate_init 
     679 
     680   SUBROUTINE stp_ctl( kt, kindic ) 
     681      !!---------------------------------------------------------------------- 
     682      !!                    ***  ROUTINE stp_ctl  *** 
     683      !! 
     684      !! ** Purpose :   Control the run 
     685      !! 
     686      !! ** Method  : - Save the time step in numstp 
     687      !! 
     688      !! ** Actions :   'time.step' file containing the last ocean time-step 
     689      !!---------------------------------------------------------------------- 
     690      INTEGER, INTENT(in   ) ::   kt      ! ocean time-step index 
     691      INTEGER, INTENT(inout) ::   kindic  ! indicator of solver convergence 
     692      !!---------------------------------------------------------------------- 
     693      ! 
     694      IF( kt == nit000 .AND. lwp ) THEN 
     695         WRITE(numout,*) 
     696         WRITE(numout,*) 'stp_ctl : time-stepping control' 
     697         WRITE(numout,*) '~~~~~~~' 
     698         ! open time.step file 
     699         CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     700      ENDIF 
     701      ! 
     702      IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp 
     703      IF(lwp) REWIND( numstp )                       ! -------------------------- 
     704      ! 
     705   END SUBROUTINE stp_ctl 
    643706   !!====================================================================== 
    644707END MODULE nemogcm 
Note: See TracChangeset for help on using the changeset viewer.