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 2814 for branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90 – NEMO

Ignore:
Timestamp:
2011-07-27T14:41:28+02:00 (13 years ago)
Author:
davestorkey
Message:
  1. Implement tidal harmonics forcing (UKMO version) in new structure.
  2. Other bug fixes and updates.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r2800 r2814  
    2424   IMPLICIT NONE 
    2525   PRIVATE    
     26  
     27   PUBLIC   fld_map    ! routine called by tides_init 
    2628 
    2729   TYPE, PUBLIC ::   FLD_N      !: Namelist field informations 
     
    629631      !!                using a general mapping (for open boundaries) 
    630632      !!---------------------------------------------------------------------- 
     633#if defined key_obc 
    631634      USE obc_oce, ONLY:  dta_global         ! workspace to read in global data arrays 
     635#endif  
    632636 
    633637      INTEGER                   , INTENT(in ) ::   num     ! stream number 
    634638      CHARACTER(LEN=*)          , INTENT(in ) ::   clvar   ! variable name 
    635       REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   dta     ! output field on model grid 
     639      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   dta   ! output field on model grid (2 dimensional) 
    636640      INTEGER                   , INTENT(in ) ::   nrec    ! record number to read (ie time slice) 
    637641      INTEGER,  DIMENSION(:)    , INTENT(in ) ::   map     ! global-to-local mapping indices 
    638642      !! 
    639       INTEGER                  ::   ipi      ! length of boundary data on local process 
    640       INTEGER                  ::   ipj      ! length of dummy dimension ( = 1 ) 
    641       INTEGER                  ::   ipk      ! number of vertical levels of dta ( 2D: ipk=1 ; 3D: ipk=jpk ) 
    642       INTEGER                  ::   ilendta  ! length of data in file 
    643       INTEGER                  ::   idvar    ! variable ID 
    644       INTEGER                  ::   ib, ik   ! loop counters 
    645       INTEGER                  ::   ierr 
    646       !! 
    647       CHARACTER(len=80)                   :: zfile 
     643      INTEGER                                 ::   ipi      ! length of boundary data on local process 
     644      INTEGER                                 ::   ipj      ! length of dummy dimension ( = 1 ) 
     645      INTEGER                                 ::   ipk      ! number of vertical levels of dta ( 2D: ipk=1 ; 3D: ipk=jpk ) 
     646      INTEGER                                 ::   ilendta  ! length of data in file 
     647      INTEGER                                 ::   idvar    ! variable ID 
     648      INTEGER                                 ::   ib, ik   ! loop counters 
     649      INTEGER                                 ::   ierr 
     650      REAL(wp), POINTER, DIMENSION(:,:,:)     ::   dta_read ! work space for global data 
    648651      !!--------------------------------------------------------------------- 
    649652             
     653#if defined key_obc 
     654      dta_read => dta_global 
     655#endif 
     656 
    650657      ipi = SIZE( dta, 1 ) 
    651658      ipj = 1 
     
    655662      ilendta = iom_file(num)%dimsz(1,idvar) 
    656663      IF(lwp) WRITE(numout,*) 'Dim size for ',TRIM(clvar),' is ', ilendta 
    657  
    658       CALL iom_get ( num, jpdom_unknown, clvar, dta_global(1:ilendta,1:ipj,1:ipk), nrec ) 
     664      IF(lwp) WRITE(numout,*) 'Number of levels for ',TRIM(clvar),' is ', ipk 
     665 
     666      SELECT CASE( ipk ) 
     667      CASE(1)    
     668         CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1    ), nrec ) 
     669      CASE DEFAULT 
     670         CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1:ipk), nrec ) 
     671      END SELECT 
    659672      ! 
    660673      DO ib = 1, ipi 
    661674         DO ik = 1, ipk 
    662             dta(ib,1,ik) =  dta_global(map(ib),1,ik) 
     675            dta(ib,1,ik) =  dta_read(map(ib),1,ik) 
    663676         END DO 
    664677      END DO 
    665678 
    666679   END SUBROUTINE fld_map 
     680 
    667681 
    668682   SUBROUTINE fld_rot( kt, sd ) 
Note: See TracChangeset for help on using the changeset viewer.