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

Changeset 2435


Ignore:
Timestamp:
2010-11-25T17:33:31+01:00 (13 years ago)
Author:
cetlod
Message:

Improve the 1D vertical configuration in v3.3beta

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC/dtadyn.F90

    r2287 r2435  
    2626   USE zpshde 
    2727   USE lib_mpp         ! distributed memory computing library 
     28   USE c1d 
    2829 
    2930   IMPLICIT NONE 
     
    183184         ENDIF 
    184185          
    185          IF( lk_ldfslp ) THEN 
     186         IF( lk_ldfslp .AND. .NOT. lk_c1d ) THEN 
    186187            ! Computes slopes. Caution : here tsn and avt are used as workspace 
    187188            tsn (:,:,:,jp_tem) = tdta  (:,:,:,2) 
     
    210211         CALL dynrea( kt, iper )    ! data read for the iper period 
    211212          
    212          IF( lk_ldfslp ) THEN 
     213         IF( lk_ldfslp .AND. .NOT. lk_c1d ) THEN 
    213214            ! Computes slopes. Caution : here tsn and avt are used as workspace 
    214215            tsn (:,:,:,jp_tem) = tdta  (:,:,:,2) 
     
    256257         CALL dynrea( kt, iper )    ! data read for the iper period 
    257258 
    258          IF( lk_ldfslp ) THEN 
     259         IF( lk_ldfslp .AND. .NOT. lk_c1d ) THEN 
    259260            ! Computes slopes. Caution : here tsn and avt are used as workspace 
    260261            tsn (:,:,:,jp_tem) = tdta  (:,:,:,2) 
     
    313314 
    314315      ! Compute bbl coefficients if needed 
    315       IF( lk_trabbl ) THEN 
     316      IF( lk_trabbl .AND. .NOT. lk_c1d ) THEN 
    316317         tsb(:,:,:,:) = tsn(:,:,:,:) 
    317318         CALL bbl( kt, 'TRC') 
     
    682683      wdta   (:,:,:,1) = wdta   (:,:,:,2) 
    683684 
    684 #if defined key_ldfslp 
     685#if defined key_ldfslp && ! defined key_c1d 
    685686      uslpdta (:,:,:,1) = uslpdta (:,:,:,2) 
    686687      vslpdta (:,:,:,1) = vslpdta (:,:,:,2) 
     
    733734 
    734735       
    735 #if defined key_ldfslp 
     736#if defined key_ldfslp && ! defined key_c1d 
    736737      uslp (:,:,:) = uslpdta (:,:,:,2)  
    737738      vslp (:,:,:) = vslpdta (:,:,:,2)  
     
    794795 
    795796       
    796 #if defined key_ldfslp 
     797#if defined key_ldfslp && ! defined key_c1d 
    797798      uslp (:,:,:) = zweighm1 * uslpdta (:,:,:,1) + pweigh * uslpdta (:,:,:,2)  
    798799      vslp (:,:,:) = zweighm1 * vslpdta (:,:,:,1) + pweigh * vslpdta (:,:,:,2)  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r2392 r2435  
    3030   USE iom              ! Library to read input files 
    3131   USE asmpar           ! Parameters for the assmilation interface 
    32 #if defined key_c1d 
    33    USE c1d, ONLY :   lk_c1d    ! 1D initialization 
    34 #endif 
     32   USE c1d              ! 1D initialization 
    3533 
    3634   IMPLICIT NONE 
     
    674672            CALL eos( tsb, rhd, rhop )                ! Before potential and in situ densities 
    675673          
    676 #if ! defined key_c1d 
    677             IF( ln_zps ) & 
     674            IF( ln_zps .AND. .NOT. lk_c1d ) & 
    678675               &  CALL zps_hde( nit000, jpts, tsb,   &  ! Partial steps: before horizontal derivative 
    679676               &                gtsu, gtsv, rhd,        &  ! of T, S, rd at the bottom ocean level 
    680677               &                gru , grv ) 
    681 #endif 
    682678 
    683679            DEALLOCATE( t_bkginc ) 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r2392 r2435  
    3333   USE domwri          ! domain: write the meshmask file 
    3434   USE domvvl          ! variable volume 
    35 #if defined key_c1d 
     35   USE c1d             ! 1D vertical configuration 
    3636   USE dyncor_c1d      ! Coriolis term (c1d case)         (cor_c1d routine) 
    37 #endif 
    3837 
    3938   IMPLICIT NONE 
     
    6564      !!              - dom_stp: defined the model time step 
    6665      !!              - dom_wri: create the meshmask file if nmsh=1 
    67       !!              - "key_c1d": 1D configuration, move Coriolis, u and v at T-point 
     66      !!              - 1D configuration, move Coriolis, u and v at T-point 
    6867      !!---------------------------------------------------------------------- 
    6968      INTEGER ::   jk                ! dummy loop argument 
     
    8483      IF( lk_vvl         )   CALL dom_vvl      ! Vertical variable mesh 
    8584      ! 
    86 #if defined key_c1d 
    87       !                                        ! 1D configuration ("key_c1d") 
    88       CALL cor_c1d                                 ! Coriolis set at T-point 
    89       umask(:,:,:) = tmask(:,:,:)                  ! U, V moved at T-point 
    90       vmask(:,:,:) = tmask(:,:,:) 
    91 #endif 
     85      IF( lk_c1d ) THEN                        ! 1D configuration  
     86         CALL cor_c1d                          ! Coriolis set at T-point 
     87         umask(:,:,:) = tmask(:,:,:)           ! U, V moved at T-point 
     88         vmask(:,:,:) = tmask(:,:,:) 
     89      END IF 
    9290      ! 
    9391      hu(:,:) = 0.e0                           ! Ocean depth at U- and V-points 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r2392 r2435  
    3434   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3535   USE closea          ! closed seas 
     36   USE c1d 
    3637 
    3738   IMPLICIT NONE 
     
    509510      !                                               ! =============== ! 
    510511 
    511 #if ! defined key_c1d 
    512       !                          ! =================== ! 
    513       CALL zgr_bat_ctl           !   Bathymetry check  ! 
    514       !                          ! =================== ! 
    515 #endif 
     512      !                                               ! =================== ! 
     513      IF( .NOT. lk_c1d )    CALL zgr_bat_ctl          !   Bathymetry check  ! 
     514      !                                               ! =================== ! 
    516515   END SUBROUTINE zgr_bat 
    517516 
     
    10071006      !                                               ! =============== ! 
    10081007 
    1009 #if ! defined key_c1d 
    1010       !                          ! =================== ! 
    1011       CALL zgr_bat_ctl           !   Bathymetry check  ! 
    1012       !                          ! =================== ! 
    1013 #endif 
     1008 
     1009      !                                               ! =================== ! 
     1010      IF( .NOT. lk_c1d )    CALL zgr_bat_ctl          !   Bathymetry check  ! 
     1011      !                                               ! =================== ! 
    10141012   END SUBROUTINE zgr_zps 
    10151013 
     
    15011499      !                                               ! =========== 
    15021500 
    1503 #if ! defined key_c1d 
    1504       !                          ! =================== ! 
    1505       CALL zgr_bat_ctl           !   Bathymetry check  ! 
    1506       !                          ! =================== ! 
    1507 #endif 
     1501 
     1502      !                                               ! =================== ! 
     1503      IF( .NOT. lk_c1d )    CALL zgr_bat_ctl          !   Bathymetry check  ! 
     1504      !                                               ! =================== ! 
    15081505 
    15091506      !                                               ! ============= 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/LDF/ldfslp.F90

    r2401 r2435  
    200200      !                                            !* horizontal Shapiro filter 
    201201      DO jk = 2, jpkm1 
    202          DO jj = 2, jpjm1, jpj-3                        ! rows jj=2 and =jpjm1 only 
     202         DO jj = 2, jpjm1, MAX(1, jpj-3)                        ! rows jj=2 and =jpjm1 only 
    203203            DO ji = 2, jpim1   
    204204               uslp(ji,jj,jk) = z1_16 * (        zwz(ji-1,jj-1,jk) + zwz(ji+1,jj-1,jk)      & 
     
    282282      !                                           !* horizontal Shapiro filter 
    283283      DO jk = 2, jpkm1 
    284          DO jj = 2, jpjm1, jpj-3                        ! rows jj=2 and =jpjm1 
     284         DO jj = 2, jpjm1, MAX(1, jpj-3)                        ! rows jj=2 and =jpjm1 only 
    285285            DO ji = 2, jpim1 
    286286               wslpi(ji,jj,jk) = (        zwz(ji-1,jj-1,jk) + zwz(ji+1,jj-1,jk)     & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r2370 r2435  
    4747   USE limvar          ! Ice variables switch 
    4848 
     49   USE c1d             ! 1D vertical configuration 
    4950   USE lbclnk          ! lateral boundary condition - MPP link 
    5051   USE iom             ! I/O manager library 
     
    192193         IF( ln_nicep )   CALL lim_prt_state( jiindx, jjindx, 1, ' - Beginning the time step - ' )   ! control print 
    193194         ! 
    194 #if ! defined key_c1d 
     195         IF( .NOT. lk_c1d ) THEN 
    195196                                                     ! Ice dynamics & transport (not in 1D case) 
    196197                          CALL lim_dyn( kt )              ! Ice dynamics    ( rheology/dynamics ) 
     
    200201         IF( ln_nicep )   CALL lim_prt_state( jiindx, jjindx,-1, ' - ice dyn & trp - ' )   ! control print 
    201202                          CALL lim_itd_me                 ! Mechanical redistribution ! (ridging/rafting) 
    202 #endif 
     203         ENDIF 
    203204         !                                           ! Ice thermodynamics  
    204205                          CALL lim_var_glo2eqv            ! equivalent variables 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r2370 r2435  
    3939   USE limwri_2 
    4040   USE limrst_2 
     41 
     42   USE c1d              ! 1D vertical configuration 
    4143 
    4244   USE lbclnk           ! lateral boundary condition - MPP link 
     
    179181 
    180182                           CALL lim_rst_opn_2  ( kt )  ! Open Ice restart file 
    181 #if ! defined key_c1d 
    182                                                        ! Ice dynamics & transport (except in 1D case) 
     183         IF( .NOT. lk_c1d ) THEN                       ! Ice dynamics & transport (except in 1D case) 
    183184                           CALL lim_dyn_2      ( kt )      ! Ice dynamics    ( rheology/dynamics ) 
    184185                           CALL lim_trp_2      ( kt )      ! Ice transport   ( Advection/diffusion ) 
    185          IF( ln_limdmp )  CALL lim_dmp_2      ( kt )      ! Ice damping  
    186 #endif 
     186           IF( ln_limdmp ) CALL lim_dmp_2      ( kt )      ! Ice damping  
     187         END IF 
    187188#if defined key_coupled 
    188189         !                                             ! Ice surface fluxes in coupled mode  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/opa.F90

    r2432 r2435  
    6161   USE cpl_oasis4      ! OASIS4 coupling (not working) 
    6262#endif 
    63 #if defined key_c1d 
    6463   USE c1d             ! 1D configuration 
    6564   USE step_c1d        ! Time stepping loop for the 1D configuration 
    66 #endif 
    6765#if defined key_top 
    6866   USE trcini          ! passive tracer initialisation 
     
    408406      ENDIF 
    409407      ! 
    410 #if defined key_c1d 
    411408      IF( lk_c1d .AND. .NOT. lk_iomput )  & 
    412409        CALL ctl_stop( ' The 1D vertical configuration must be used in conjunction',   & 
    413410            &          ' with the IOM Input/Output manager. Compile with key_iomput enabled' ) 
    414 #endif 
    415411      ! 
    416412   END SUBROUTINE opa_ctl 
Note: See TracChangeset for help on using the changeset viewer.