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 3331 for branches/2012/dev_r3322_NOCS09_SAS/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2012-03-19T15:52:27+01:00 (12 years ago)
Author:
sga
Message:

NEMO 2012 development branch dev_r3322_NOCS09_SAS
Code changes made for compilation and running of StandAlone? Surface scheme (tinkering still required)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3322_NOCS09_SAS/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r3324 r3331  
    4444   USE cla             ! cross land advection               (tra_cla routine) 
    4545   USE domcfg          ! domain configuration               (dom_cfg routine) 
     46   USE daymod          ! calendar 
    4647   USE mppini          ! shared/distributed memory setting (mpp_init routine) 
    4748   USE domain          ! domain initialization             (dom_init routine) 
    48    USE obcini          ! open boundary cond. initialization (obc_ini routine) 
    49    USE bdyini          ! open boundary cond. initialization (bdy_init routine) 
    50    USE bdydta          ! open boundary cond. initialization (bdy_dta_init routine) 
    51    USE bdytides        ! open boundary cond. initialization (tide_init routine) 
    52    USE istate          ! initial state setting          (istate_init routine) 
    53    USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine) 
    54    USE ldftra          ! lateral diffusivity setting    (ldftra_init routine) 
    55    USE zdfini          ! vertical physics setting          (zdf_init routine) 
    5649   USE phycst          ! physical constant                  (par_cst routine) 
    57    USE trdmod          ! momentum/tracers trends       (trd_mod_init routine) 
    58    USE asmtrj          ! writing out state trajectory 
    59    USE diaptr          ! poleward transports           (dia_ptr_init routine) 
    60    USE diadct          ! sections transports           (dia_dct_init routine) 
    61    USE diaobs          ! Observation diagnostics       (dia_obs_init routine) 
    6250   USE step            ! NEMO time-stepping                 (stp     routine) 
    63 #if defined key_oasis3 
    64    USE cpl_oasis3      ! OASIS3 coupling 
    65 #elif defined key_oasis4 
    66    USE cpl_oasis4      ! OASIS4 coupling (not working) 
    67 #endif 
    68    USE c1d             ! 1D configuration 
    69    USE step_c1d        ! Time stepping loop for the 1D configuration 
    70 #if defined key_top 
    71    USE trcini          ! passive tracer initialisation 
    72 #endif 
    7351   USE lib_mpp         ! distributed memory computing 
    7452#if defined key_iomput 
    7553   USE mod_ioclient 
    7654#endif 
     55   USE sbcsas 
    7756 
    7857   IMPLICIT NONE 
     
    11796#if defined key_agrif 
    11897      CALL Agrif_Declare_Var       ! AGRIF: set the meshes 
    119 # if defined key_top 
    120       CALL Agrif_Declare_Var_Top   ! AGRIF: set the meshes 
    121 # endif 
    12298#endif 
    12399      ! check that all process are still there... If some process have an error, 
     
    131107      !                            !-----------------------! 
    132108      istp = nit000 
    133 #if defined key_c1d 
    134          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    135             CALL stp_c1d( istp ) 
    136             istp = istp + 1 
    137          END DO 
     109         
     110      DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
     111#if defined key_agrif 
     112         CALL Agrif_Step( stp )           ! AGRIF: time stepping 
    138113#else 
    139           IF( lk_asminc ) THEN 
    140              IF( ln_bkgwri ) CALL asm_bkg_wri( nit000 - 1 )    ! Output background fields 
    141              IF( ln_trjwri ) CALL asm_trj_wri( nit000 - 1 )    ! Output trajectory fields 
    142              IF( ln_asmdin ) THEN                        ! Direct initialization 
    143                 IF( ln_trainc ) CALL tra_asm_inc( nit000 - 1 )    ! Tracers 
    144                 IF( ln_dyninc ) THEN  
    145                    CALL dyn_asm_inc( nit000 - 1 )    ! Dynamics 
    146                    IF ( ln_asmdin ) CALL ssh_wzv ( nit000 - 1 )      ! update vertical velocity  
    147                 ENDIF 
    148                 IF( ln_sshinc ) CALL ssh_asm_inc( nit000 - 1 )    ! SSH 
    149              ENDIF 
    150           ENDIF 
    151          
    152          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    153 #if defined key_agrif 
    154             CALL Agrif_Step( stp )           ! AGRIF: time stepping 
    155 #else 
    156             CALL stp( istp )                 ! standard time stepping 
    157 #endif 
    158             istp = istp + 1 
    159             IF( lk_mpp )   CALL mpp_max( nstop ) 
    160          END DO 
    161 #endif 
    162  
    163       IF( lk_diaobs ) CALL dia_obs_wri 
    164         
     114         CALL stp( istp )                 ! standard time stepping 
     115#endif 
     116         istp = istp + 1 
     117         IF( lk_mpp )   CALL mpp_max( nstop ) 
     118      END DO 
    165119      !                            !------------------------! 
    166120      !                            !==  finalize the run  ==! 
     
    175129#if defined key_agrif 
    176130      CALL Agrif_ParentGrid_To_ChildGrid() 
    177       IF( lk_diaobs ) CALL dia_obs_wri 
    178131      IF( nn_timing == 1 )   CALL timing_finalize 
    179132      CALL Agrif_ChildGrid_To_ParentGrid() 
     
    182135      ! 
    183136      CALL nemo_closefile 
    184 #if defined key_oasis3 || defined key_oasis4 
    185       CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
    186 #else 
    187137      IF( lk_mpp )   CALL mppstop       ! end mpp communications 
    188 #endif 
    189138      ! 
    190139   END SUBROUTINE nemo_gcm 
     
    218167#if defined key_iomput 
    219168      IF( Agrif_Root() ) THEN 
    220 # if defined key_oasis3 || defined key_oasis4 
    221          CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis 
    222 # endif 
    223169         CALL  init_ioclient( ilocal_comm )                 ! exchange io_server nemo local communicator with the io_server 
    224170      ENDIF 
    225171      narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection 
    226172#else 
    227 # if defined key_oasis3 || defined key_oasis4 
    228       IF( Agrif_Root() ) THEN 
    229          CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis 
    230       ENDIF 
    231       narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
    232 # else 
    233173      ilocal_comm = 0 
    234174      narea = mynode( cltxt, numnam, nstop )                 ! Nodes selection (control print return in cltxt) 
    235 # endif 
    236175#endif 
    237176      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
     
    277216         WRITE(numout,*) '            Ocean General Circulation Model' 
    278217         WRITE(numout,*) '                  version 3.4  (2011) ' 
     218         WRITE(numout,*) '             StandAlone Surface version (SAS) ' 
    279219         WRITE(numout,*) 
    280220         WRITE(numout,*) 
     
    303243      IF( nn_timing == 1 )  CALL timing_init 
    304244      ! 
    305       !                                      ! General initialization 
    306                             CALL     phy_cst    ! Physical constants 
    307                             CALL     eos_init   ! Equation of state 
    308                             CALL     dom_cfg    ! Domain configuration 
    309                             CALL     dom_init   ! Domain 
     245      !                                     ! General initialization 
     246                            CALL phy_cst    ! Physical constants 
     247                            CALL eos_init   ! Equation of state 
     248                            CALL dom_cfg    ! Domain configuration 
     249                            CALL dom_init   ! Domain 
    310250 
    311251      IF( ln_nnogather )    CALL nemo_northcomms   ! Initialise the northfold neighbour lists (must be done after the masks are defined) 
    312252 
    313253      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
    314  
    315       IF( lk_obc        )   CALL     obc_init   ! Open boundaries  
    316       IF( lk_bdy        )   CALL     bdy_init       ! Open boundaries initialisation 
    317       IF( lk_bdy        )   CALL     bdy_dta_init   ! Open boundaries initialisation of external data arrays 
    318       IF( lk_bdy        )   CALL     tide_init      ! Open boundaries initialisation of tidal harmonic forcing 
    319  
    320254                            CALL flush(numout) 
    321                             CALL dyn_nept_init  ! simplified form of Neptune effect 
    322                             CALL flush(numout) 
    323  
    324                             CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    325  
    326       !                                     ! Ocean physics 
    327                             CALL     sbc_init   ! Forcings : surface module  
    328       !                                         ! Vertical physics 
    329                             CALL     zdf_init      ! namelist read 
    330                             CALL zdf_bfr_init      ! bottom friction 
    331       IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz 
    332       IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme 
    333       IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme 
    334       IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme 
    335       IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing 
    336       IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &  
    337          &                  CALL zdf_ddm_init      ! double diffusive mixing 
    338       !                                         ! Lateral physics 
    339                             CALL ldf_tra_init      ! Lateral ocean tracer physics 
    340                             CALL ldf_dyn_init      ! Lateral ocean momentum physics 
    341       IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing 
    342  
    343       !                                     ! Active tracers 
    344                             CALL tra_qsr_init   ! penetrative solar radiation qsr 
    345                             CALL tra_bbc_init   ! bottom heat flux 
    346       IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    347       IF( ln_tradmp     )   CALL tra_dmp_init   ! internal damping trends 
    348                             CALL tra_adv_init   ! horizontal & vertical advection 
    349                             CALL tra_ldf_init   ! lateral mixing 
    350                             CALL tra_zdf_init   ! vertical mixing and after tracer fields 
    351  
    352       !                                     ! Dynamics 
    353                             CALL dyn_adv_init   ! advection (vector or flux form) 
    354                             CALL dyn_vor_init   ! vorticity term including Coriolis 
    355                             CALL dyn_ldf_init   ! lateral mixing 
    356                             CALL dyn_hpg_init   ! horizontal gradient of Hydrostatic pressure 
    357                             CALL dyn_zdf_init   ! vertical diffusion 
    358                             CALL dyn_spg_init   ! surface pressure gradient 
    359                              
    360       !                                     ! Misc. options 
    361       IF( nn_cla == 1   )   CALL cla_init       ! Cross Land Advection 
     255 
     256                            CALL day_init   ! model calendar (using both namelist and restart infos) 
     257 
     258                            CALL sbc_sas_init   ! initialise standalone scheme 
     259                            CALL sbc_init   ! Forcings : surface module  
    362260       
    363 #if defined key_top 
    364       !                                     ! Passive tracers 
    365                             CALL     trc_init 
    366 #endif 
    367       !                                     ! Diagnostics 
    368       IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
    369                             CALL     iom_init   ! iom_put initialization 
    370       IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    371                             CALL dia_ptr_init   ! Poleward TRansports initialization 
    372       IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    373                             CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    374                             CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    375       IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    376                             CALL dia_obs_init            ! Initialize observational data 
    377                             CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    378       ENDIF       
    379       !                                     ! Assimilation increments 
    380       IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
     261                            CALL iom_init   ! iom_put initialization 
    381262      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
    382263      ! 
     
    464345      ENDIF 
    465346      ! 
    466       IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ',   & 
    467          &                                               'with the IOM Input/Output manager. '         ,   & 
    468          &                                               'Compile with key_iomput enabled' ) 
    469       ! 
    470347   END SUBROUTINE nemo_ctl 
    471348 
     
    483360      ! 
    484361      IF( numstp      /= -1 )   CLOSE( numstp      )   ! time-step file 
    485       IF( numsol      /= -1 )   CLOSE( numsol      )   ! solver file 
    486362      IF( numnam      /= -1 )   CLOSE( numnam      )   ! oce namelist 
    487363      IF( numnam_ice  /= -1 )   CLOSE( numnam_ice  )   ! ice namelist 
    488364      IF( numevo_ice  /= -1 )   CLOSE( numevo_ice  )   ! ice variables (temp. evolution) 
    489365      IF( numout      /=  6 )   CLOSE( numout      )   ! standard model output file 
    490       IF( numdct_vol  /= -1 )   CLOSE( numdct_vol  )   ! volume transports 
    491       IF( numdct_heat /= -1 )   CLOSE( numdct_heat )   ! heat transports 
    492       IF( numdct_salt /= -1 )   CLOSE( numdct_salt )   ! salt transports 
    493  
    494366      ! 
    495367      numout = 6                                     ! redefine numout in case it is used after this point... 
     
    508380      USE diawri    , ONLY: dia_wri_alloc 
    509381      USE dom_oce   , ONLY: dom_oce_alloc 
    510       USE ldfdyn_oce, ONLY: ldfdyn_oce_alloc 
    511       USE ldftra_oce, ONLY: ldftra_oce_alloc 
    512       USE trc_oce   , ONLY: trc_oce_alloc 
    513382      ! 
    514383      INTEGER :: ierr 
     
    518387      ierr = ierr + dia_wri_alloc   () 
    519388      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
    520       ierr = ierr + ldfdyn_oce_alloc()          ! ocean lateral  physics : dynamics 
    521       ierr = ierr + ldftra_oce_alloc()          ! ocean lateral  physics : tracers 
    522       ierr = ierr + zdf_oce_alloc   ()          ! ocean vertical physics 
    523       ! 
    524389      ierr = ierr + lib_mpp_alloc   (numout)    ! mpp exchanges 
    525       ierr = ierr + trc_oce_alloc   ()          ! shared TRC / TRA arrays 
    526390      ! 
    527391      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
Note: See TracChangeset for help on using the changeset viewer.