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 253 for trunk – NEMO

Changeset 253 for trunk


Ignore:
Timestamp:
2005-08-30T15:26:11+02:00 (19 years ago)
Author:
opalod
Message:

nemo_v1_update_001 : Add the 1D configuration possibility

Location:
trunk/NEMO
Files:
7 added
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC/iceini.F90

    r247 r253  
    2020   USE limistate 
    2121   USE limrst 
     22   USE ini1d           ! initialization of the 1D configuration 
    2223 
    2324   IMPLICIT NONE 
     
    119120      REWIND ( numnam_ice ) 
    120121      READ   ( numnam_ice , namicerun ) 
     122 
     123      IF( lk_cfg_1d  )  ln_limdyn = .FALSE.       ! No ice transport in 1D configuration 
     124 
    121125      IF(lwp) THEN 
    122126         WRITE(numout,*) 
  • trunk/NEMO/OPA_SRC/DOM/domzgr.F90

    r250 r253  
    2222   USE closea 
    2323   USE solisl 
     24   USE ini1d           ! initialization of the 1D configuration 
    2425 
    2526   IMPLICIT NONE 
     
    592593      ! ================ 
    593594 
    594       ! Suppress isolated ocean grid points 
    595  
    596       IF(lwp) WRITE(numout,*) 
    597       IF(lwp) WRITE(numout,*)'                   suppress isolated ocean grid points' 
    598       IF(lwp) WRITE(numout,*)'                   -----------------------------------' 
    599  
    600       icompt = 0 
    601  
    602       DO jl = 1, 2 
    603  
    604          IF( nperio == 1 .OR. nperio  ==  4 .OR. nperio  ==  6 ) THEN 
    605             mbathy( 1 ,:) = mbathy(jpim1,:) 
    606             mbathy(jpi,:) = mbathy(  2  ,:) 
    607          ENDIF 
    608          DO jj = 2, jpjm1 
    609             DO ji = 2, jpim1 
    610                ibtest = MAX( mbathy(ji-1,jj), mbathy(ji+1,jj),   & 
    611                   mbathy(ji,jj-1),mbathy(ji,jj+1) ) 
    612                IF( ibtest < mbathy(ji,jj) ) THEN 
    613                   IF(lwp) WRITE(numout,*) ' the number of ocean level at ',   & 
    614                      'grid-point (i,j) =  ',ji,jj,' is changed from ',   & 
    615                      mbathy(ji,jj),' to ', ibtest 
    616                   mbathy(ji,jj) = ibtest 
    617                   icompt = icompt + 1 
    618                ENDIF 
     595      IF( .NOT. lk_cfg_1d )   THEN 
     596 
     597         ! Suppress isolated ocean grid points 
     598 
     599         IF(lwp) WRITE(numout,*) 
     600         IF(lwp) WRITE(numout,*)'                   suppress isolated ocean grid points' 
     601         IF(lwp) WRITE(numout,*)'                   -----------------------------------' 
     602 
     603         icompt = 0 
     604 
     605         DO jl = 1, 2 
     606 
     607            IF( nperio == 1 .OR. nperio  ==  4 .OR. nperio  ==  6 ) THEN 
     608               mbathy( 1 ,:) = mbathy(jpim1,:) 
     609               mbathy(jpi,:) = mbathy(  2  ,:) 
     610            ENDIF 
     611            DO jj = 2, jpjm1 
     612               DO ji = 2, jpim1 
     613                  ibtest = MAX( mbathy(ji-1,jj), mbathy(ji+1,jj),   & 
     614                     mbathy(ji,jj-1),mbathy(ji,jj+1) ) 
     615                  IF( ibtest < mbathy(ji,jj) ) THEN 
     616                     IF(lwp) WRITE(numout,*) ' the number of ocean level at ',   & 
     617                        'grid-point (i,j) =  ',ji,jj,' is changed from ',   & 
     618                        mbathy(ji,jj),' to ', ibtest 
     619                     mbathy(ji,jj) = ibtest 
     620                     icompt = icompt + 1 
     621                  ENDIF 
     622               END DO 
    619623            END DO 
     624 
    620625         END DO 
    621  
    622       END DO 
    623       IF( icompt == 0 ) THEN 
    624          IF(lwp) WRITE(numout,*)'     no isolated ocean grid points' 
    625       ELSE 
    626          IF(lwp) WRITE(numout,*)'    ',icompt,' ocean grid points suppressed' 
    627       ENDIF 
    628       IF( lk_mpp ) THEN 
    629          zbathy(:,:) = FLOAT( mbathy(:,:) ) 
    630          CALL lbc_lnk( zbathy, 'T', 1. ) 
    631          mbathy(:,:) = INT( zbathy(:,:) ) 
    632       ENDIF 
    633  
    634       ! 3.2 East-west cyclic boundary conditions 
    635  
    636       IF( nperio == 0 ) THEN 
    637          IF(lwp) WRITE(numout,*) ' mbathy set to 0 along east and west',   & 
    638             ' boundary: nperio = ', nperio 
     626         IF( icompt == 0 ) THEN 
     627            IF(lwp) WRITE(numout,*)'     no isolated ocean grid points' 
     628         ELSE 
     629            IF(lwp) WRITE(numout,*)'    ',icompt,' ocean grid points suppressed' 
     630         ENDIF 
    639631         IF( lk_mpp ) THEN 
    640             IF( nbondi == -1 .OR. nbondi == 2 ) THEN 
    641                IF( jperio /= 1 )   mbathy(1,:) = 0 
    642             ENDIF 
    643             IF( nbondi == 1 .OR. nbondi == 2 ) THEN 
    644                IF( jperio /= 1 )   mbathy(nlci,:) = 0 
    645             ENDIF 
    646          ELSE 
    647             mbathy( 1 ,:) = 0 
    648             mbathy(jpi,:) = 0 
    649          ENDIF 
    650       ELSEIF( nperio == 1 .OR. nperio == 4 .OR. nperio ==  6 ) THEN 
    651          IF(lwp) WRITE(numout,*)' east-west cyclic boundary conditions',   & 
    652             ' on mbathy: nperio = ', nperio 
    653          mbathy( 1 ,:) = mbathy(jpim1,:) 
    654          mbathy(jpi,:) = mbathy(  2  ,:) 
    655       ELSEIF( nperio == 2 ) THEN 
    656          IF(lwp) WRITE(numout,*) '   equatorial boundary conditions',   & 
    657             ' on mbathy: nperio = ', nperio 
    658       ELSE 
    659          IF(lwp) WRITE(numout,*) '    e r r o r' 
    660          IF(lwp) WRITE(numout,*) '    parameter , nperio = ', nperio 
    661          !         STOP 'dom_mba' 
    662       ENDIF 
    663  
    664       ! Set to zero mbathy over islands if necessary  (lk_isl=F) 
    665       IF( .NOT. lk_isl ) THEN    ! No island 
    666          IF(lwp) WRITE(numout,*) 
    667          IF(lwp) WRITE(numout,*) '         mbathy set to 0 over islands' 
    668          IF(lwp) WRITE(numout,*) '         ----------------------------' 
    669  
    670          mbathy(:,:) = MAX( 0, mbathy(:,:) ) 
    671  
    672          !  Boundary condition on mbathy 
    673          IF( .NOT.lk_mpp ) THEN  
    674             !!bug ???  y reflechir! 
    675             !   ... mono- or macro-tasking: T-point, >0, 2D array, no slab 
    676632            zbathy(:,:) = FLOAT( mbathy(:,:) ) 
    677633            CALL lbc_lnk( zbathy, 'T', 1. ) 
    678634            mbathy(:,:) = INT( zbathy(:,:) ) 
     635         ENDIF 
     636 
     637         ! 3.2 East-west cyclic boundary conditions 
     638 
     639         IF( nperio == 0 ) THEN 
     640            IF(lwp) WRITE(numout,*) ' mbathy set to 0 along east and west',   & 
     641               ' boundary: nperio = ', nperio 
     642            IF( lk_mpp ) THEN 
     643               IF( nbondi == -1 .OR. nbondi == 2 ) THEN 
     644                  IF( jperio /= 1 )   mbathy(1,:) = 0 
     645               ENDIF 
     646               IF( nbondi == 1 .OR. nbondi == 2 ) THEN 
     647                  IF( jperio /= 1 )   mbathy(nlci,:) = 0 
     648               ENDIF 
     649            ELSE 
     650               mbathy( 1 ,:) = 0 
     651               mbathy(jpi,:) = 0 
     652            ENDIF 
     653         ELSEIF( nperio == 1 .OR. nperio == 4 .OR. nperio ==  6 ) THEN 
     654            IF(lwp) WRITE(numout,*)' east-west cyclic boundary conditions',   & 
     655               ' on mbathy: nperio = ', nperio 
     656            mbathy( 1 ,:) = mbathy(jpim1,:) 
     657            mbathy(jpi,:) = mbathy(  2  ,:) 
     658         ELSEIF( nperio == 2 ) THEN 
     659            IF(lwp) WRITE(numout,*) '   equatorial boundary conditions',   & 
     660               ' on mbathy: nperio = ', nperio 
     661         ELSE 
     662            IF(lwp) WRITE(numout,*) '    e r r o r' 
     663            IF(lwp) WRITE(numout,*) '    parameter , nperio = ', nperio 
     664            !         STOP 'dom_mba' 
     665         ENDIF 
     666 
     667         ! Set to zero mbathy over islands if necessary  (lk_isl=F) 
     668         IF( .NOT. lk_isl ) THEN    ! No island 
     669            IF(lwp) WRITE(numout,*) 
     670            IF(lwp) WRITE(numout,*) '         mbathy set to 0 over islands' 
     671            IF(lwp) WRITE(numout,*) '         ----------------------------' 
     672 
     673            mbathy(:,:) = MAX( 0, mbathy(:,:) ) 
     674 
     675            !  Boundary condition on mbathy 
     676            IF( .NOT.lk_mpp ) THEN  
     677               !!bug ???  y reflechir! 
     678               !   ... mono- or macro-tasking: T-point, >0, 2D array, no slab 
     679               zbathy(:,:) = FLOAT( mbathy(:,:) ) 
     680               CALL lbc_lnk( zbathy, 'T', 1. ) 
     681               mbathy(:,:) = INT( zbathy(:,:) ) 
     682            ENDIF 
     683 
    679684         ENDIF 
    680685 
  • trunk/NEMO/OPA_SRC/DOM/domzgr_s.h90

    r247 r253  
    196196      END DO 
    197197 
     198      ! =========== 
     199      ! Zoom domain  
     200      ! =========== 
     201 
     202      IF( lzoom )   CALL zgr_bat_zoom 
     203 
    198204      ! 2.4 Control print 
    199205 
  • trunk/NEMO/OPA_SRC/DOM/domzgr_zps.h90

    r247 r253  
    418418   ENDIF 
    419419 
     420      ! =========== 
     421      ! Zoom domain  
     422      ! =========== 
     423 
     424      IF( lzoom )   CALL zgr_bat_zoom 
     425 
    420426      ! ================ 
    421427      ! Bathymetry check 
  • trunk/NEMO/OPA_SRC/ZDF/zdftke.F90

    r247 r253  
    6060      evmean        ! 
    6161# endif 
     62 
     63# if defined key_cfg_1d 
     64   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &    
     65      e_dis,    &   ! dissipation turbulent lengh scale 
     66      e_mix,    &   ! mixing turbulent lengh scale 
     67      e_pdl,    &   ! prandl number 
     68      e_ric         ! local Richardson number 
     69#endif 
    6270 
    6371   !! * Substitutions 
     
    153161      !!   8.1  !  99-01  (E. Stretta) new option for the mixing length 
    154162      !!   8.5  !  02-08  (G. Madec)  ri_c and Free form, F90 
     163      !!   9.0  !  04-10  (C. Ethe )  1D configuration 
    155164      !!---------------------------------------------------------------------- 
    156165      !! * Modules used 
     
    287296 
    288297      END SELECT 
     298 
     299# if defined key_cfg_1d 
     300      ! save mixing and dissipation turbulent length scales 
     301      e_dis(:,:,:) = zmxld(:,:,:) 
     302      e_mix(:,:,:) = zmxlm(:,:,:) 
     303# endif 
    289304 
    290305 
     
    382397                  ! local Richardson number 
    383398                  zri  = MAX( rn2(ji,jj,jk), 0. ) / ( zsh2 + 1.e-20 ) 
     399# if defined key_cfg_1d 
     400                  ! save masked local Richardson number in zmxlm array 
     401                  e_ric(ji,jj,jk) = zri * tmask(ji,jj,jk) 
     402# endif 
    384403                  ! Prandtl number 
    385404                  zpdl = 1.0 
     
    409428 
    410429      END SELECT 
     430 
     431# if defined key_cfg_1d 
     432      !  save masked Prandlt number 
     433      e_pdl(:,:,2:jpkm1) = zmxld(:,:,2:jpkm1) 
     434      e_pdl(:,:,      1) = e_pdl(:,:,      2) 
     435      e_pdl(:,:,    jpk) = e_pdl(:,:,  jpkm1)       
     436# endif 
    411437 
    412438      ! 4. Matrix inversion from level 2 (tke prescribed at level 1) 
  • trunk/NEMO/OPA_SRC/opa.F90

    r247 r253  
    3333   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine) 
    3434   USE zdfini 
    35 !!!USE zdf_oce         ! ocean vertical physics            (zdf_init routine) 
    3635 
    3736   USE phycst          ! physical constant                  (par_cst routine) 
     
    4746 
    4847   USE step            ! OPA time-stepping                  (stp     routine) 
     48   USE ini1d           ! re-initialization of u-v mask for the 1D configuration 
     49   USE dyncor1d        ! Coriolis factor at T-point 
     50   USE step1d          ! Time stepping loop for the 1D configuration 
    4951 
    5052   IMPLICIT NONE 
     
    9395      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules 
    9496      !!    "   !  04-08  (C. Talandier) New trends organization 
     97      !!    "   !  05-06  (C. Ethe) Add the 1D configuration possibility 
    9598      !!---------------------------------------------------------------------- 
    9699      !! * Local declarations 
     
    166169      CALL dom_init                         ! Domain 
    167170 
    168       IF( lk_obc    )   CALL obc_init        ! Open boundaries  
     171      IF( lk_cfg_1d )   CALL fcorio_1d      ! redefine Coriolis at T-point 
     172 
     173      IF( lk_obc    )   CALL obc_init       ! Open boundaries  
    169174 
    170175      CALL solver_init                      ! Elliptic solver 
     
    178183                       CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency 
    179184 
    180       IF( lk_zps    )   CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
    181                                           gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
    182                                           gtv, gsv, grv ) 
     185      IF( lk_zps .AND. .NOT. lk_cfg_1d )   & 
     186         &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
     187                                            gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
     188                                            gtv, gsv, grv ) 
    183189 
    184190!!add 
     
    236242      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA 
    237243 
    238       istp = nit000 
    239       DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    240          CALL stp( istp ) 
    241          istp = istp + 1 
    242       END DO 
     244      IF( lk_cfg_1d  )  THEN  
     245         CALL init_1d 
     246         istp = nit000 
     247         DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
     248            CALL stp_1d( istp ) 
     249            istp = istp + 1 
     250         END DO 
     251      ELSE 
     252         istp = nit000 
     253         DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
     254            CALL stp( istp ) 
     255            istp = istp + 1 
     256         END DO 
     257      ENDIF 
    243258      !                                     ! ========= ! 
    244259      !                                     !  Job end  ! 
  • trunk/NEMO/OPA_SRC/par_ORCA_R2.h90

    r247 r253  
    4545      jpnisl  = 400             !: maximum number of points per island 
    4646 
     47#elif defined key_cfg_1d 
     48      ! global domain size     !!! *  global domain  * 
     49      jpiglo  = 3     ,      &  !: 1st dimension of global domain --> i 
     50      jpjglo  = 3     ,      &  !: 2nd    "                  "    --> j 
     51      jpk     = jpkdta,      &  !: number of vertical levels 
     52      ! starting position of the zoom  
     53      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     54      ! jpjzoom =   133  ,    &  !: in data domain indices (160W,75N) 
     55      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     56      ! jpjzoom =   110  ,    &  !: in data domain indices (160W,50N) 
     57      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     58      ! jpjzoom =   97   ,    &  !: in data domain indices (160W,30N) 
     59      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     60      ! jpjzoom =   86   ,    &  !: in data domain indices (160W,10N) 
     61      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     62      ! jpjzoom =   49   ,    &  !: in data domain indices (160W,30S) 
     63      ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     64      ! jpjzoom =   27   ,    &  !: in data domain indices (160W,60S) 
     65      jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
     66      jpjzoom =    7   ,    &  !: in data domain indices (160W,75S) 
     67      ! Domain characteristics 
     68      jperio  =   0   ,      &  !: lateral cond. type (between 0 and 6) 
     69      jpisl   =  18   ,      &  !: number of islands 
     70      jpnisl  = 800             !: maximum number of points per island 
    4771#else 
    4872      ! global domain size     !!! *  global domain  * 
     
    5781      jpisl   =  18   ,      &  !: number of islands 
    5882      jpnisl  = 800             !: maximum number of points per island 
    59  
    6083#endif 
    6184 
Note: See TracChangeset for help on using the changeset viewer.