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 5682 for branches/2015/dev_r5072_UKMO2_OBS_simplification/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2015-08-12T17:46:45+02:00 (9 years ago)
Author:
mattmartin
Message:

OBS simplification changes committed to branch after running SETTE tests to make sure we get the same results as the trunk for ORCA2_LIM_OBS.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5072_UKMO2_OBS_simplification/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r4990 r5682  
    8282   USE crsini          ! initialise grid coarsening utility 
    8383   USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges  
     84   USE sbc_oce, ONLY: lk_oasis 
     85   USE stopar 
     86   USE stopts 
    8487 
    8588   IMPLICIT NONE 
     
    158161          ENDIF 
    159162 
     163#if defined key_agrif 
     164          CALL Agrif_Regrid() 
     165#endif 
     166 
    160167         DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    161168#if defined key_agrif 
    162             CALL Agrif_Step( stp )           ! AGRIF: time stepping 
     169            CALL stp                         ! AGRIF: time stepping 
    163170#else 
    164171            CALL stp( istp )                 ! standard time stepping 
     
    169176#endif 
    170177 
    171       IF( lk_diaobs   )   CALL dia_obs_wri 
     178      IF( ln_diaobs   )   CALL dia_obs_wri 
    172179      ! 
    173180      IF( ln_icebergs )   CALL icb_end( nitend ) 
     
    184191      ! 
    185192#if defined key_agrif 
    186       CALL Agrif_ParentGrid_To_ChildGrid() 
    187       IF( lk_diaobs ) CALL dia_obs_wri 
    188       IF( nn_timing == 1 )   CALL timing_finalize 
    189       CALL Agrif_ChildGrid_To_ParentGrid() 
     193      IF( .NOT. Agrif_Root() ) THEN 
     194         CALL Agrif_ParentGrid_To_ChildGrid() 
     195         IF( ln_diaobs ) CALL dia_obs_wri 
     196         IF( nn_timing == 1 )   CALL timing_finalize 
     197         CALL Agrif_ChildGrid_To_ParentGrid() 
     198      ENDIF 
    190199#endif 
    191200      IF( nn_timing == 1 )   CALL timing_finalize 
     
    195204#if defined key_iomput 
    196205      CALL xios_finalize                ! end mpp communications with xios 
    197       IF( lk_cpl ) CALL cpl_finalize    ! end coupling and mpp communications with OASIS 
     206      IF( lk_oasis ) CALL cpl_finalize    ! end coupling and mpp communications with OASIS 
    198207#else 
    199       IF( lk_cpl ) THEN  
     208      IF( lk_oasis ) THEN  
    200209         CALL cpl_finalize              ! end coupling and mpp communications with OASIS 
    201210      ELSE 
     
    222231         &             nn_bench, nn_timing 
    223232      NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    224          &             jpizoom, jpjzoom, jperio 
     233         &             jpizoom, jpjzoom, jperio, ln_use_jattr 
    225234      !!---------------------------------------------------------------------- 
    226235      ! 
    227236      cltxt = '' 
     237      cxios_context = 'nemo' 
    228238      ! 
    229239      !                             ! Open reference namelist and configuration namelist files 
     
    261271      nperio  = 0 
    262272      jperio  = 0 
     273      ln_use_jattr = .false. 
    263274   ENDIF 
    264275#endif 
     
    271282#if defined key_iomput 
    272283      IF( Agrif_Root() ) THEN 
    273          IF( lk_cpl ) THEN 
    274             CALL cpl_init( ilocal_comm )                               ! nemo local communicator given by oasis 
    275             CALL xios_initialize( "oceanx",local_comm=ilocal_comm )    ! send nemo communicator to xios 
     284         IF( lk_oasis ) THEN 
     285            CALL cpl_init( "oceanx", ilocal_comm )                     ! nemo local communicator given by oasis 
     286            CALL xios_initialize( "not used",local_comm=ilocal_comm )    ! send nemo communicator to xios 
    276287         ELSE 
    277             CALL  xios_initialize( "nemo",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
     288            CALL  xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
    278289         ENDIF 
    279290      ENDIF 
    280       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
     291      ! Nodes selection (control print return in cltxt) 
     292      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    281293#else 
    282       IF( lk_cpl ) THEN 
     294      IF( lk_oasis ) THEN 
    283295         IF( Agrif_Root() ) THEN 
    284             CALL cpl_init( ilocal_comm )                       ! nemo local communicator given by oasis 
     296            CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
    285297         ENDIF 
    286          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
     298         ! Nodes selection (control print return in cltxt) 
     299         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    287300      ELSE 
    288301         ilocal_comm = 0 
    289          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
     302         ! Nodes selection (control print return in cltxt) 
     303         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
    290304      ENDIF 
    291305#endif 
     
    326340         jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim. 
    327341#endif 
    328       ENDIF 
     342      ENDIF          
    329343         jpk = jpkdta                                             ! third dim 
     344#if defined key_agrif 
     345         ! simple trick to use same vertical grid as parent 
     346         ! but different number of levels:  
     347         ! Save maximum number of levels in jpkdta, then define all vertical grids 
     348         ! with this number. 
     349         ! Suppress once vertical online interpolation is ok 
     350         IF(.NOT.Agrif_Root()) jpkdta = Agrif_Parent(jpkdta) 
     351#endif 
    330352         jpim1 = jpi-1                                            ! inner domain indices 
    331353         jpjm1 = jpj-1                                            !   "           " 
     
    341363         WRITE(numout,*) '                       NEMO team' 
    342364         WRITE(numout,*) '            Ocean General Circulation Model' 
    343          WRITE(numout,*) '                  version 3.4  (2011) ' 
     365         WRITE(numout,*) '                  version 3.6  (2015) ' 
    344366         WRITE(numout,*) 
    345367         WRITE(numout,*) 
     
    383405      IF( lk_tide       )   CALL    tide_init( nit000 )    ! Initialisation of the tidal harmonics 
    384406 
     407                            CALL     sbc_init   ! Forcings : surface module (clem: moved here for bdy purpose) 
     408 
    385409      IF( lk_bdy        )   CALL     bdy_init   ! Open boundaries initialisation 
    386410      IF( lk_bdy        )   CALL bdy_dta_init   ! Open boundaries initialisation of external data arrays 
     
    389413 
    390414                            CALL dyn_nept_init  ! simplified form of Neptune effect 
    391  
    392415      !      
    393416      IF( ln_crs        )   CALL     crs_init   ! Domain initialization of coarsened grid 
    394417      ! 
    395418                                ! Ocean physics 
    396                             CALL     sbc_init   ! Forcings : surface module 
    397419      !                                         ! Vertical physics 
    398420                            CALL     zdf_init      ! namelist read 
     
    431453      IF( nn_cla == 1 .AND. cp_cfg == 'orca' .AND. jp_cfg == 2 )   CALL cla_init       ! Cross Land Advection 
    432454                            CALL icb_init( rdt, nit000)   ! initialise icebergs instance 
     455                            CALL sto_par_init   ! Stochastic parametrization 
     456      IF( ln_sto_eos     )  CALL sto_pts_init   ! RRandom T/S fluctuations 
    433457      
    434458#if defined key_top 
     
    443467                            CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    444468                            CALL     trd_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    445       IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    446469                            CALL dia_obs_init            ! Initialize observational data 
    447                             CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    448       ENDIF 
    449  
    450       !                                     ! Assimilation increments 
     470      IF( ln_diaobs     )   CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
     471 
     472      !                                         ! Assimilation increments 
    451473      IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    452474      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     
    506528         WRITE(numout,*) '      left bottom j index of the zoom (in data domain) jpizoom = ', jpjzoom 
    507529         WRITE(numout,*) '      lateral cond. type (between 0 and 6) jperio = ', jperio    
     530         WRITE(numout,*) '      use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr 
    508531      ENDIF 
    509532      !                             ! Parameter control 
     
    699722      INTEGER :: ifac, jl, inu 
    700723      INTEGER, PARAMETER :: ntest = 14 
    701       INTEGER :: ilfax(ntest) 
    702       ! 
     724      INTEGER, DIMENSION(ntest) :: ilfax 
     725      !!---------------------------------------------------------------------- 
    703726      ! lfax contains the set of allowed factors. 
    704       data (ilfax(jl),jl=1,ntest) / 16384, 8192, 4096, 2048, 1024, 512, 256,  & 
    705          &                            128,   64,   32,   16,    8,   4,   2  / 
    706       !!---------------------------------------------------------------------- 
     727      ilfax(:) = (/(2**jl,jl=ntest,1,-1)/) 
    707728 
    708729      ! Clear the error flag and initialise output vars 
Note: See TracChangeset for help on using the changeset viewer.