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 2066 for branches – NEMO

Changeset 2066 for branches


Ignore:
Timestamp:
2010-08-27T14:04:19+02:00 (14 years ago)
Author:
rblod
Message:

Suppress dummy module on FCM branch since there is no more need of it for dependancy search

Location:
branches/DEV_r1879_FCM/NEMOGCM
Files:
4 deleted
11 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r1694 r2066  
    3434   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3535   USE closea          ! closed seas 
    36    USE c1d             ! 1D configuration 
    3736 
    3837   IMPLICIT NONE 
     
    482481      !                                               ! =============== ! 
    483482 
    484       !                                               ! =================== ! 
    485       IF( .NOT. lk_c1d )   CALL zgr_bat_ctl           !   Bathymetry check  ! 
    486       !                                               ! =================== ! 
     483#if ! defined key_c1d 
     484      !                          ! =================== ! 
     485      CALL zgr_bat_ctl           !   Bathymetry check  ! 
     486      !                          ! =================== ! 
     487#endif 
    487488   END SUBROUTINE zgr_bat 
    488489 
     
    984985      !                                               ! =============== ! 
    985986 
    986       !                                               ! =================== ! 
    987       IF( .NOT. lk_c1d )   CALL zgr_bat_ctl           !   Bathymetry check  ! 
    988       !                                               ! =================== ! 
     987#if ! defined key_c1d 
     988      !                          ! =================== ! 
     989      CALL zgr_bat_ctl           !   Bathymetry check  ! 
     990      !                          ! =================== ! 
     991#endif 
    989992   END SUBROUTINE zgr_zps 
    990993 
     
    14761479      !                                               ! =========== 
    14771480 
    1478       !                                               ! =================== ! 
    1479       IF( .NOT. lk_c1d )   CALL zgr_bat_ctl           !   Bathymetry check  ! 
    1480       !                                               ! =================== ! 
     1481#if ! defined key_c1d 
     1482      !                          ! =================== ! 
     1483      CALL zgr_bat_ctl           !   Bathymetry check  ! 
     1484      !                          ! =================== ! 
     1485#endif 
    14811486 
    14821487      !                                               ! ============= 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/DYN/dynnxt.F90

    r2007 r2066  
    3232   USE bdydta          ! unstructured open boundary conditions 
    3333   USE bdydyn          ! unstructured open boundary conditions 
    34    USE agrif_opa_update 
    35    USE agrif_opa_interp 
    3634   USE in_out_manager  ! I/O manager 
    3735   USE lbclnk          ! lateral boundary condition (or mpp link) 
    3836   USE prtctl          ! Print control 
     37#if defined key_agrif 
     38   USE agrif_opa_update 
     39   USE agrif_opa_interp 
     40#endif 
    3941 
    4042   IMPLICIT NONE 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_flt.F90

    r2013 r2066  
    4444   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    4545   USE prtctl          ! Print control 
    46    USE agrif_opa_interp 
    4746   USE iom 
    4847   USE restart         ! only for lrst_oce 
     48#if defined key_agrif 
     49   USE agrif_opa_interp 
     50#endif 
    4951 
    5052   IMPLICIT NONE 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r1613 r2066  
    2020   USE in_out_manager  ! I/O manager 
    2121   USE iom             ! I/O module 
    22    USE c1d             ! re-initialization of u-v mask for the 1D configuration 
    2322   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
    2423   USE eosbn2          ! equation of state            (eos bn2 routine) 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r1715 r2066  
    1919   !!---------------------------------------------------------------------- 
    2020   USE oce             ! ocean dynamics and tracers 
    21    USE c1d             ! 1d configuration 
    2221   USE dom_oce         ! ocean space and time domain 
    2322   USE lib_mpp 
     
    196195         IF( ln_nicep )   CALL lim_prt_state( jiindx, jjindx, 1, ' - Beginning the time step - ' )   ! control print 
    197196         ! 
    198          IF( .NOT. lk_c1d ) THEN                     ! Ice dynamics & transport (not in 1D case) 
     197#if ! defined key_c1d 
     198         ! Ice dynamics & transport (not in 1D case) 
    199199                          CALL lim_dyn( kt )              ! Ice dynamics    ( rheology/dynamics ) 
    200200                          CALL lim_trp( kt )              ! Ice transport   ( Advection/diffusion ) 
     
    203203         IF( ln_nicep )   CALL lim_prt_state( jiindx, jjindx,-1, ' - ice dyn & trp - ' )   ! control print 
    204204                          CALL lim_itd_me                 ! Mechanical redistribution ! (ridging/rafting) 
    205          ENDIF 
     205#endif 
    206206         ! 
    207207         !                                           ! Ice thermodynamics  
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r1715 r2066  
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce             ! ocean dynamics and tracers 
    19    USE c1d             ! 1d configuration 
    2019   USE dom_oce         ! ocean space and time domain 
    2120   USE lib_mpp 
     
    174173 
    175174                                        CALL lim_rst_opn_2  ( kt )      ! Open Ice restart file 
    176          IF( .NOT. lk_c1d ) THEN                                        ! Ice dynamics & transport (not in 1D case) 
     175#if ! defined key_c1d 
     176            ! Ice dynamics & transport (not in 1D case) 
    177177                                        CALL lim_dyn_2      ( kt )           ! Ice dynamics    ( rheology/dynamics ) 
    178178                                        CALL lim_trp_2      ( kt )           ! Ice transport   ( Advection/diffusion ) 
    179179            IF( ln_limdmp )             CALL lim_dmp_2      ( kt )           ! Ice damping  
    180          ENDIF 
     180#endif 
    181181#if defined key_coupled 
    182182         IF( ksbc == 5    )             CALL sbc_cpl_ice_flx( frld   ,                               & 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r2007 r2066  
    3636   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3737   USE prtctl          ! Print control 
     38   USE obc_oce  
     39#if defined key_agrif 
    3840   USE agrif_opa_update 
    3941   USE agrif_opa_interp 
    40    USE obc_oce  
     42#endif 
    4143 
    4244   IMPLICIT NONE 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/istate.F90

    r1566 r2066  
    3434   USE in_out_manager  ! I/O manager 
    3535   USE iom 
    36    USE c1d             ! re-initialization of u-v mask for the 1D configuration 
    3736   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
    3837   USE eosbn2          ! equation of state            (eos bn2 routine) 
     
    124123         CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities 
    125124          
    126          IF( ln_zps .AND. .NOT. lk_c1d )   & 
     125#if ! defined key_c1d 
     126         IF( ln_zps )   & 
    127127            &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
    128128            &                                  gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
    129129            &                                  gtv, gsv, grv ) 
     130#endif 
    130131          
    131132      ENDIF 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/opa.F90

    r2007 r2066  
    6262   USE dynspg_oce      ! Control choice of surface pressure gradient schemes 
    6363   USE prtctl          ! Print control                 (prt_ctl_init routine) 
    64    USE c1d             ! 1D configuration 
     64#if defined key_c1d 
    6565   USE dyncor_c1d      ! Coriolis factor at T-point 
    6666   USE step_c1d        ! Time stepping loop for the 1D configuration 
     67#endif 
    6768#if defined key_top 
    6869   USE trcini          ! passive tracer initialisation 
     
    127128      !                            !-----------------------! 
    128129      istp = nit000 
    129       IF( lk_c1d ) THEN                 !==  1D configuration  ==! 
    130          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    131             CALL stp_c1d( istp ) 
    132             istp = istp + 1 
    133          END DO 
    134       ELSE                              !==  3D ocean with  ==! 
    135          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    136 #if defined key_agrif 
    137             CALL Agrif_Step( stp )           ! AGRIF: time stepping 
     130#if defined key_c1d 
     131      !==  1D configuration  ==! 
     132      DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
     133         CALL stp_c1d( istp ) 
     134         istp = istp + 1 
     135      END DO 
    138136#else 
    139             CALL stp( istp )                 ! standard time stepping 
    140 #endif 
    141             istp = istp + 1 
    142             IF( lk_mpp )   CALL mpp_max( nstop ) 
    143          END DO 
    144       ENDIF 
    145         
     137      !==  3D ocean with  ==! 
     138      DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
     139# if defined key_agrif 
     140         CALL Agrif_Step( stp )           ! AGRIF: time stepping 
     141# else 
     142         CALL stp( istp )                 ! standard time stepping 
     143# endif 
     144         istp = istp + 1 
     145         IF( lk_mpp )   CALL mpp_max( nstop ) 
     146      END DO 
     147#endif        
    146148      !                            !------------------------! 
    147149      !                            !==  finalize the run  ==! 
     
    251253      CALL dom_init                         ! Domain 
    252254!!gm c1d case can be moved in dom_init routine 
    253       IF( lk_c1d ) THEN                          ! 1D configuration  
     255#if defined key_c1d 
    254256         CALL cor_c1d                            ! Coriolis defined at T-point 
    255257         umask(:,:,:) = tmask(:,:,:)             ! U, V and T-points are the same 
    256258         vmask(:,:,:) = tmask(:,:,:)             !  
    257       ENDIF 
     259#endif 
    258260!!gm c1d end 
    259261 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r2013 r2066  
    3030   USE trdmld_trc 
    3131   USE trdmld_trc_oce 
     32# if defined key_agrif 
    3233   USE agrif_top_update 
    3334   USE agrif_top_interp 
     35# endif 
    3436 
    3537   IMPLICIT NONE 
  • branches/DEV_r1879_FCM/NEMOGCM/TOOLS/cfg.txt

    r1987 r2066  
    1 GYRE OPA_SRC LIM_SRC_2 C1D_SRC 
     1GYRE OPA_SRC 
    22ORCA2_LIM_PISCES OPA_SRC LIM_SRC_2 NST_SRC C1D_SRC TOP_SRC 
    3 GYRE_LOBSTER OPA_SRC LIM_SRC_2 NST_SRC C1D_SRC TOP_SRC 
     3GYRE_LOBSTER OPA_SRC TOP_SRC 
    44ORCA2_OFF_PISCES OFF_SRC TOP_SRC 
    5 POMME OPA_SRC LIM_SRC_2 NST_SRC C1D_SRC 
     5POMME OPA_SRC NST_SRC 
    66ORCA2_LIM OPA_SRC LIM_SRC_2 NST_SRC C1D_SRC 
Note: See TracChangeset for help on using the changeset viewer.