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 2496 – NEMO

Changeset 2496


Ignore:
Timestamp:
2010-12-20T16:28:20+01:00 (13 years ago)
Author:
gm
Message:

v3.3beta: cosmetic changes: model.f90 and opa.F90 changed into nemo.f90 and nemogcm.F90, resp.

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO
Files:
2 edited
2 moved

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r2287 r2496  
    6666      USE oce  
    6767      USE dom_oce 
    68       USE opa 
     68      USE nemogcm 
    6969#if defined key_top 
    7070      USE trc 
     
    111111#endif 
    112112 
    113       Call opa_init  ! Initializations of each fine grid 
    114       Call agrif_opa_init 
     113      Call nemo_init  ! Initializations of each fine grid 
     114      Call agrif_nemo_init 
    115115 
    116116      ! 1. Declaration of the type of variable which have to be interpolated 
     
    339339      USE oce  
    340340      USE dom_oce 
    341       USE opa 
     341      USE nemogcm 
    342342      USE trc 
    343343      USE in_out_manager 
     
    359359#endif 
    360360 
    361       Call opa_init  ! Initializations of each fine grid 
    362       Call agrif_opa_init 
     361      Call nemo_init  ! Initializations of each fine grid 
     362      Call agrif_nemo_init 
    363363 
    364364      ! 1. Declaration of the type of variable which have to be interpolated 
     
    473473 
    474474 
    475    SUBROUTINE agrif_opa_init 
     475   SUBROUTINE agrif_nemo_init 
    476476      !!---------------------------------------------------------------------- 
    477477      !!                     *** ROUTINE agrif_init *** 
     
    484484      NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn 
    485485      !!---------------------------------------------------------------------- 
    486  
     486      ! 
    487487      REWIND( numnam )                ! Read namagrif namelist 
    488488      READ  ( numnam, namagrif ) 
     
    490490      IF(lwp) THEN                    ! control print 
    491491         WRITE(numout,*) 
    492          WRITE(numout,*) 'agrif_opa_init : AGRIF parameters' 
    493          WRITE(numout,*) '~~~~~~~~~~~~' 
     492         WRITE(numout,*) 'agrif_nemo_init : AGRIF parameters' 
     493         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    494494         WRITE(numout,*) '   Namelist namagrif : set AGRIF parameters' 
    495495         WRITE(numout,*) '      baroclinic update frequency       nn_cln_update = ', nn_cln_update 
     
    505505      visc_dyn      = rn_sponge_dyn 
    506506      ! 
    507     END SUBROUTINE agrif_opa_init 
     507    END SUBROUTINE agrif_nemo_init 
    508508 
    509509# if defined key_mpp_mpi 
     
    520520      !!---------------------------------------------------------------------- 
    521521      ! 
    522       SELECT CASE(i) 
    523       CASE(1) 
    524          indglob = indloc + nimppt(nprocloc+1) - 1 
    525       CASE(2) 
    526          indglob = indloc + njmppt(nprocloc+1) - 1  
    527       CASE(3) 
    528          indglob = indloc 
    529       CASE(4) 
    530          indglob = indloc 
     522      SELECT CASE( i ) 
     523      CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1 
     524      CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1  
     525      CASE(3)   ;   indglob = indloc 
     526      CASE(4)   ;   indglob = indloc 
    531527      END SELECT 
    532528      ! 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/nemo.f90

    r2482 r2496  
    1 PROGRAM model 
     1PROGRAM nemo 
     2   !!====================================================================== 
     3   !!                     ***  PROGRAM nemo  *** 
     4   !! 
     5   !! ** Purpose :   encapsulate nemo_gcm so that it can also be called 
     6   !!              together with the linear tangent and adjoint models 
     7   !!====================================================================== 
     8   !! History :   OPA  ! 2001-02  (M. Imbard, A. Weaver)  Original code 
     9   !!   NEMO      1.0  ! 2003-10  (G. Madec) F90 
    210   !!---------------------------------------------------------------------- 
    3    !!                     ***  PROGRAM model  *** 
    4    !! 
    5    !! ** Purpose :   encapsulate the opa model so that opa can also be  
    6    !!      called together with the adjoint and linear tangent models 
    7    !! 
    8    !! History : 
    9    !!   8.0  !  01-02  (M. Imbard, A. Weaver)  Original code 
    10    !!   9.0  !  03-10  (G. Madec) F90 
    11    !!---------------------------------------------------------------------- 
    12    USE opa                  ! OPA system     (opa_model routine) 
     11   USE nemogcm   ! NEMO system   (nemo_gcm routine) 
    1312   !!---------------------------------------------------------------------- 
    1413   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    1514   !! $Id$  
    16    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     15   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    1716   !!---------------------------------------------------------------------- 
    18   
    19    CALL opa_model           ! OPA system 
    20   
    21 END PROGRAM model 
     17   ! 
     18   CALL nemo_gcm           ! NEMO direct code 
     19   !  
     20   !!====================================================================== 
     21END PROGRAM nemo 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r2482 r2496  
    1 MODULE opa 
     1MODULE nemogcm 
    22   !!====================================================================== 
    3    !!                       ***  MODULE opa   *** 
    4    !! Ocean system   : OPA ocean dynamics (including on-line tracers and sea-ice) 
     3   !!                       ***  MODULE nemogcm   *** 
     4   !! Ocean system   : NEMO GCM (ocean dynamics, on-line tracers, biochemistry and sea-ice) 
    55   !!====================================================================== 
    66   !! History :  OPA  ! 1990-10  (C. Levy, G. Madec)  Original code 
     
    3030 
    3131   !!---------------------------------------------------------------------- 
    32    !!   opa_model      : solve ocean dynamics, tracer and/or sea-ice 
    33    !!   opa_init       : initialization of the opa model 
    34    !!   opa_ctl        : initialisation of algorithm flag  
    35    !!   opa_closefile  : close remaining files 
     32   !!   nemo_gcm       : solve ocean dynamics, tracer, biogeochemistry and/or sea-ice 
     33   !!   nemo_init      : initialization of the NEMO system 
     34   !!   nemo_ctl       : initialisation of the contol print  
     35   !!   nemo_closefile : close remaining open files 
    3636   !!---------------------------------------------------------------------- 
    37  
    3837   USE step_oce        ! module used in the ocean time stepping module 
    3938   USE sbc_oce         ! surface boundary condition: ocean 
     
    5554   USE diaptr          ! poleward transports           (dia_ptr_init routine) 
    5655   USE diaobs          ! Observation diagnostics       (dia_obs_init routine) 
    57    USE step            ! OPA time-stepping                  (stp     routine) 
     56   USE step            ! NEMO time-stepping                 (stp     routine) 
    5857#if defined key_oasis3 
    5958   USE cpl_oasis3      ! OASIS3 coupling 
     
    7372   PRIVATE 
    7473 
    75    PUBLIC   opa_model   ! called by model.F90 
    76    PUBLIC   opa_init    ! needed by AGRIF 
     74   PUBLIC   nemo_gcm    ! called by model.F90 
     75   PUBLIC   nemo_init   ! needed by AGRIF 
    7776 
    7877   CHARACTER (len=64) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
     
    8584CONTAINS 
    8685 
    87    SUBROUTINE opa_model 
    88       !!---------------------------------------------------------------------- 
    89       !!                     ***  ROUTINE opa  *** 
    90       !! 
    91       !! ** Purpose :   opa solves the primitive equations on an orthogonal  
     86   SUBROUTINE nemo_gcm 
     87      !!---------------------------------------------------------------------- 
     88      !!                     ***  ROUTINE nemo_gcm  *** 
     89      !! 
     90      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal  
    9291      !!              curvilinear mesh on the sphere. 
    9392      !! 
     
    107106 
    108107      !                            !-----------------------! 
    109       CALL opa_init                !==  Initialisations  ==! 
     108      CALL nemo_init               !==  Initialisations  ==! 
    110109      !                            !-----------------------! 
    111110 
     
    162161      ENDIF 
    163162      ! 
    164       CALL opa_closefile 
     163      CALL nemo_closefile 
    165164#if defined key_oasis3 || defined key_oasis4 
    166165      CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
     
    169168#endif 
    170169      ! 
    171    END SUBROUTINE opa_model 
    172  
    173  
    174    SUBROUTINE opa_init 
    175       !!---------------------------------------------------------------------- 
    176       !!                     ***  ROUTINE opa_init  *** 
    177       !! 
    178       !! ** Purpose :   initialization of the opa model 
    179       !! 
    180       !!---------------------------------------------------------------------- 
    181       INTEGER ::   ji            ! dummy loop indices 
     170   END SUBROUTINE nemo_gcm 
     171 
     172 
     173   SUBROUTINE nemo_init 
     174      !!---------------------------------------------------------------------- 
     175      !!                     ***  ROUTINE nemo_init  *** 
     176      !! 
     177      !! ** Purpose :   initialization of the NEMO GCM 
     178      !!---------------------------------------------------------------------- 
     179      INTEGER ::   ji          ! dummy loop indices 
    182180      INTEGER :: ilocal_comm   ! local integer 
    183       CHARACTER(len=80), DIMENSION(10) ::   cltxt = '' 
     181      CHARACTER(len=80), DIMENSION(10) ::   cltxt 
    184182      !! 
    185183      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
    186184         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle, nn_bench 
    187185      !!---------------------------------------------------------------------- 
     186      ! 
     187      cltxt = '' 
    188188      ! 
    189189      !                             ! open Namelist file 
     
    235235         ! 
    236236      ENDIF 
    237       !                             !--------------------------------! 
    238       !                             !  Model general initialization  ! 
    239       !                             !--------------------------------! 
    240  
    241       CALL opa_ctl                           ! Control prints & Benchmark 
     237      !                             !-------------------------------! 
     238      !                             !  NEMO general initialization  ! 
     239      !                             !-------------------------------! 
     240 
     241      CALL nemo_ctl                          ! Control prints & Benchmark 
    242242 
    243243      !                                      ! Domain decomposition 
     
    315315      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
    316316      ! 
    317    END SUBROUTINE opa_init 
    318  
    319  
    320    SUBROUTINE opa_ctl 
    321       !!---------------------------------------------------------------------- 
    322       !!                     ***  ROUTINE opa_ctl  *** 
     317   END SUBROUTINE nemo_init 
     318 
     319 
     320   SUBROUTINE nemo_ctl 
     321      !!---------------------------------------------------------------------- 
     322      !!                     ***  ROUTINE nemo_ctl  *** 
    323323      !! 
    324324      !! ** Purpose :   control print setting  
     
    327327      !!---------------------------------------------------------------------- 
    328328      ! 
    329       IF(lwp) THEN                  ! Parameter print 
     329      IF(lwp) THEN                  ! control print 
    330330         WRITE(numout,*) 
    331          WRITE(numout,*) 'opa_ctl: Control prints & Benchmark' 
     331         WRITE(numout,*) 'nemo_ctl: Control prints & Benchmark' 
    332332         WRITE(numout,*) '~~~~~~~ ' 
    333333         WRITE(numout,*) '   Namelist namctl' 
     
    355355      IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
    356356         IF( lk_mpp ) THEN 
    357             isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real splitted domain 
     357            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
    358358         ELSE 
    359359            IF( isplt == 1 .AND. jsplt == 1  ) THEN 
     
    398398      ENDIF 
    399399      ! 
    400       IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'opa_ctl: The 1D configuration must be used ',   & 
    401          &                                               'with the IOM Input/Output manager. '        ,   & 
     400      IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ',   & 
     401         &                                               'with the IOM Input/Output manager. '         ,   & 
    402402         &                                               'Compile with key_iomput enabled' ) 
    403403      ! 
    404    END SUBROUTINE opa_ctl 
    405  
    406  
    407    SUBROUTINE opa_closefile 
    408       !!---------------------------------------------------------------------- 
    409       !!                     ***  ROUTINE opa_closefile  *** 
     404   END SUBROUTINE nemo_ctl 
     405 
     406 
     407   SUBROUTINE nemo_closefile 
     408      !!---------------------------------------------------------------------- 
     409      !!                     ***  ROUTINE nemo_closefile  *** 
    410410      !! 
    411411      !! ** Purpose :   Close the files 
     
    425425      numout = 6                                     ! redefine numout in case it is used after this point... 
    426426      ! 
    427    END SUBROUTINE opa_closefile 
     427   END SUBROUTINE nemo_closefile 
    428428 
    429429   !!====================================================================== 
    430 END MODULE opa 
     430END MODULE nemogcm 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/step.F90

    r2474 r2496  
    195195 
    196196      IF( ln_dynhpg_imp  ) THEN                             ! semi-implicit hpg (time stepping then eos) 
    197          IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )            ! update after fields by non-penetrative convection 
    198                              CALL tra_nxt    ( kstp )            ! tracer fields at next time step 
    199                              CALL eos( tsa, rhd, rhop )       ! Time-filtered in situ density for hpg computation 
     197         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
     198                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
     199                             CALL eos    ( tsa, rhd, rhop )      ! Time-filtered in situ density for hpg computation 
    200200         IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsa, gtsu, gtsv,  &    ! zps: time filtered hor. derivative 
    201201            &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
    202202          
    203203      ELSE                                                  ! centered hpg  (eos then time stepping) 
    204                              CALL eos( tsn, rhd, rhop )       ! now in situ density for hpg computation 
     204                             CALL eos    ( tsn, rhd, rhop )      ! now in situ density for hpg computation 
    205205         IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &    ! zps: now hor. derivative 
    206206            &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
    207          IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )       ! update after fields by non-penetrative convection 
    208                              CALL tra_nxt    ( kstp )       ! tracer fields at next time step 
     207         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
     208                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
    209209      ENDIF  
    210210                             CALL tra_unswap                ! udate T & S 3D arrays  (to be suppressed) 
Note: See TracChangeset for help on using the changeset viewer.