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 2797 for branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/OBC/obcdta.F90 – NEMO

Ignore:
Timestamp:
2011-07-11T12:53:56+02:00 (13 years ago)
Author:
davestorkey
Message:

Delete BDY module and first implementation of new OBC module.

  1. Initial restructuring.
  2. Use fldread to read open boundary data.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/OBC/obcdta.F90

    r2722 r2797  
    11MODULE obcdta 
    2    !!============================================================================== 
    3    !!                            ***  MODULE obcdta  *** 
    4    !! Open boundary data : read the data for the open boundaries. 
    5    !!============================================================================== 
    6    !! History :  OPA  ! 1998-05 (J.M. Molines) Original code 
    7    !!            8.5  ! 2002-10 (C. Talandier, A-M. Treguier) Free surface, F90 
    8    !!   NEMO     1.0  ! 2004-06 (F. Durand, A-M. Treguier) Netcdf BC files on input 
    9    !!            3.0  ! 2007-2008 (C. Langlais, P. Mathiot, J.M. Molines) high frequency boundaries data 
    10    !!------------------------------------------------------------------------------ 
     2   !!====================================================================== 
     3   !!                       ***  MODULE obcdta  *** 
     4   !! Open boundary data : read the data for the unstructured open boundaries. 
     5   !!====================================================================== 
     6   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code 
     7   !!             -   !  2007-01  (D. Storkey) Update to use IOM module 
     8   !!             -   !  2007-07  (D. Storkey) add obc_dta_fla 
     9   !!            3.0  !  2008-04  (NEMO team)  add in the reference version 
     10   !!            3.3  !  2010-09  (E.O'Dea) modifications for Shelf configurations  
     11   !!            3.3  !  2010-09  (D.Storkey) add ice boundary conditions 
     12   !!            3.4  ???????????????? 
     13   !!---------------------------------------------------------------------- 
    1114#if defined key_obc 
    12    !!------------------------------------------------------------------------------ 
    13    !!   'key_obc'         :                                Open Boundary Conditions 
    14    !!------------------------------------------------------------------------------ 
    15    !!   obc_dta           : read u, v, t, s data along each open boundary 
    16    !!------------------------------------------------------------------------------ 
    17    USE oce             ! ocean dynamics and tracers  
     15   !!---------------------------------------------------------------------- 
     16   !!   'key_obc'                     Open Boundary Conditions 
     17   !!---------------------------------------------------------------------- 
     18   !!    obc_dta        : read external data along open boundaries from file 
     19   !!    obc_dta_init   : initialise arrays etc for reading of external data 
     20   !!---------------------------------------------------------------------- 
     21   USE oce             ! ocean dynamics and tracers 
    1822   USE dom_oce         ! ocean space and time domain 
    19    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2023   USE phycst          ! physical constants 
    21    USE obc_par         ! ocean open boundary conditions 
    2224   USE obc_oce         ! ocean open boundary conditions 
     25   USE obctides        ! tidal forcing at boundaries 
     26   USE fldread         ! read input fields 
     27   USE iom             ! IOM library 
    2328   USE in_out_manager  ! I/O logical units 
    24    USE lib_mpp         ! distributed memory computing 
    25    USE dynspg_oce      ! ocean: surface pressure gradient 
    26    USE ioipsl          ! now only for  ymds2ju function  
    27    USE iom             !  
     29#if defined key_lim2 
     30   USE ice_2 
     31#endif 
    2832 
    2933   IMPLICIT NONE 
    3034   PRIVATE 
    3135 
    32    PUBLIC   obc_dta         ! routine  called by step.F90 
    33    PUBLIC   obc_dta_bt      ! routine  called by dynspg_ts.F90 
    34    PUBLIC   obc_dta_alloc   ! function called by obcini.F90 
    35  
    36    REAL(wp),  DIMENSION(2)              ::   zjcnes_obc   !  
    37    REAL(wp),  DIMENSION(:), ALLOCATABLE ::   ztcobc 
    38    REAL(wp) :: rdt_obc 
    39    REAL(wp) :: zjcnes 
    40    INTEGER :: imm0, iyy0, idd0, iyy, imm, idd 
    41    INTEGER :: nt_a=2, nt_b=1, itobc, ndate0_cnes, nday_year0 
    42    INTEGER ::  itobce, itobcw, itobcs, itobcn, itobc_b  ! number of time steps in OBC files 
    43  
    44    INTEGER ::   ntobc        ! where we are in the obc file 
    45    INTEGER ::   ntobc_b      ! first record used 
    46    INTEGER ::   ntobc_a      ! second record used 
    47  
    48    CHARACTER (len=40) ::   cl_obc_eTS, cl_obc_eU   ! name of data files 
    49    CHARACTER (len=40) ::   cl_obc_wTS, cl_obc_wU   !   -       - 
    50    CHARACTER (len=40) ::   cl_obc_nTS, cl_obc_nV   !   -       - 
    51    CHARACTER (len=40) ::   cl_obc_sTS, cl_obc_sV   !   -       - 
    52  
    53    ! bt arrays for interpolating time dependent data on the boundaries 
    54    INTEGER ::   nt_m=0, ntobc_m 
    55    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ubtedta, vbtedta, sshedta    ! East 
    56    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ubtwdta, vbtwdta, sshwdta    ! West 
    57    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ubtndta, vbtndta, sshndta    ! North 
    58    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ubtsdta, vbtsdta, sshsdta    ! South 
    59    ! arrays used for interpolating time dependent data on the boundaries 
    60    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: uedta, vedta, tedta, sedta    ! East 
    61    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: uwdta, vwdta, twdta, swdta    ! West 
    62    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: undta, vndta, tndta, sndta    ! North 
    63    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: usdta, vsdta, tsdta, ssdta    ! South 
    64  
    65    ! Masks set to .TRUE. after successful allocation below 
    66    LOGICAL , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ltemsk, luemsk, lvemsk  ! boolean msks 
    67    LOGICAL , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ltwmsk, luwmsk, lvwmsk  ! used for outliers 
    68    LOGICAL , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ltnmsk, lunmsk, lvnmsk  ! checks 
    69    LOGICAL , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ltsmsk, lusmsk, lvsmsk 
    70  
    71    !! * Substitutions 
    72 #  include "obc_vectopt_loop_substitute.h90" 
    73 #  include "domzgr_substitute.h90" 
     36   PUBLIC   obc_dta          ! routine called by step.F90 and dynspg_ts.F90 
     37   PUBLIC   obc_dta_init     ! routine called by nemogcm.F90 
     38 
     39   INTEGER, ALLOCATABLE, DIMENSION(:)   ::   nb_obc_fld        ! Number of fields to update for each boundary set. 
     40   INTEGER                              ::   nb_obc_fld_sum    ! Total number of fields to update for all boundary sets. 
     41 
     42   TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:), TARGET ::   bf        ! structure of input fields (file informations, fields read) 
     43 
     44   TYPE(MAP_POINTER), ALLOCATABLE, DIMENSION(:) :: nbmap_ptr   ! array of pointers to nbmap 
     45 
    7446   !!---------------------------------------------------------------------- 
    7547   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    76    !! $Id$ 
    77    !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     48   !! $Id$  
     49   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    7850   !!---------------------------------------------------------------------- 
    7951CONTAINS 
    8052 
    81    INTEGER FUNCTION obc_dta_alloc() 
    82       !!------------------------------------------------------------------- 
    83       !!                     ***  ROUTINE obc_dta_alloc  *** 
    84       !!------------------------------------------------------------------- 
    85       INTEGER :: ierr(2) 
    86       !!------------------------------------------------------------------- 
    87 # if defined key_dynspg_ts 
    88       ALLOCATE(   &     ! time-splitting : 0:jptobc 
    89          ! bt arrays for interpolating time dependent data on the boundaries 
    90          &      ubtedta  (jpj,0:jptobc) , vbtedta  (jpj,0:jptobc) , sshedta  (jpj,0:jptobc) ,    & 
    91          &      ubtwdta  (jpj,0:jptobc) , vbtwdta  (jpj,0:jptobc) , sshwdta  (jpj,0:jptobc) ,    & 
    92          &      ubtndta  (jpi,0:jptobc) , vbtndta  (jpi,0:jptobc) , sshndta  (jpi,0:jptobc) ,    & 
    93          &      ubtsdta  (jpi,0:jptobc) , vbtsdta  (jpi,0:jptobc) , sshsdta  (jpi,0:jptobc) ,    & 
    94          ! arrays used for interpolating time dependent data on the boundaries 
    95          &      uedta(jpj,jpk,0:jptobc) , vedta(jpj,jpk,0:jptobc)                           ,     & 
    96          &      tedta(jpj,jpk,0:jptobc) , sedta(jpj,jpk,0:jptobc)                           ,     & 
    97          &      uwdta(jpj,jpk,0:jptobc) , vwdta(jpj,jpk,0:jptobc)                           ,     & 
    98          &      twdta(jpj,jpk,0:jptobc) , swdta(jpj,jpk,0:jptobc)                           ,     & 
    99          &      undta(jpi,jpk,0:jptobc) , vndta(jpi,jpk,0:jptobc)                           ,     & 
    100          &      tndta(jpi,jpk,0:jptobc) , sndta(jpi,jpk,0:jptobc)                           ,     & 
    101          &      usdta(jpi,jpk,0:jptobc) , vsdta(jpi,jpk,0:jptobc)                           ,     & 
    102          &      tsdta(jpi,jpk,0:jptobc) , ssdta(jpi,jpk,0:jptobc)                           , STAT=ierr(1) ) 
    103 # else 
    104       ALLOCATE(   &     ! no time splitting : 1:jptobc 
    105          ! bt arrays for interpolating time dependent data on the boundaries 
    106          &      ubtedta  (jpj,jptobc) , vbtedta  (jpj,jptobc) , sshedta  (jpj,jptobc)  ,     & 
    107          &      ubtwdta  (jpj,jptobc) , vbtwdta  (jpj,jptobc) , sshwdta  (jpj,jptobc)  ,     & 
    108          &      ubtndta  (jpi,jptobc) , vbtndta  (jpi,jptobc) , sshndta  (jpi,jptobc)  ,     & 
    109          &      ubtsdta  (jpi,jptobc) , vbtsdta  (jpi,jptobc) , sshsdta  (jpi,jptobc)  ,     & 
    110          ! arrays used for interpolating time dependent data on the boundaries 
    111          &      uedta(jpj,jpk,jptobc) , vedta(jpj,jpk,jptobc)                          ,     & 
    112          &      tedta(jpj,jpk,jptobc) , sedta(jpj,jpk,jptobc)                          ,     & 
    113          &      uwdta(jpj,jpk,jptobc) , vwdta(jpj,jpk,jptobc)                          ,     & 
    114          &      twdta(jpj,jpk,jptobc) , swdta(jpj,jpk,jptobc)                          ,     & 
    115          &      undta(jpi,jpk,jptobc) , vndta(jpi,jpk,jptobc)                          ,     & 
    116          &      tndta(jpi,jpk,jptobc) , sndta(jpi,jpk,jptobc)                          ,     & 
    117          &      usdta(jpi,jpk,jptobc) , vsdta(jpi,jpk,jptobc)                          ,     & 
    118          &      tsdta(jpi,jpk,jptobc) , ssdta(jpi,jpk,jptobc)                          , STAT=ierr(1) ) 
    119 # endif 
    120  
    121       ALLOCATE( ltemsk(jpj,jpk) , luemsk(jpj,jpk) , lvemsk(jpj,jpk) ,     & 
    122          &      ltwmsk(jpj,jpk) , luwmsk(jpj,jpk) , lvwmsk(jpj,jpk) ,     & 
    123          &      ltnmsk(jpj,jpk) , lunmsk(jpj,jpk) , lvnmsk(jpj,jpk) ,     & 
    124          &      ltsmsk(jpj,jpk) , lusmsk(jpj,jpk) , lvsmsk(jpj,jpk) , STAT=ierr(2) ) 
    125  
    126       obc_dta_alloc = MAXVAL( ierr ) 
    127       IF( lk_mpp )   CALL mpp_sum( obc_dta_alloc ) 
    128  
    129       IF( obc_dta_alloc == 0 )  THEN         ! Initialise mask values following successful allocation 
    130          !      east            !          west            !          north           !          south           ! 
    131          ltemsk(:,:) = .TRUE.   ;   ltwmsk(:,:) = .TRUE.   ;   ltnmsk(:,:) = .TRUE.   ;   ltsmsk(:,:) = .TRUE. 
    132          luemsk(:,:) = .TRUE.   ;   luwmsk(:,:) = .TRUE.   ;   lunmsk(:,:) = .TRUE.   ;   lusmsk(:,:) = .TRUE. 
    133          lvemsk(:,:) = .TRUE.   ;   lvwmsk(:,:) = .TRUE.   ;   lvnmsk(:,:) = .TRUE.   ;   lvsmsk(:,:) = .TRUE. 
    134       END IF 
    135       ! 
    136    END FUNCTION obc_dta_alloc 
    137  
    138  
    139    SUBROUTINE obc_dta( kt ) 
    140       !!--------------------------------------------------------------------------- 
    141       !!                      ***  SUBROUTINE obc_dta  *** 
     53      SUBROUTINE obc_dta( kt, jit ) 
     54      !!---------------------------------------------------------------------- 
     55      !!                   ***  SUBROUTINE obc_dta  *** 
    14256      !!                     
    143       !! ** Purpose :   Find the climatological  boundary arrays for the specified date,  
    144       !!                The boundary arrays are netcdf files. Three possible cases:  
    145       !!                - one time frame only in the file (time dimension = 1). 
    146       !!                in that case the boundary data does not change in time. 
    147       !!                - many time frames. In that case,  if we have 12 frames 
    148       !!                we assume monthly fields.  
    149       !!                Else, we assume that time_counter is in seconds  
    150       !!                since the beginning of either the current year or a reference 
    151       !!                year given in the namelist. 
    152       !!                (no check is done so far but one would have to check the "unit" 
    153       !!                 attribute of variable time_counter). 
     57      !! ** Purpose :   Update external data for open boundary conditions 
     58      !! 
     59      !! ** Method  :   Use fldread.F90 
     60      !!                 
     61      !!---------------------------------------------------------------------- 
     62      INTEGER, INTENT( in )           ::   kt    ! ocean time-step index  
     63      INTEGER, INTENT( in ), OPTIONAL ::   jit   ! subcycle time-step index (for timesplitting option) 
     64      !! 
     65      INTEGER     ::  ib_obc, jfld, jstart, jend            ! local indices 
     66      INTEGER, POINTER, DIMENSION(:)  ::   nblen, nblenrim  ! short cuts 
    15467      !! 
    15568      !!--------------------------------------------------------------------------- 
    156       INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    157       ! 
    158       INTEGER, SAVE :: immfile, iyyfile                     ! 
    159       INTEGER :: nt              !  record indices (incrementation) 
    160       REAL(wp) ::   zsec, zxy, znum, zden ! time interpolation weight 
     69 
     70      ! for nn_dtactl = 0, initialise data arrays once for all 
     71      ! from initial conditions 
     72      !------------------------------------------------------- 
     73      IF( kt .eq. 1 .and. .not. PRESENT(jit) ) THEN 
     74 
     75         DO ib_obc = 1, nb_obc 
     76            IF( nn_dtactl(ib_obc) .eq. 0 ) THEN 
     77 
     78               !!! TO BE DONE !!! 
     79 
     80            ENDIF 
     81         ENDDO 
     82 
     83      ENDIF 
     84 
     85      ! for nn_dtactl = 1, update external data from files 
     86      !--------------------------------------------------- 
     87      
     88      jstart = 1 
     89      DO ib_obc = 1, nb_obc    
     90         IF( nn_dtactl(ib_obc) .eq. 1 ) THEN 
     91       
     92            IF( PRESENT(jit) ) THEN 
     93               ! Update barotropic boundary conditions only 
     94               ! jit is optional argument for fld_read 
     95               IF( nn_dyn2d(ib_obc) .gt. 0 ) THEN 
     96                  jend = jstart + 2 
     97                  CALL fld_read( kt=kt, kn_fsbc=1, sd=bf(jstart:jend), map=nbmap_ptr(jstart:jend), jit=jit ) 
     98               ENDIF 
     99            ELSE 
     100               jend = jstart + nb_obc_fld(ib_obc) - 1 
     101               CALL fld_read( kt=kt, kn_fsbc=1, sd=bf(jstart:jend ), map=nbmap_ptr(jstart:jend), timeshift=1 ) 
     102            ENDIF 
     103            jstart = jend+1 
     104 
     105         END IF ! nn_dtactl(ib_obc) = 1 
     106      END DO  ! ib_obc 
     107 
     108      END SUBROUTINE obc_dta 
     109 
     110 
     111      SUBROUTINE obc_dta_init 
     112      !!---------------------------------------------------------------------- 
     113      !!                   ***  SUBROUTINE obc_dta_init  *** 
     114      !!                     
     115      !! ** Purpose :   Initialise arrays for reading of external data  
     116      !!                for open boundary conditions 
     117      !! 
     118      !! ** Method  :   Use fldread.F90 
     119      !!                 
     120      !!---------------------------------------------------------------------- 
     121      INTEGER     ::  ib_obc, jfld, jstart, jend, ierror  ! local indices 
     122      !! 
     123      CHARACTER(len=100)                     ::   cn_dir        ! Root directory for location of data files 
     124      CHARACTER(len=100), DIMENSION(nb_obc)  ::   cn_dir_array  ! Root directory for location of data files 
     125      INTEGER                                ::   ilen_global   ! Max length required for global obc dta arrays 
     126      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   ilen1, ilen3  ! size of 1st and 3rd dimensions of local arrays 
     127      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   iobc           ! obc set for a particular jfld 
     128      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   igrid         ! index for grid type (1,2,3 = T,U,V) 
     129      INTEGER, POINTER, DIMENSION(:)         ::   nblen, nblenrim  ! short cuts 
     130      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   blf_i         !  array of namelist information structures 
     131      TYPE(FLD_N) ::   bn_tem, bn_sal, bn_u3d, bn_v3d   !  
     132      TYPE(FLD_N) ::   bn_ssh, bn_u2d, bn_v2d           ! informations about the fields to be read 
     133#if defined key_lim2 
     134      TYPE(FLD_N) ::   bn_frld, bn_hicif, bn_hsnif      ! 
     135#endif 
     136      NAMELIST/namobc_dta/ cn_dir, bn_tem, bn_sal, bn_u3d, bn_v3d, bn_ssh, bn_u2d, bn_v2d  
     137#if defined key_lim2 
     138      NAMELIST/namobc_dta/ bn_frld, bn_hicif, bn_hsnif 
     139#endif 
    161140      !!--------------------------------------------------------------------------- 
    162141 
    163       ! 0.  initialisation : 
    164       ! -------------------- 
    165       IF ( kt == nit000  )  CALL obc_dta_ini ( kt ) 
    166       IF ( nobc_dta == 0 )  RETURN   ! already done in obc_dta_ini 
    167       IF ( itobc == 1    )  RETURN   ! case of only one time frame in file done in obc_dta_ini 
    168  
    169       ! in the following code, we assume that obc data are read from files, with more than 1 time frame in it 
    170  
    171       iyyfile=iyy ; immfile = 00  ! set component of the current file name 
    172       IF ( cffile /= 'annual') immfile = imm   !  
    173       IF ( ln_obc_clim       ) iyyfile = 0000  ! assume that climatological files are labeled y0000 
    174  
    175       ! 1. Synchronize time of run with time of data files 
    176       !--------------------------------------------------- 
    177       ! nday_year is the day number in the current year ( 1 for 01/01 ) 
    178       zsec=MOD( (kt-nit000)*rdt - (nday_year - nday_year0 )*rday, rday ) ! number of seconds in the current day 
    179       IF (ln_obc_clim)  THEN  
    180          zjcnes = nday_year - 1  + zsec/rday 
    181       ELSE 
    182          zjcnes = zjcnes + rdt/rday 
     142      ! Work out how many fields there are to read in and allocate arrays 
     143      ! ----------------------------------------------------------------- 
     144      ALLOCATE( nb_obc_fld(nb_obc) ) 
     145      nb_obc_fld(:) = 0 
     146      DO ib_obc = 1, nb_obc          
     147         IF( nn_dtactl(ib_obc) .eq. 1 ) THEN 
     148            IF( nn_dyn2d(ib_obc) .gt. 0 ) THEN 
     149               nb_obc_fld(ib_obc) = nb_obc_fld(ib_obc) + 3 
     150            ENDIF 
     151            IF( nn_dyn3d(ib_obc) .gt. 0 ) THEN 
     152               nb_obc_fld(ib_obc) = nb_obc_fld(ib_obc) + 2 
     153            ENDIF 
     154            IF( nn_tra(ib_obc) .gt. 0 ) THEN 
     155               nb_obc_fld(ib_obc) = nb_obc_fld(ib_obc) + 2 
     156            ENDIF 
     157#if defined key_lim2 
     158            IF( nn_ice_lim2(ib_obc) .gt. 0 ) THEN 
     159               nb_obc_fld(ib_obc) = nb_obc_fld(ib_obc) + 3 
     160            ENDIF 
     161#endif                
     162         ENDIF 
     163      ENDDO             
     164 
     165      nb_obc_fld_sum = SUM( nb_obc_fld ) 
     166 
     167      ALLOCATE( bf(nb_obc_fld_sum), STAT=ierror ) 
     168      IF( ierror > 0 ) THEN    
     169         CALL ctl_stop( 'obc_dta: unable to allocate bf structure' )   ;   RETURN   
    183170      ENDIF 
    184  
    185       ! look for 'before' record number in the current file 
    186       ntobc = nrecbef ()  ! this function return the record number for 'before', relative to zjcnes 
    187  
    188       IF (MOD(kt-1,10)==0) THEN 
    189          IF (lwp) WRITE(numout,*) 'kt= ',kt,' zjcnes =', zjcnes,' ndastp =',ndastp, 'mm =',imm  
    190       END IF 
    191  
    192       ! 2. read a new data if necessary  
    193       !-------------------------------- 
    194       IF ( ntobc /= ntobc_b ) THEN 
    195          ! we need to read the 'after' record 
    196          ! swap working index: 
    197 # if defined key_dynspg_ts 
    198          nt=nt_m ; nt_m=nt_b ; nt_b=nt 
    199 # endif 
    200          nt=nt_b ; nt_b=nt_a ; nt_a=nt 
    201          ntobc_b = ntobc 
    202  
    203          ! new record number : 
    204          ntobc_a = ntobc_a + 1  
    205  
    206          ! all tricky things related to record number, changing files etc... are managed by obc_read 
    207  
    208          CALL obc_read (kt, nt_a, ntobc_a, iyyfile, immfile ) 
    209  
    210          ! update zjcnes_obc 
    211 # if defined key_dynspg_ts 
    212          ntobc_m=mod(ntobc_b-2+itobc,itobc)+1 
    213          zjcnes_obc(nt_m)= ztcobc(ntobc_m) 
    214 # endif 
    215          zjcnes_obc(nt_b)= ztcobc(ntobc_b) 
    216          zjcnes_obc(nt_a)= ztcobc(ntobc_a) 
     171      ALLOCATE( blf_i(nb_obc_fld_sum), STAT=ierror ) 
     172      IF( ierror > 0 ) THEN    
     173         CALL ctl_stop( 'obc_dta: unable to allocate blf_i structure' )   ;   RETURN   
    217174      ENDIF 
    218  
    219       ! 3.   interpolation at each time step 
    220       ! ------------------------------------ 
    221       IF( ln_obc_clim) THEN 
    222          znum= MOD(zjcnes           - zjcnes_obc(nt_b), REAL(nyear_len(1),wp) ) 
    223          IF( znum < 0 ) znum = znum + REAL(nyear_len(1),wp) 
    224          zden= MOD(zjcnes_obc(nt_a) - zjcnes_obc(nt_b), REAL(nyear_len(1),wp) )  
    225          IF( zden < 0 ) zden = zden + REAL(nyear_len(1),wp) 
    226       ELSE 
    227          znum= zjcnes           - zjcnes_obc(nt_b) 
    228          zden= zjcnes_obc(nt_a) - zjcnes_obc(nt_b) 
     175      ALLOCATE( nbmap_ptr(nb_obc_fld_sum), STAT=ierror ) 
     176      IF( ierror > 0 ) THEN    
     177         CALL ctl_stop( 'obc_dta: unable to allocate nbmap_ptr structure' )   ;   RETURN   
    229178      ENDIF 
    230       zxy = znum / zden 
    231  
    232       IF( lp_obc_east ) THEN 
    233          !  fills sfoe, tfoe, ufoe ,vfoe 
    234          sfoe(:,:) = zxy * sedta (:,:,nt_a) + (1. - zxy)*sedta(:,:,nt_b) 
    235          tfoe(:,:) = zxy * tedta (:,:,nt_a) + (1. - zxy)*tedta(:,:,nt_b) 
    236          ufoe(:,:) = zxy * uedta (:,:,nt_a) + (1. - zxy)*uedta(:,:,nt_b) 
    237          vfoe(:,:) = zxy * vedta (:,:,nt_a) + (1. - zxy)*vedta(:,:,nt_b) 
     179      ALLOCATE( ilen1(nb_obc_fld_sum), ilen3(nb_obc_fld_sum) )  
     180      ALLOCATE( iobc(nb_obc_fld_sum) )  
     181      ALLOCATE( igrid(nb_obc_fld_sum) )  
     182 
     183      ! Read namelists 
     184      ! -------------- 
     185      REWIND(numnam) 
     186      jfld = 0  
     187      DO ib_obc = 1, nb_obc          
     188         IF( nn_dtactl(ib_obc) .eq. 1 ) THEN 
     189            ! set file information 
     190            cn_dir = './'        ! directory in which the model is executed 
     191            ! ... default values (NB: frequency positive => hours, negative => months) 
     192            !                    !  file       ! frequency !  variable        ! time intep !  clim   ! 'yearly' or ! weights  ! rotation  ! 
     193            !                    !  name       !  (hours)  !   name           !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs     ! 
     194            bn_ssh     = FLD_N(  'obc_ssh'     ,    24     ,  'sossheig'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     195            bn_u2d     = FLD_N(  'obc_vel2d_u' ,    24     ,  'vobtcrtx'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     196            bn_v2d     = FLD_N(  'obc_vel2d_v' ,    24     ,  'vobtcrty'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     197            bn_u3d     = FLD_N(  'obc_vel3d_u' ,    24     ,  'vozocrtx'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     198            bn_v3d     = FLD_N(  'obc_vel3d_v' ,    24     ,  'vomecrty'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     199            bn_tem     = FLD_N(  'obc_tem'     ,    24     ,  'votemper'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     200            bn_sal     = FLD_N(  'obc_sal'     ,    24     ,  'vosaline'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     201#if defined key_lim2 
     202            bn_frld    = FLD_N(  'obc_frld'    ,    24     ,  'ildsconc'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     203            bn_hicif   = FLD_N(  'obc_hicif'   ,    24     ,  'iicethic'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     204            bn_hsnif   = FLD_N(  'obc_hsnif'   ,    24     ,  'isnothic'    ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
     205#endif 
     206 
     207            ! Important NOT to rewind here. 
     208            READ( numnam, namobc_dta ) 
     209 
     210            cn_dir_array(ib_obc) = cn_dir 
     211 
     212            nblen => idx_obc(ib_obc)%nblen 
     213            nblenrim => idx_obc(ib_obc)%nblenrim 
     214 
     215            ! Only read in necessary fields for this set. 
     216            ! Important that barotropic variables come first. 
     217            IF( nn_dyn2d(ib_obc) .gt. 0 ) THEN  
     218 
     219               jfld = jfld + 1 
     220               blf_i(jfld) = bn_ssh 
     221               iobc(jfld) = ib_obc 
     222               igrid(jfld) = 1 
     223               IF( nn_dyn2d(ib_obc) .eq. jp_frs ) THEN 
     224                  ilen1(jfld) = nblen(igrid(jfld)) 
     225               ELSE 
     226                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     227               ENDIF 
     228               ilen3(jfld) = 1 
     229 
     230               jfld = jfld + 1 
     231               blf_i(jfld) = bn_u2d 
     232               iobc(jfld) = ib_obc 
     233               igrid(jfld) = 2 
     234               IF( nn_dyn2d(ib_obc) .eq. jp_frs ) THEN 
     235                  ilen1(jfld) = nblen(igrid(jfld)) 
     236               ELSE 
     237                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     238               ENDIF 
     239               ilen3(jfld) = 1 
     240 
     241               jfld = jfld + 1 
     242               blf_i(jfld) = bn_v2d 
     243               iobc(jfld) = ib_obc 
     244               igrid(jfld) = 3 
     245               IF( nn_dyn2d(ib_obc) .eq. jp_frs ) THEN 
     246                  ilen1(jfld) = nblen(igrid(jfld)) 
     247               ELSE 
     248                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     249               ENDIF 
     250               ilen3(jfld) = 1 
     251 
     252            ENDIF 
     253 
     254            ! baroclinic velocities 
     255            IF( nn_dyn3d(ib_obc) .gt. 0 ) THEN 
     256 
     257               jfld = jfld + 1 
     258               blf_i(jfld) = bn_u3d 
     259               iobc(jfld) = ib_obc 
     260               igrid(jfld) = 2 
     261               IF( nn_dyn3d(ib_obc) .eq. jp_frs ) THEN 
     262                  ilen1(jfld) = nblen(igrid(jfld)) 
     263               ELSE 
     264                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     265               ENDIF 
     266               ilen3(jfld) = jpk 
     267 
     268               jfld = jfld + 1 
     269               blf_i(jfld) = bn_v3d 
     270               iobc(jfld) = ib_obc 
     271               igrid(jfld) = 3 
     272               IF( nn_dyn3d(ib_obc) .eq. jp_frs ) THEN 
     273                  ilen1(jfld) = nblen(igrid(jfld)) 
     274               ELSE 
     275                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     276               ENDIF 
     277               ilen3(jfld) = jpk 
     278 
     279            ENDIF 
     280 
     281            ! temperature and salinity 
     282            IF( nn_tra(ib_obc) .gt. 0 ) THEN 
     283 
     284               jfld = jfld + 1 
     285               blf_i(jfld) = bn_tem 
     286               iobc(jfld) = ib_obc 
     287               igrid(jfld) = 1 
     288               IF( nn_tra(ib_obc) .eq. jp_frs ) THEN 
     289                  ilen1(jfld) = nblen(igrid(jfld)) 
     290               ELSE 
     291                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     292               ENDIF 
     293               ilen3(jfld) = jpk 
     294 
     295               jfld = jfld + 1 
     296               blf_i(jfld) = bn_sal 
     297               iobc(jfld) = ib_obc 
     298               igrid(jfld) = 1 
     299               IF( nn_tra(ib_obc) .eq. jp_frs ) THEN 
     300                  ilen1(jfld) = nblen(igrid(jfld)) 
     301               ELSE 
     302                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     303               ENDIF 
     304               ilen3(jfld) = jpk 
     305 
     306            ENDIF 
     307 
     308#if defined key_lim2 
     309            ! sea ice 
     310            IF( nn_tra(ib_obc) .gt. 0 ) THEN 
     311 
     312               jfld = jfld + 1 
     313               blf_i(jfld) = bn_frld 
     314               iobc(jfld) = ib_obc 
     315               igrid(jfld) = 1 
     316               IF( nn_ice_lim2(ib_obc) .eq. jp_frs ) THEN 
     317                  ilen1(jfld) = nblen(igrid(jfld)) 
     318               ELSE 
     319                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     320               ENDIF 
     321               ilen3(jfld) = 1 
     322 
     323               jfld = jfld + 1 
     324               blf_i(jfld) = bn_hicif 
     325               iobc(jfld) = ib_obc 
     326               igrid(jfld) = 1 
     327               IF( nn_ice_lim2(ib_obc) .eq. jp_frs ) THEN 
     328                  ilen1(jfld) = nblen(igrid(jfld)) 
     329               ELSE 
     330                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     331               ENDIF 
     332               ilen3(jfld) = 1 
     333 
     334               jfld = jfld + 1 
     335               blf_i(jfld) = bn_hsnif 
     336               iobc(jfld) = ib_obc 
     337               igrid(jfld) = 1 
     338               IF( nn_ice_lim2(ib_obc) .eq. jp_frs ) THEN 
     339                  ilen1(jfld) = nblen(igrid(jfld)) 
     340               ELSE 
     341                  ilen1(jfld) = nblenrim(igrid(jfld)) 
     342               ENDIF 
     343               ilen3(jfld) = 1 
     344 
     345            ENDIF 
     346#endif 
     347         ENDIF ! nn_dtactl .eq. 1 
     348      ENDDO ! ib_obc 
     349 
     350      IF( jfld .ne. nb_obc_fld_sum ) THEN 
     351         CALL ctl_stop( 'obc_dta: error in initialisation: jpfld .ne. nb_obc_fld_sum' )   ;   RETURN   
    238352      ENDIF 
    239353 
    240       IF( lp_obc_west) THEN 
    241          !  fills sfow, tfow, ufow ,vfow 
    242          sfow(:,:) = zxy * swdta (:,:,nt_a) + (1. - zxy)*swdta(:,:,nt_b) 
    243          tfow(:,:) = zxy * twdta (:,:,nt_a) + (1. - zxy)*twdta(:,:,nt_b) 
    244          ufow(:,:) = zxy * uwdta (:,:,nt_a) + (1. - zxy)*uwdta(:,:,nt_b) 
    245          vfow(:,:) = zxy * vwdta (:,:,nt_a) + (1. - zxy)*vwdta(:,:,nt_b) 
    246       ENDIF 
    247  
    248       IF( lp_obc_north) THEN 
    249          !  fills sfon, tfon, ufon ,vfon 
    250          sfon(:,:) = zxy * sndta (:,:,nt_a) + (1. - zxy)*sndta(:,:,nt_b) 
    251          tfon(:,:) = zxy * tndta (:,:,nt_a) + (1. - zxy)*tndta(:,:,nt_b) 
    252          ufon(:,:) = zxy * undta (:,:,nt_a) + (1. - zxy)*undta(:,:,nt_b) 
    253          vfon(:,:) = zxy * vndta (:,:,nt_a) + (1. - zxy)*vndta(:,:,nt_b) 
    254       ENDIF 
    255  
    256       IF( lp_obc_south) THEN 
    257          !  fills sfos, tfos, ufos ,vfos 
    258          sfos(:,:) = zxy * ssdta (:,:,nt_a) + (1. - zxy)*ssdta(:,:,nt_b) 
    259          tfos(:,:) = zxy * tsdta (:,:,nt_a) + (1. - zxy)*tsdta(:,:,nt_b) 
    260          ufos(:,:) = zxy * usdta (:,:,nt_a) + (1. - zxy)*usdta(:,:,nt_b) 
    261          vfos(:,:) = zxy * vsdta (:,:,nt_a) + (1. - zxy)*vsdta(:,:,nt_b) 
    262       ENDIF 
     354      DO jfld = 1, nb_obc_fld_sum 
     355         ALLOCATE( bf(jfld)%fnow(ilen1(jfld),1,ilen3(jfld)) ) 
     356         IF( blf_i(jfld)%ln_tint ) ALLOCATE( bf(jfld)%fdta(ilen1(jfld),1,ilen3(jfld),2) ) 
     357         nbmap_ptr(jfld)%ptr => idx_obc(iobc(jfld))%nbmap(:,igrid(jfld)) 
     358      ENDDO 
     359 
     360      ! fill bf with blf_i and control print 
     361      !------------------------------------- 
     362      jstart = 1 
     363      DO ib_obc = 1, nb_obc 
     364         jend = jstart + nb_obc_fld(ib_obc) - 1 
     365         CALL fld_fill( bf(jstart:jend), blf_i(jstart:jend), cn_dir_array(ib_obc), 'obc_dta', 'open boundary conditions', 'namobc_dta' ) 
     366         jstart = jend + 1 
     367      ENDDO 
     368 
     369      ! Initialise local boundary data arrays 
     370      ! nn_dtactl=0 : allocate space - will be filled from initial conditions later 
     371      ! nn_dtactl=1 : point to "fnow" arrays 
     372      !------------------------------------- 
     373 
     374      jfld = 0 
     375      DO ib_obc=1, nb_obc 
     376 
     377         nblen => idx_obc(ib_obc)%nblen 
     378         nblenrim => idx_obc(ib_obc)%nblenrim 
     379 
     380         IF( nn_dtactl(ib_obc) .eq. 0 ) THEN 
     381                
     382            ! nn_dtactl = 0  
     383            ! Allocate space 
     384            !--------------- 
     385            IF (nn_dyn2d(ib_obc) .gt. 0) THEN 
     386               IF( nn_dyn2d(ib_obc) .eq. jp_frs ) THEN 
     387                  ilen1(1) = nblen(1) 
     388                  ilen1(2) = nblen(2) 
     389                  ilen1(3) = nblen(3) 
     390               ELSE 
     391                  ilen1(1) = nblenrim(1) 
     392                  ilen1(2) = nblenrim(2) 
     393                  ilen1(3) = nblenrim(3) 
     394               ENDIF 
     395               ALLOCATE( dta_obc(ib_obc)%ssh(ilen1(1)) ) 
     396               ALLOCATE( dta_obc(ib_obc)%u2d(ilen1(2)) ) 
     397               ALLOCATE( dta_obc(ib_obc)%v2d(ilen1(3)) ) 
     398            ENDIF 
     399            IF (nn_dyn3d(ib_obc) .gt. 0) THEN 
     400               IF( nn_dyn3d(ib_obc) .eq. jp_frs ) THEN 
     401                  ilen1(2) = nblen(2) 
     402                  ilen1(3) = nblen(3) 
     403               ELSE 
     404                  ilen1(2) = nblenrim(2) 
     405                  ilen1(3) = nblenrim(3) 
     406               ENDIF 
     407               ALLOCATE( dta_obc(ib_obc)%u3d(ilen1(2),jpk) ) 
     408               ALLOCATE( dta_obc(ib_obc)%v3d(ilen1(3),jpk) ) 
     409            ENDIF 
     410            IF (nn_tra(ib_obc) .gt. 0) THEN 
     411               IF( nn_tra(ib_obc) .eq. jp_frs ) THEN 
     412                  ilen1(1) = nblen(1) 
     413               ELSE 
     414                  ilen1(1) = nblenrim(1) 
     415               ENDIF 
     416               ALLOCATE( dta_obc(ib_obc)%tem(ilen1(1),jpk) ) 
     417               ALLOCATE( dta_obc(ib_obc)%sal(ilen1(1),jpk) ) 
     418            ENDIF 
     419#if defined key_lim2 
     420            IF (nn_ice_lim2(ib_obc) .gt. 0) THEN 
     421               IF( nn_ice_lim2(ib_obc) .eq. jp_frs ) THEN 
     422                  ilen1(1) = nblen(igrid(jfld)) 
     423               ELSE 
     424                  ilen1(1) = nblenrim(igrid(jfld)) 
     425               ENDIF 
     426               ALLOCATE( dta_obc(ib_obc)%ssh(ilen1(1)) ) 
     427               ALLOCATE( dta_obc(ib_obc)%u2d(ilen1(1)) ) 
     428               ALLOCATE( dta_obc(ib_obc)%v2d(ilen1(1)) ) 
     429            ENDIF 
     430#endif 
     431 
     432         ELSE 
     433 
     434            ! nn_dtactl = 1 
     435            ! Set boundary data arrays to point to relevant "fnow" arrays 
     436            !----------------------------------------------------------- 
     437            IF (nn_dyn2d(ib_obc) .gt. 0) THEN 
     438               jfld = jfld + 1 
     439               dta_obc(ib_obc)%ssh => bf(jfld)%fnow(:,1,1) 
     440               jfld = jfld + 1 
     441               dta_obc(ib_obc)%u2d => bf(jfld)%fnow(:,1,1) 
     442               jfld = jfld + 1 
     443               dta_obc(ib_obc)%v2d => bf(jfld)%fnow(:,1,1) 
     444            ENDIF 
     445            IF (nn_dyn3d(ib_obc) .gt. 0) THEN 
     446               jfld = jfld + 1 
     447               dta_obc(ib_obc)%u3d => bf(jfld)%fnow(:,1,:) 
     448               jfld = jfld + 1 
     449               dta_obc(ib_obc)%v3d => bf(jfld)%fnow(:,1,:) 
     450            ENDIF 
     451            IF (nn_tra(ib_obc) .gt. 0) THEN 
     452               jfld = jfld + 1 
     453               dta_obc(ib_obc)%tem => bf(jfld)%fnow(:,1,:) 
     454               jfld = jfld + 1 
     455               dta_obc(ib_obc)%sal => bf(jfld)%fnow(:,1,:) 
     456            ENDIF 
     457#if defined key_lim2 
     458            IF (nn_ice_lim2(ib_obc) .gt. 0) THEN 
     459               jfld = jfld + 1 
     460               dta_obc(ib_obc)%frld  => bf(jfld)%fnow(:,1,1) 
     461               jfld = jfld + 1 
     462               dta_obc(ib_obc)%hicif => bf(jfld)%fnow(:,1,1) 
     463               jfld = jfld + 1 
     464               dta_obc(ib_obc)%hsnif => bf(jfld)%fnow(:,1,1) 
     465            ENDIF 
     466#endif 
     467 
     468         ENDIF ! nn_dtactl .eq. 0 
     469 
     470      ENDDO ! ib_obc  
     471 
     472      END SUBROUTINE obc_dta_init 
     473 
     474#else 
     475   !!---------------------------------------------------------------------- 
     476   !!   Dummy module                   NO Open Boundary Conditions 
     477   !!---------------------------------------------------------------------- 
     478CONTAINS 
     479   SUBROUTINE obc_dta( kt, jit )              ! Empty routine 
     480      WRITE(*,*) 'obc_dta: You should not have seen this print! error?', kt 
    263481   END SUBROUTINE obc_dta 
    264  
    265  
    266    SUBROUTINE obc_dta_ini( kt ) 
    267       !!----------------------------------------------------------------------------- 
    268       !!                       ***  SUBROUTINE obc_dta_ini  *** 
    269       !! 
    270       !! ** Purpose :   When obc_dta first call, realize some data initialization 
    271       !!---------------------------------------------------------------------------- 
    272       INTEGER, INTENT(in)  :: kt      ! ocean time-step index 
    273       ! 
    274       INTEGER ::   ji, jj   ! dummy loop indices 
    275       INTEGER, SAVE :: immfile, iyyfile                     ! 
    276  
    277       ! variables for the julian day calculation 
    278       INTEGER :: iyear, imonth, iday 
    279       REAL(wp) :: zsec , zjulian, zjuliancnes    
    280  
    281       IF(lwp) WRITE(numout,*) 
    282       IF(lwp) WRITE(numout,*)  'obc_dta : find boundary data' 
    283       IF(lwp) WRITE(numout,*)  '~~~~~~~' 
    284       IF (lwp) THEN 
    285          IF ( nobc_dta == 0 ) THEN  
    286             WRITE(numout,*)  '          OBC data taken from initial conditions.' 
    287          ELSE       
    288             WRITE(numout,*)  '          OBC data taken from netcdf files.' 
    289          ENDIF 
    290       ENDIF 
    291       nday_year0 = nday_year  ! to remember the day when kt=nit000 
    292  
    293       sedta(:,:,:) = 0.e0 ; tedta(:,:,:) = 0.e0 ; uedta(:,:,:) = 0.e0 ; vedta(:,:,:) = 0.e0 ! East 
    294       swdta(:,:,:) = 0.e0 ; twdta(:,:,:) = 0.e0 ; uwdta(:,:,:) = 0.e0 ; vwdta(:,:,:) = 0.e0 ! West 
    295       sndta(:,:,:) = 0.e0 ; tndta(:,:,:) = 0.e0 ; undta(:,:,:) = 0.e0 ; vndta(:,:,:) = 0.e0 ! North 
    296       ssdta(:,:,:) = 0.e0 ; tsdta(:,:,:) = 0.e0 ; usdta(:,:,:) = 0.e0 ; vsdta(:,:,:) = 0.e0 ! South 
    297  
    298       sfoe(:,:) = 0.e0  ; tfoe(:,:) = 0.e0 ; ufoe(:,:) = 0.e0 ; vfoe(:,:) = 0.e0   ! East 
    299       sfow(:,:) = 0.e0  ; tfow(:,:) = 0.e0 ; ufow(:,:) = 0.e0 ; vfow(:,:) = 0.e0   ! West 
    300       sfon(:,:) = 0.e0  ; tfon(:,:) = 0.e0 ; ufon(:,:) = 0.e0 ; vfon(:,:) = 0.e0   ! North 
    301       sfos(:,:) = 0.e0  ; tfos(:,:) = 0.e0 ; ufos(:,:) = 0.e0 ; vfos(:,:) = 0.e0   ! South 
    302  
    303       IF (nobc_dta == 0 ) THEN   ! boundary data are the initial data of this run (set only at nit000) 
    304          IF (lp_obc_east) THEN  ! East 
    305             DO ji = nie0 , nie1     
    306                sfoe(nje0:nje1,:) = temsk(nje0:nje1,:) * sn (ji+1 , nje0:nje1 , :) * tmask(ji+1,nje0:nje1 , :) 
    307                tfoe(nje0:nje1,:) = temsk(nje0:nje1,:) * tn (ji+1 , nje0:nje1 , :) * tmask(ji+1,nje0:nje1 , :) 
    308                ufoe(nje0:nje1,:) = uemsk(nje0:nje1,:) * un (ji   , nje0:nje1 , :) * umask(ji,  nje0:nje1 , :) 
    309                vfoe(nje0:nje1,:) = vemsk(nje0:nje1,:) * vn (ji+1 , nje0:nje1 , :) * vmask(ji+1,nje0:nje1 , :) 
    310             END DO 
    311          ENDIF 
    312  
    313          IF (lp_obc_west) THEN  ! West 
    314             DO ji = niw0 , niw1     
    315                sfow(njw0:njw1,:) = twmsk(njw0:njw1,:) * sn (ji , njw0:njw1 , :) * tmask(ji , njw0:njw1 , :) 
    316                tfow(njw0:njw1,:) = twmsk(njw0:njw1,:) * tn (ji , njw0:njw1 , :) * tmask(ji , njw0:njw1 , :) 
    317                ufow(njw0:njw1,:) = uwmsk(njw0:njw1,:) * un (ji , njw0:njw1 , :) * umask(ji , njw0:njw1 , :) 
    318                vfow(njw0:njw1,:) = vwmsk(njw0:njw1,:) * vn (ji , njw0:njw1 , :) * vmask(ji , njw0:njw1 , :) 
    319             END DO 
    320          ENDIF 
    321  
    322          IF (lp_obc_north) THEN ! North 
    323             DO jj = njn0 , njn1 
    324                sfon(nin0:nin1,:) = tnmsk(nin0:nin1,:) * sn (nin0:nin1 , jj+1 , :) * tmask(nin0:nin1 , jj+1 , :) 
    325                tfon(nin0:nin1,:) = tnmsk(nin0:nin1,:) * tn (nin0:nin1 , jj+1 , :) * tmask(nin0:nin1 , jj+1 , :) 
    326                ufon(nin0:nin1,:) = unmsk(nin0:nin1,:) * un (nin0:nin1 , jj+1 , :) * umask(nin0:nin1 , jj+1 , :) 
    327                vfon(nin0:nin1,:) = vnmsk(nin0:nin1,:) * vn (nin0:nin1 , jj   , :) * vmask(nin0:nin1 , jj   , :) 
    328             END DO 
    329          ENDIF 
    330  
    331          IF (lp_obc_south) THEN ! South 
    332             DO jj = njs0 , njs1 
    333                sfos(nis0:nis1,:) = tsmsk(nis0:nis1,:) * sn (nis0:nis1 , jj , :) * tmask(nis0:nis1 , jj , :) 
    334                tfos(nis0:nis1,:) = tsmsk(nis0:nis1,:) * tn (nis0:nis1 , jj , :) * tmask(nis0:nis1 , jj , :) 
    335                ufos(nis0:nis1,:) = usmsk(nis0:nis1,:) * un (nis0:nis1 , jj , :) * umask(nis0:nis1 , jj , :) 
    336                vfos(nis0:nis1,:) = vsmsk(nis0:nis1,:) * vn (nis0:nis1 , jj , :) * vmask(nis0:nis1 , jj , :) 
    337             END DO 
    338          ENDIF 
    339          RETURN  ! exit the routine all is done 
    340       ENDIF  ! nobc_dta = 0  
    341  
    342 !!!! In the following OBC data are read from files. 
    343       ! all logical-mask are initialzed to true when declared 
    344       WHERE ( temsk == 0 ) ltemsk=.FALSE.  
    345       WHERE ( uemsk == 0 ) luemsk=.FALSE.  
    346       WHERE ( vemsk == 0 ) lvemsk=.FALSE.  
    347  
    348       WHERE ( twmsk == 0 ) ltwmsk=.FALSE.  
    349       WHERE ( uwmsk == 0 ) luwmsk=.FALSE.  
    350       WHERE ( vwmsk == 0 ) lvwmsk=.FALSE.  
    351  
    352       WHERE ( tnmsk == 0 ) ltnmsk=.FALSE.  
    353       WHERE ( unmsk == 0 ) lunmsk=.FALSE.  
    354       WHERE ( vnmsk == 0 ) lvnmsk=.FALSE.  
    355  
    356       WHERE ( tsmsk == 0 ) ltsmsk=.FALSE.  
    357       WHERE ( usmsk == 0 ) lusmsk=.FALSE.  
    358       WHERE ( vsmsk == 0 ) lvsmsk=.FALSE.  
    359  
    360       iyear=1950;  imonth=01; iday=01;  zsec=0.  
    361       ! zjuliancnes : julian day corresonding  to  01/01/1950 
    362       CALL ymds2ju(iyear, imonth, iday,zsec , zjuliancnes) 
    363  
    364       !current year and curent month  
    365       iyy=INT(ndastp/10000) ; imm=INT((ndastp -iyy*10000)/100) ; idd=(ndastp-iyy*10000-imm*100) 
    366       IF (iyy <  1900)  iyy = iyy+1900  ! always assume that years are on 4 digits. 
    367       CALL ymds2ju(iyy, imm, idd ,zsec , zjulian) 
    368       ndate0_cnes = zjulian - zjuliancnes   ! jcnes day when call to obc_dta_ini 
    369  
    370       iyyfile=iyy ; immfile=0  ! set component of the current file name 
    371       IF ( cffile /= 'annual') immfile=imm 
    372       IF ( ln_obc_clim) iyyfile = 0  ! assume that climatological files are labeled y0000 
    373  
    374       CALL obc_dta_chktime ( iyyfile, immfile ) 
    375  
    376       IF ( itobc == 1 ) THEN  
    377          ! in this case we will provide boundary data only once. 
    378          nt_a=1 ; ntobc_a=1 
    379          CALL obc_read (nit000, nt_a, ntobc_a, iyyfile, immfile)  
    380          IF( lp_obc_east ) THEN 
    381             !  fills sfoe, tfoe, ufoe ,vfoe 
    382             sfoe(:,:) =  sedta (:,:,1) ; tfoe(:,:) =  tedta (:,:,1) 
    383             ufoe(:,:) =  uedta (:,:,1) ; vfoe(:,:) =  vedta (:,:,1) 
    384          ENDIF 
    385  
    386          IF( lp_obc_west) THEN 
    387             !  fills sfow, tfow, ufow ,vfow 
    388             sfow(:,:) =  swdta (:,:,1) ; tfow(:,:) =  twdta (:,:,1) 
    389             ufow(:,:) =  uwdta (:,:,1) ; vfow(:,:) =  vwdta (:,:,1) 
    390          ENDIF 
    391  
    392          IF( lp_obc_north) THEN 
    393             !  fills sfon, tfon, ufon ,vfon 
    394             sfon(:,:) =  sndta (:,:,1) ; tfon(:,:) =  tndta (:,:,1) 
    395             ufon(:,:) =  undta (:,:,1) ; vfon(:,:) =  vndta (:,:,1) 
    396          ENDIF 
    397  
    398          IF( lp_obc_south) THEN 
    399             !  fills sfos, tfos, ufos ,vfos 
    400             sfos(:,:) =  ssdta (:,:,1) ; tfos(:,:) =  tsdta (:,:,1) 
    401             ufos(:,:) =  usdta (:,:,1) ; vfos(:,:) =  vsdta (:,:,1) 
    402          ENDIF 
    403          RETURN  ! we go out of obc_dta_ini -------------------------------------->>>>> 
    404       ENDIF 
    405  
    406       ! nday_year is the day number in the current year ( 1 for 01/01 ) 
    407       ! we suppose that we always start from the begining of a day 
    408       !    zsec=MOD( (kt-nit000)*rdt - (nday_year - nday_year0 )*rday, rday ) ! number of seconds in the current day 
    409       zsec=0.e0  ! here, kt=nit000, nday_year = ndat_year0  
    410  
    411       IF (ln_obc_clim)  THEN  
    412          zjcnes = nday_year - 1  + zsec/rday  ! for clim file time is in days in a year 
    413       ELSE 
    414          zjcnes = ndate0_cnes + (nday_year - nday_year0 ) + zsec/rday 
    415       ENDIF 
    416  
    417       ! look for 'before' record number in the current file 
    418       ntobc = nrecbef () 
    419  
    420       IF (lwp) WRITE(numout,*) 'obc files frequency :',cffile 
    421       IF (lwp) WRITE(numout,*) ' zjcnes0 =',zjcnes,' ndastp0 =',ndastp 
    422       IF (lwp) WRITE(numout,*) ' annee0 ',iyy,' month0 ', imm,' day0 ', idd 
    423       IF (lwp) WRITE(numout,*) 'first file open :',cl_obc_nTS 
    424  
    425       ! record initialisation 
    426       !-------------------- 
    427       nt_b = 1 ; nt_a = 2 
    428  
    429       ntobc_a = ntobc + 1 
    430       ntobc_b = ntobc 
    431  
    432       CALL obc_read (kt, nt_b, ntobc_b, iyyfile, immfile)  ! read 'before' fields 
    433       CALL obc_read (kt, nt_a, ntobc_a, iyyfile, immfile)  ! read 'after' fields 
    434  
    435       ! additional frame in case of time-splitting 
    436 # if defined key_dynspg_ts 
    437       nt_m = 0 
    438       ntobc_m=mod(ntobc_b-2+itobc,itobc)+1 
    439       zjcnes_obc(nt_m)= ztcobc(ntobc_m) ! FDbug has not checked that this is correct!! 
    440       IF (ln_rstart) THEN 
    441          CALL obc_read (kt, nt_m, ntobc_m, iyyfile, immfile)  ! read 'after' fields 
    442       ENDIF 
    443 # endif 
    444  
    445       zjcnes_obc(nt_b)= ztcobc(ntobc_b) 
    446       zjcnes_obc(nt_a)= ztcobc(ntobc_a) 
    447       !  
    448    END SUBROUTINE obc_dta_ini 
    449  
    450  
    451    SUBROUTINE obc_dta_chktime (kyyfile, kmmfile) 
    452       ! 
    453       ! check the number of time steps in the files and read ztcobc  
    454       ! 
    455       ! * Arguments 
    456       INTEGER, INTENT(in) :: kyyfile, kmmfile 
    457       ! * local variables 
    458       INTEGER :: istop       ! error control 
    459       INTEGER :: ji          ! dummy loop index 
    460  
    461       INTEGER ::  idvar, id_e, id_w, id_n, id_s       ! file identifiers 
    462       INTEGER, DIMENSION(1)  :: itmp 
    463       CHARACTER(LEN=25) :: cl_vname 
    464  
    465       ntobc_a = 0; itobce =0 ; itobcw = 0; itobcn = 0; itobcs = 0 
    466       ! build file name 
    467       IF(ln_obc_clim) THEN   ! revert to old convention for climatological OBC forcing 
    468          cl_obc_eTS='obceast_TS.nc' 
    469          cl_obc_wTS='obcwest_TS.nc' 
    470          cl_obc_nTS='obcnorth_TS.nc' 
    471          cl_obc_sTS='obcsouth_TS.nc' 
    472       ELSE                   ! convention for climatological OBC 
    473          WRITE(cl_obc_eTS ,'("obc_east_TS_y",i4.4,"m",i2.2,".nc")'  ) kyyfile,kmmfile 
    474          WRITE(cl_obc_wTS ,'("obc_west_TS_y",i4.4,"m",i2.2,".nc")'  ) kyyfile,kmmfile 
    475          WRITE(cl_obc_nTS ,'("obc_north_TS_y",i4.4,"m",i2.2,".nc")' ) kyyfile,kmmfile 
    476          WRITE(cl_obc_sTS ,'("obc_south_TS_y",i4.4,"m",i2.2,".nc")' ) kyyfile,kmmfile 
    477       ENDIF 
    478  
    479       cl_vname = 'time_counter' 
    480       IF ( lp_obc_east ) THEN 
    481          CALL iom_open ( cl_obc_eTS , id_e ) 
    482          idvar = iom_varid( id_e, cl_vname, kdimsz = itmp ); itobce=itmp(1) 
    483       ENDIF 
    484       IF ( lp_obc_west ) THEN 
    485          CALL iom_open ( cl_obc_wTS , id_w ) 
    486          idvar = iom_varid( id_w, cl_vname, kdimsz = itmp ) ; itobcw=itmp(1) 
    487       ENDIF 
    488       IF ( lp_obc_north ) THEN 
    489          CALL iom_open ( cl_obc_nTS , id_n ) 
    490          idvar = iom_varid( id_n, cl_vname, kdimsz = itmp ) ; itobcn=itmp(1) 
    491       ENDIF 
    492       IF ( lp_obc_south ) THEN 
    493          CALL iom_open ( cl_obc_sTS , id_s ) 
    494          idvar = iom_varid( id_s, cl_vname, kdimsz = itmp ) ; itobcs=itmp(1) 
    495       ENDIF 
    496  
    497       itobc = MAX( itobce, itobcw, itobcn, itobcs ) 
    498       istop = 0 
    499       IF ( lp_obc_east  .AND. itobce /= itobc ) istop = istop+1  
    500       IF ( lp_obc_west  .AND. itobcw /= itobc ) istop = istop+1       
    501       IF ( lp_obc_north .AND. itobcn /= itobc ) istop = istop+1 
    502       IF ( lp_obc_south .AND. itobcs /= itobc ) istop = istop+1  
    503       nstop = nstop + istop 
    504  
    505       IF ( istop /=  0 )  THEN 
    506          WRITE(ctmp1,*) ' east, west, north, south: ', itobce, itobcw, itobcn, itobcs 
    507          CALL ctl_stop( 'obcdta : all files must have the same number of time steps', ctmp1 ) 
    508       ENDIF 
    509  
    510       IF ( itobc == 1 ) THEN  
    511          IF (lwp) THEN 
    512             WRITE(numout,*) ' obcdta found one time step only in the OBC files' 
    513             IF (ln_obc_clim) THEN 
    514                ! OK no problem 
    515             ELSE 
    516                ln_obc_clim=.true. 
    517                WRITE(numout,*) ' we force ln_obc_clim to T' 
    518             ENDIF 
    519          ENDIF 
    520       ELSE 
    521          IF ( ALLOCATED(ztcobc) ) DEALLOCATE ( ztcobc ) 
    522          ALLOCATE (ztcobc(itobc)) 
    523          DO ji=1,1   ! use a dummy loop to read ztcobc only once 
    524             IF ( lp_obc_east ) THEN 
    525                CALL iom_gettime ( id_e, ztcobc, cl_vname ) ; CALL iom_close (id_e) ; EXIT 
    526             ENDIF 
    527             IF ( lp_obc_west ) THEN 
    528                CALL iom_gettime ( id_w, ztcobc, cl_vname ) ; CALL iom_close (id_w) ; EXIT 
    529             ENDIF 
    530             IF ( lp_obc_north ) THEN 
    531                CALL iom_gettime ( id_n, ztcobc, cl_vname ) ; CALL iom_close (id_n) ; EXIT 
    532             ENDIF 
    533             IF ( lp_obc_south ) THEN 
    534                CALL iom_gettime ( id_s, ztcobc, cl_vname ) ; CALL iom_close (id_s) ; EXIT 
    535             ENDIF 
    536          END DO 
    537          rdt_obc = ztcobc(2)-ztcobc(1)  !  just an information, not used for any computation 
    538          IF (lwp) WRITE(numout,*) ' obcdta found', itobc,' time steps in the OBC files' 
    539          IF (lwp) WRITE(numout,*) ' time step of obc data :', rdt_obc,' days'             
    540       ENDIF 
    541       zjcnes = zjcnes - rdt/rday  ! trick : zcnes is always incremented by rdt/rday in obc_dta! 
    542    END SUBROUTINE obc_dta_chktime 
    543  
    544 # if defined key_dynspg_ts || defined key_dynspg_exp 
    545    SUBROUTINE obc_dta_bt( kt, kbt ) 
    546       !!--------------------------------------------------------------------------- 
    547       !!                      ***  SUBROUTINE obc_dta  *** 
    548       !! 
    549       !! ** Purpose :   time interpolation of barotropic data for time-splitting scheme 
    550       !!                Data at the boundary must be in m2/s  
    551       !! 
    552       !! History :  9.0  !  05-11 (V. garnier) Original code 
    553       !!--------------------------------------------------------------------------- 
    554       INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    555       INTEGER, INTENT( in ) ::   kbt         ! barotropic ocean time-step index 
    556       ! 
    557       INTEGER ::   ji, jj  ! dummy loop indices 
    558       INTEGER ::   i15 
    559       INTEGER ::   itobcm, itobcp 
    560       REAL(wp) ::  zxy 
    561       INTEGER ::   isrel           ! number of seconds since 1/1/1992 
    562       !!--------------------------------------------------------------------------- 
    563  
    564       ! 1.   First call: check time frames available in files. 
    565       ! ------------------------------------------------------- 
    566  
    567       IF( kt == nit000 ) THEN 
    568  
    569          ! 1.1  Barotropic tangential velocities set to zero 
    570          ! ------------------------------------------------- 
    571          IF( lp_obc_east  ) vbtfoe(:) = 0.e0 
    572          IF( lp_obc_west  ) vbtfow(:) = 0.e0 
    573          IF( lp_obc_south ) ubtfos(:) = 0.e0 
    574          IF( lp_obc_north ) ubtfon(:) = 0.e0 
    575  
    576          ! 1.2  Sea surface height and normal barotropic velocities set to zero 
    577          !                               or initial conditions if nobc_dta == 0 
    578          ! -------------------------------------------------------------------- 
    579  
    580          IF( lp_obc_east ) THEN 
    581             ! initialisation to zero 
    582             sshedta(:,:) = 0.e0 
    583             ubtedta(:,:) = 0.e0 
    584             vbtedta(:,:) = 0.e0 ! tangential component 
    585             !                                        ! ================== ! 
    586             IF( nobc_dta == 0 )   THEN               ! initial state used ! 
    587                !                                     ! ================== ! 
    588                !  Fills sedta, tedta, uedta (global arrays) 
    589                !  Remark: this works for njzoom = 1. Should the definition of ij include njzoom? 
    590                DO ji = nie0, nie1 
    591                   DO jj = 1, jpj 
    592                      sshedta(jj,1) = sshn(ji+1,jj) * tmask(ji+1,jj,1) 
    593                   END DO 
    594                END DO 
    595             ENDIF 
    596          ENDIF 
    597  
    598          IF( lp_obc_west) THEN 
    599             ! initialisation to zero 
    600             sshwdta(:,:) = 0.e0 
    601             ubtwdta(:,:) = 0.e0 
    602             vbtwdta(:,:) = 0.e0 ! tangential component 
    603             !                                        ! ================== ! 
    604             IF( nobc_dta == 0 )   THEN               ! initial state used ! 
    605                !                                     ! ================== ! 
    606                !  Fills swdta, twdta, uwdta (global arrays) 
    607                !  Remark: this works for njzoom = 1. Should the definition of ij include njzoom? 
    608                DO ji = niw0, niw1 
    609                   DO jj = 1, jpj 
    610                      sshwdta(jj,1) = sshn(ji,jj) * tmask(ji,jj,1) 
    611                   END DO 
    612                END DO 
    613             ENDIF 
    614          ENDIF 
    615  
    616          IF( lp_obc_north) THEN 
    617             ! initialisation to zero 
    618             sshndta(:,:) = 0.e0 
    619             ubtndta(:,:) = 0.e0 ! tangential component 
    620             vbtndta(:,:) = 0.e0 
    621             !                                        ! ================== ! 
    622             IF( nobc_dta == 0 ) THEN                 ! initial state used ! 
    623                !                                     ! ================== ! 
    624                !  Fills sndta, tndta, vndta (global arrays) 
    625                !  Remark: this works for njzoom = 1. Should the definition of ij include njzoom? 
    626                DO jj = njn0, njn1 
    627                   DO ji = 1, jpi 
    628                      sshndta(ji,1) = sshn(ji,jj+1) * tmask(ji,jj+1,1) 
    629                   END DO 
    630                END DO 
    631             ENDIF 
    632          ENDIF 
    633  
    634          IF( lp_obc_south) THEN 
    635             ! initialisation to zero 
    636             sshsdta(:,:) = 0.e0 
    637             ubtsdta(:,:) = 0.e0 ! tangential component 
    638             vbtsdta(:,:) = 0.e0 
    639             !                                        ! ================== ! 
    640             IF( nobc_dta == 0 )   THEN               ! initial state used ! 
    641                !                                     ! ================== ! 
    642                !  Fills ssdta, tsdta, vsdta (global arrays) 
    643                !  Remark: this works for njzoom = 1. Should the definition of ij include njzoom? 
    644                DO jj = njs0, njs1 
    645                   DO ji = 1, jpi 
    646                      sshsdta(ji,1) = sshn(ji,jj) * tmask(ji,jj,1) 
    647                   END DO 
    648                END DO 
    649             ENDIF 
    650          ENDIF 
    651  
    652          IF( nobc_dta == 0 ) CALL obc_depth_average(1)   ! depth averaged velocity from the OBC depth-dependent frames 
    653  
    654       ENDIF        !       END kt == nit000 
    655  
    656       !!------------------------------------------------------------------------------------ 
    657       ! 2.      Initialize the time we are at. Does this every time the routine is called, 
    658       !         excepted when nobc_dta = 0 
    659       ! 
    660  
    661       ! 3.  Call at every time step : Linear interpolation of BCs to current time step 
    662       ! ---------------------------------------------------------------------- 
    663  
    664       IF( lk_dynspg_ts ) THEN 
    665          isrel = (kt-1)*rdt + kbt*(rdt/REAL(nn_baro,wp)) 
    666       ELSE IF( lk_dynspg_exp ) THEN 
    667          isrel=kt*rdt 
    668       ENDIF 
    669  
    670       itobcm = nt_b 
    671       itobcp = nt_a 
    672       IF( itobc == 1 .OR. nobc_dta == 0 ) THEN 
    673          zxy = 0.e0 
    674          itobcm = 1 
    675          itobcp = 1 
    676       ELSE IF( itobc == 12 ) THEN 
    677          i15   = nday / 16 
    678          zxy = FLOAT( nday + 15 - 30 * i15 ) / 30. 
    679       ELSE 
    680          zxy = (zjcnes_obc(nt_a)-FLOAT(isrel)) / (zjcnes_obc(nt_a)-zjcnes_obc(nt_b)) 
    681          IF( zxy < 0. ) THEN   ! case of extrapolation, switch to old time frames 
    682             itobcm = nt_m 
    683             itobcp = nt_b 
    684             zxy = (zjcnes_obc(nt_b)-FLOAT(isrel)) / (zjcnes_obc(nt_b)-zjcnes_obc(nt_m)) 
    685          ENDIF 
    686       ENDIF 
    687  
    688       IF( lp_obc_east ) THEN           !  fills sshfoe, ubtfoe (local to each processor) 
    689          DO jj = 1, jpj 
    690             sshfoe(jj) = zxy * sshedta(jj,itobcp) + (1.-zxy) * sshedta(jj,itobcm) 
    691             ubtfoe(jj) = zxy * ubtedta(jj,itobcp) + (1.-zxy) * ubtedta(jj,itobcm) 
    692             vbtfoe(jj) = zxy * vbtedta(jj,itobcp) + (1.-zxy) * vbtedta(jj,itobcm) 
    693          END DO 
    694       ENDIF 
    695  
    696       IF( lp_obc_west) THEN            !  fills sshfow, ubtfow (local to each processor) 
    697          DO jj = 1, jpj 
    698             sshfow(jj) = zxy * sshwdta(jj,itobcp) + (1.-zxy) * sshwdta(jj,itobcm) 
    699             ubtfow(jj) = zxy * ubtwdta(jj,itobcp) + (1.-zxy) * ubtwdta(jj,itobcm) 
    700             vbtfow(jj) = zxy * vbtwdta(jj,itobcp) + (1.-zxy) * vbtwdta(jj,itobcm) 
    701          END DO 
    702       ENDIF 
    703  
    704       IF( lp_obc_north) THEN           !  fills sshfon, vbtfon (local to each processor) 
    705          DO ji = 1, jpi 
    706             sshfon(ji) = zxy * sshndta(ji,itobcp) + (1.-zxy) * sshndta(ji,itobcm) 
    707             ubtfon(ji) = zxy * ubtndta(ji,itobcp) + (1.-zxy) * ubtndta(ji,itobcm) 
    708             vbtfon(ji) = zxy * vbtndta(ji,itobcp) + (1.-zxy) * vbtndta(ji,itobcm) 
    709          END DO 
    710       ENDIF 
    711  
    712       IF( lp_obc_south) THEN           !  fills sshfos, vbtfos (local to each processor) 
    713          DO ji = 1, jpi 
    714             sshfos(ji) = zxy * sshsdta(ji,itobcp) + (1.-zxy) * sshsdta(ji,itobcm) 
    715             ubtfos(ji) = zxy * ubtsdta(ji,itobcp) + (1.-zxy) * ubtsdta(ji,itobcm) 
    716             vbtfos(ji) = zxy * vbtsdta(ji,itobcp) + (1.-zxy) * vbtsdta(ji,itobcm) 
    717          END DO 
    718       ENDIF 
    719  
    720    END SUBROUTINE obc_dta_bt 
    721  
    722 # else 
    723    !!----------------------------------------------------------------------------- 
    724    !!   Default option 
    725    !!----------------------------------------------------------------------------- 
    726    SUBROUTINE obc_dta_bt ( kt, kbt )       ! Empty routine 
    727       !! * Arguments 
    728       INTEGER,INTENT(in) :: kt 
    729       INTEGER, INTENT( in ) ::   kbt         ! barotropic ocean time-step index 
    730       WRITE(*,*) 'obc_dta_bt: You should not have seen this print! error?', kt 
    731       WRITE(*,*) 'obc_dta_bt: You should not have seen this print! error?', kbt 
    732    END SUBROUTINE obc_dta_bt 
    733 # endif 
    734  
    735    SUBROUTINE obc_read (kt, nt_x, ntobc_x, iyy, imm) 
    736       !!------------------------------------------------------------------------- 
    737       !!                      ***  ROUTINE obc_read  *** 
    738       !! 
    739       !! ** Purpose :  Read the boundary data in files identified by iyy and imm 
    740       !!               According to the validated open boundaries, return the  
    741       !!               following arrays : 
    742       !!                sedta, tedta : East OBC salinity and temperature 
    743       !!                uedta, vedta :   "   "  u and v velocity component       
    744       !! 
    745       !!                swdta, twdta : West OBC salinity and temperature 
    746       !!                uwdta, vwdta :   "   "  u and v velocity component       
    747       !! 
    748       !!                sndta, tndta : North OBC salinity and temperature 
    749       !!                undta, vndta :   "   "  u and v velocity component       
    750       !! 
    751       !!                ssdta, tsdta : South OBC salinity and temperature 
    752       !!                usdta, vsdta :   "   "  u and v velocity component       
    753       !! 
    754       !! ** Method  :  These fields are read in the record ntobc_x of the files. 
    755       !!               The number of records is already known. If  ntobc_x is greater 
    756       !!               than the number of record, this routine will look for next file, 
    757       !!               updating the indices (case of inter-annual obcs) or loop at the 
    758       !!               begining in case of climatological file (ln_obc_clim = true ). 
    759       !! ------------------------------------------------------------------------- 
    760       !! History:     !  2005  ( P. Mathiot, C. Langlais ) Original code 
    761       !!              !  2008  ( J,M, Molines ) Use IOM and cleaning 
    762       !!-------------------------------------------------------------------------- 
    763  
    764       ! * Arguments 
    765       INTEGER, INTENT( in ) :: kt, nt_x 
    766       INTEGER, INTENT( inout ) :: ntobc_x , iyy, imm      ! yes ! inout ! 
    767  
    768       ! * Local variables 
    769       CHARACTER (len=40) :: &    ! file names 
    770          cl_obc_eTS   , cl_obc_eU,  cl_obc_eV,& 
    771          cl_obc_wTS   , cl_obc_wU,  cl_obc_wV,& 
    772          cl_obc_nTS   , cl_obc_nU,  cl_obc_nV,& 
    773          cl_obc_sTS   , cl_obc_sU,  cl_obc_sV 
    774  
    775       INTEGER :: ikprint 
    776       REAL(wp) :: zmin, zmax   ! control of boundary values 
    777  
    778       !IOM stuff 
    779       INTEGER :: id_e, id_w, id_n, id_s 
    780       INTEGER, DIMENSION(2) :: istart, icount 
    781  
    782       !-------------------------------------------------------------------------- 
    783       IF ( ntobc_x > itobc ) THEN 
    784          IF (ln_obc_clim) THEN  ! just loop on the same file 
    785             ntobc_x = 1  
    786          ELSE 
    787             ! need to change file : it is always for an 'after' data 
    788             IF ( cffile == 'annual' ) THEN ! go to next year file 
    789                iyy = iyy + 1 
    790             ELSE IF ( cffile =='monthly' ) THEN  ! go to next month file 
    791                imm = imm + 1  
    792                IF ( imm == 13 ) THEN  
    793                   imm = 1 ; iyy = iyy + 1 
    794                ENDIF 
    795             ELSE 
    796                ctmp1='obcread : this type of obc file is not supported :( ' 
    797                ctmp2=TRIM(cffile) 
    798                CALL ctl_stop (ctmp1, ctmp2) 
    799                ! cffile should be either annual or monthly ... 
    800             ENDIF 
    801             ! as the file is changed, need to update itobc etc ... 
    802             CALL obc_dta_chktime (iyy,imm) 
    803             ntobc_x = nrecbef() + 1 ! remember : this case occur for an after data 
    804          ENDIF 
    805       ENDIF 
    806  
    807       IF( lp_obc_east ) THEN  
    808          ! ... Read datafile and set temperature, salinity and normal velocity 
    809          ! ... initialise the sedta, tedta, uedta arrays 
    810          IF(ln_obc_clim) THEN  ! revert to old convention for climatological OBC forcing 
    811             cl_obc_eTS='obceast_TS.nc' 
    812             cl_obc_eU ='obceast_U.nc' 
    813             cl_obc_eV ='obceast_V.nc' 
    814          ELSE                  ! convention for climatological OBC 
    815             WRITE(cl_obc_eTS ,'("obc_east_TS_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    816             WRITE(cl_obc_eU  ,'("obc_east_U_y"   ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    817             WRITE(cl_obc_eV  ,'("obc_east_V_y"   ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    818          ENDIF 
    819          ! JMM this may change depending on the obc data format ... 
    820          istart(:)=(/nje0+njmpp-1,1/) ; icount(:)=(/nje1-nje0 +1,jpk/) 
    821          IF (lwp) WRITE(numout,*) 'read data in :', TRIM(cl_obc_eTS) 
    822          IF (nje1 >= nje0 ) THEN 
    823             CALL iom_open ( cl_obc_eTS , id_e ) 
    824             CALL iom_get ( id_e, jpdom_unknown, 'votemper', tedta(nje0:nje1,:,nt_x), & 
    825                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    826             CALL iom_get ( id_e, jpdom_unknown, 'vosaline', sedta(nje0:nje1,:,nt_x), & 
    827                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    828 # if defined key_dynspg_ts || defined key_dynspg_exp 
    829             CALL iom_get ( id_e, jpdom_unknown, 'vossurfh', sshedta(nje0:nje1,nt_x), & 
    830                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    831 # endif 
    832             CALL iom_close (id_e) 
    833             ! 
    834             CALL iom_open ( cl_obc_eU , id_e ) 
    835             CALL iom_get  ( id_e, jpdom_unknown, 'vozocrtx', uedta(nje0:nje1,:,nt_x), & 
    836                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    837             CALL iom_close ( id_e ) 
    838             ! 
    839             CALL iom_open ( cl_obc_eV , id_e ) 
    840             CALL iom_get ( id_e, jpdom_unknown, 'vomecrty', vedta(nje0:nje1,:,nt_x), & 
    841                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    842             CALL iom_close ( id_e ) 
    843  
    844             ! mask the boundary values 
    845             tedta(:,:,nt_x) = tedta(:,:,nt_x)*temsk(:,:) ;  sedta(:,:,nt_x) = sedta(:,:,nt_x)*temsk(:,:) 
    846             uedta(:,:,nt_x) = uedta(:,:,nt_x)*uemsk(:,:) ;  vedta(:,:,nt_x) = vedta(:,:,nt_x)*vemsk(:,:) 
    847  
    848             ! check any outliers  
    849             zmin=MINVAL( sedta(:,:,nt_x), mask=ltemsk ) ; zmax=MAXVAL(sedta(:,:,nt_x), mask=ltemsk) 
    850             IF (  zmin < 5 .OR. zmax > 50)   THEN 
    851                CALL ctl_stop('Error in sedta',' routine obcdta') 
    852             ENDIF 
    853             zmin=MINVAL( tedta(:,:,nt_x), mask=ltemsk ) ; zmax=MAXVAL(tedta(:,:,nt_x), mask=ltemsk) 
    854             IF (  zmin < -10. .OR. zmax > 40)   THEN 
    855                CALL ctl_stop('Error in tedta',' routine obcdta') 
    856             ENDIF 
    857             zmin=MINVAL( uedta(:,:,nt_x), mask=luemsk ) ; zmax=MAXVAL(uedta(:,:,nt_x), mask=luemsk) 
    858             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    859                CALL ctl_stop('Error in uedta',' routine obcdta') 
    860             ENDIF 
    861             zmin=MINVAL( vedta(:,:,nt_x), mask=lvemsk ) ; zmax=MAXVAL(vedta(:,:,nt_x), mask=lvemsk) 
    862             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    863                CALL ctl_stop('Error in vedta',' routine obcdta') 
    864             ENDIF 
    865  
    866             !               Usually printout is done only once at kt = nit000, unless nprint (namelist) > 1       
    867             IF ( lwp .AND.  ( kt == nit000 .OR. nprint /= 0 )  ) THEN 
    868                WRITE(numout,*) 
    869                WRITE(numout,*) ' Read East OBC data records ', ntobc_x 
    870                ikprint = jpj/20 +1 
    871                WRITE(numout,*) ' Temperature  record 1 - printout every 3 level' 
    872                CALL prihre( tedta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    873                WRITE(numout,*) 
    874                WRITE(numout,*) ' Salinity  record 1 - printout every 3 level' 
    875                CALL prihre( sedta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    876                WRITE(numout,*) 
    877                WRITE(numout,*) ' Normal velocity U  record 1  - printout every 3 level' 
    878                CALL prihre( uedta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    879                WRITE(numout,*) 
    880                WRITE(numout,*) ' Tangential velocity V  record 1  - printout every 3 level' 
    881                CALL prihre( vedta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    882             ENDIF 
    883          ENDIF 
    884       ENDIF 
    885 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    886       IF ( lp_obc_west ) THEN 
    887          ! ... Read datafile and set temperature, salinity and normal velocity 
    888          ! ... initialise the swdta, twdta, uwdta arrays 
    889          IF (ln_obc_clim) THEN   ! revert to old convention for climatological OBC forcing 
    890             cl_obc_wTS='obcwest_TS.nc' 
    891             cl_obc_wU ='obcwest_U.nc' 
    892             cl_obc_wV ='obcwest_V.nc' 
    893          ELSE                    ! convention for climatological OBC 
    894             WRITE(cl_obc_wTS ,'("obc_west_TS_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    895             WRITE(cl_obc_wU  ,'("obc_west_U_y"   ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    896             WRITE(cl_obc_wV  ,'("obc_west_V_y"   ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    897          ENDIF 
    898          istart(:)=(/njw0+njmpp-1,1/) ; icount(:)=(/njw1-njw0 +1,jpk/) 
    899          IF (lwp) WRITE(numout,*) 'read data in :', TRIM(cl_obc_wTS) 
    900  
    901          IF ( njw1 >= njw0 ) THEN 
    902             CALL iom_open ( cl_obc_wTS , id_w ) 
    903             CALL iom_get ( id_w, jpdom_unknown, 'votemper', twdta(njw0:njw1,:,nt_x), &  
    904                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    905  
    906             CALL iom_get ( id_w, jpdom_unknown, 'vosaline', swdta(njw0:njw1,:,nt_x), & 
    907                &               ktime=ntobc_x , kstart=istart, kcount= icount) 
    908 # if defined key_dynspg_ts || defined key_dynspg_exp 
    909             CALL iom_get ( id_w, jpdom_unknown, 'vossurfh', sshwdta(njw0:njw1,nt_x), & 
    910                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    911 # endif 
    912             CALL iom_close (id_w) 
    913             ! 
    914             CALL iom_open ( cl_obc_wU , id_w ) 
    915             CALL iom_get  ( id_w, jpdom_unknown, 'vozocrtx', uwdta(njw0:njw1,:,nt_x),& 
    916                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    917             CALL iom_close ( id_w ) 
    918             ! 
    919             CALL iom_open ( cl_obc_wV , id_w ) 
    920             CALL iom_get ( id_w, jpdom_unknown, 'vomecrty', vwdta(njw0:njw1,:,nt_x), & 
    921                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    922             CALL iom_close ( id_w ) 
    923  
    924             ! mask the boundary values 
    925             twdta(:,:,nt_x) = twdta(:,:,nt_x)*twmsk(:,:) ;  swdta(:,:,nt_x) = swdta(:,:,nt_x)*twmsk(:,:) 
    926             uwdta(:,:,nt_x) = uwdta(:,:,nt_x)*uwmsk(:,:) ;  vwdta(:,:,nt_x) = vwdta(:,:,nt_x)*vwmsk(:,:) 
    927  
    928             ! check any outliers 
    929             zmin=MINVAL( swdta(:,:,nt_x), mask=ltwmsk ) ; zmax=MAXVAL(swdta(:,:,nt_x), mask=ltwmsk) 
    930             IF (  zmin < 5 .OR. zmax > 50)   THEN 
    931                CALL ctl_stop('Error in swdta',' routine obcdta') 
    932             ENDIF 
    933             zmin=MINVAL( twdta(:,:,nt_x), mask=ltwmsk ) ; zmax=MAXVAL(twdta(:,:,nt_x), mask=ltwmsk) 
    934             IF (  zmin < -10. .OR. zmax > 40)   THEN 
    935                CALL ctl_stop('Error in twdta',' routine obcdta') 
    936             ENDIF 
    937             zmin=MINVAL( uwdta(:,:,nt_x), mask=luwmsk ) ; zmax=MAXVAL(uwdta(:,:,nt_x), mask=luwmsk) 
    938             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    939                CALL ctl_stop('Error in uwdta',' routine obcdta') 
    940             ENDIF 
    941             zmin=MINVAL( vwdta(:,:,nt_x), mask=lvwmsk ) ; zmax=MAXVAL(vwdta(:,:,nt_x), mask=lvwmsk) 
    942             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    943                CALL ctl_stop('Error in vwdta',' routine obcdta') 
    944             ENDIF 
    945  
    946  
    947             IF ( lwp .AND.  ( kt == nit000 .OR. nprint /= 0 )  ) THEN 
    948                WRITE(numout,*) 
    949                WRITE(numout,*) ' Read West OBC data records ', ntobc_x 
    950                ikprint = jpj/20 +1 
    951                WRITE(numout,*) ' Temperature  record 1 - printout every 3 level' 
    952                CALL prihre( twdta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    953                WRITE(numout,*) 
    954                WRITE(numout,*) ' Salinity  record 1 - printout every 3 level' 
    955                CALL prihre( swdta(:,:,nt_x),jpj,jpk, 1, jpj, ikprint,   jpk, 1, -3, 1., numout ) 
    956                WRITE(numout,*) 
    957                WRITE(numout,*) ' Normal velocity U  record 1  - printout every 3 level' 
    958                CALL prihre( uwdta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    959                WRITE(numout,*) 
    960                WRITE(numout,*) ' Tangential velocity V  record 1  - printout every 3 level' 
    961                CALL prihre( vwdta(:,:,nt_x), jpj, jpk, 1, jpj, ikprint, jpk, 1, -3, 1., numout ) 
    962             ENDIF 
    963          END IF 
    964       ENDIF 
    965 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    966       IF( lp_obc_north) THEN 
    967          IF(ln_obc_clim) THEN   ! revert to old convention for climatological OBC forcing 
    968             cl_obc_nTS='obcnorth_TS.nc' 
    969             cl_obc_nU ='obcnorth_U.nc' 
    970             cl_obc_nV ='obcnorth_V.nc' 
    971          ELSE                   ! convention for climatological OBC 
    972             WRITE(cl_obc_nTS ,'("obc_north_TS_y" ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    973             WRITE(cl_obc_nV  ,'("obc_north_V_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    974             WRITE(cl_obc_nU  ,'("obc_north_U_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    975          ENDIF 
    976          istart(:)=(/nin0+nimpp-1,1/) ; icount(:)=(/nin1-nin0 +1,jpk/) 
    977          IF (lwp) WRITE(numout,*) 'read data in :', TRIM(cl_obc_nTS) 
    978          IF ( nin1 >= nin0 ) THEN 
    979             CALL iom_open ( cl_obc_nTS , id_n ) 
    980             CALL iom_get ( id_n, jpdom_unknown, 'votemper', tndta(nin0:nin1,:,nt_x), & 
    981                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    982             CALL iom_get ( id_n, jpdom_unknown, 'vosaline', sndta(nin0:nin1,:,nt_x), & 
    983                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    984 # if defined key_dynspg_ts || defined key_dynspg_exp 
    985             CALL iom_get ( id_n, jpdom_unknown, 'vossurfh', sshndta(nin0:nin1,nt_x), & 
    986                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    987 # endif 
    988             CALL iom_close (id_n) 
    989             ! 
    990             CALL iom_open ( cl_obc_nU , id_n ) 
    991             CALL iom_get  ( id_n, jpdom_unknown, 'vozocrtx', undta(nin0:nin1,:,nt_x), & 
    992                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    993             CALL iom_close ( id_n ) 
    994             ! 
    995             CALL iom_open ( cl_obc_nV , id_n ) 
    996             CALL iom_get  ( id_n, jpdom_unknown, 'vomecrty', vndta(nin0:nin1,:,nt_x), & 
    997                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    998             CALL iom_close ( id_n ) 
    999  
    1000             ! mask the boundary values 
    1001             tndta(:,:,nt_x) = tndta(:,:,nt_x)*tnmsk(:,:) ;  sndta(:,:,nt_x) = sndta(:,:,nt_x)*tnmsk(:,:) 
    1002             undta(:,:,nt_x) = undta(:,:,nt_x)*unmsk(:,:) ;  vndta(:,:,nt_x) = vndta(:,:,nt_x)*vnmsk(:,:) 
    1003  
    1004             ! check any outliers 
    1005             zmin=MINVAL( sndta(:,:,nt_x), mask=ltnmsk ) ; zmax=MAXVAL(sndta(:,:,nt_x), mask=ltnmsk) 
    1006             IF (  zmin < 5 .OR. zmax > 50)   THEN 
    1007                CALL ctl_stop('Error in sndta',' routine obcdta') 
    1008             ENDIF 
    1009             zmin=MINVAL( tndta(:,:,nt_x), mask=ltnmsk ) ; zmax=MAXVAL(tndta(:,:,nt_x), mask=ltnmsk) 
    1010             IF (  zmin < -10. .OR. zmax > 40)   THEN 
    1011                CALL ctl_stop('Error in tndta',' routine obcdta') 
    1012             ENDIF 
    1013             zmin=MINVAL( undta(:,:,nt_x), mask=lunmsk ) ; zmax=MAXVAL(undta(:,:,nt_x), mask=lunmsk) 
    1014             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    1015                CALL ctl_stop('Error in undta',' routine obcdta') 
    1016             ENDIF 
    1017             zmin=MINVAL( vndta(:,:,nt_x), mask=lvnmsk ) ; zmax=MAXVAL(vndta(:,:,nt_x), mask=lvnmsk) 
    1018             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    1019                CALL ctl_stop('Error in vndta',' routine obcdta') 
    1020             ENDIF 
    1021  
    1022             IF ( lwp .AND.  ( kt == nit000 .OR. nprint /= 0 )  ) THEN 
    1023                WRITE(numout,*) 
    1024                WRITE(numout,*) ' Read North OBC data records ', ntobc_x 
    1025                ikprint = jpi/20 +1 
    1026                WRITE(numout,*) ' Temperature  record 1 - printout every 3 level' 
    1027                CALL prihre( tndta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1028                WRITE(numout,*) 
    1029                WRITE(numout,*) ' Salinity  record 1 - printout every 3 level' 
    1030                CALL prihre( sndta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1031                WRITE(numout,*) 
    1032                WRITE(numout,*) ' Normal velocity V  record 1  - printout every 3 level' 
    1033                CALL prihre( vndta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1034                WRITE(numout,*) 
    1035                WRITE(numout,*) ' Tangential  velocity U  record 1  - printout every 3 level' 
    1036                CALL prihre( undta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1037             ENDIF 
    1038          ENDIF 
    1039       ENDIF 
    1040 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    1041       IF( lp_obc_south) THEN  
    1042          IF(ln_obc_clim) THEN   ! revert to old convention for climatological OBC forcing 
    1043             cl_obc_sTS='obcsouth_TS.nc' 
    1044             cl_obc_sU ='obcsouth_U.nc' 
    1045             cl_obc_sV ='obcsouth_V.nc' 
    1046          ELSE                    ! convention for climatological OBC 
    1047             WRITE(cl_obc_sTS ,'("obc_south_TS_y" ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    1048             WRITE(cl_obc_sV  ,'("obc_south_V_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    1049             WRITE(cl_obc_sU  ,'("obc_south_U_y"  ,i4.4,"m",i2.2,".nc")' ) iyy,imm 
    1050          ENDIF 
    1051          istart(:)=(/nis0+nimpp-1,1/) ; icount(:)=(/nis1-nis0 +1,jpk/) 
    1052          IF (lwp) WRITE(numout,*) 'read data in :', TRIM(cl_obc_sTS) 
    1053          IF ( nis1 >= nis0 ) THEN  
    1054             CALL iom_open ( cl_obc_sTS , id_s ) 
    1055             CALL iom_get ( id_s, jpdom_unknown, 'votemper', tsdta(nis0:nis1,:,nt_x), & 
    1056                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    1057             CALL iom_get ( id_s, jpdom_unknown, 'vosaline', ssdta(nis0:nis1,:,nt_x), & 
    1058                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    1059 # if defined key_dynspg_ts || defined key_dynspg_exp 
    1060             CALL iom_get ( id_s, jpdom_unknown, 'vossurfh', sshsdta(nis0:nis1,nt_x), & 
    1061                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    1062 # endif 
    1063             CALL iom_close (id_s) 
    1064             ! 
    1065             CALL iom_open ( cl_obc_sU , id_s ) 
    1066             CALL iom_get  ( id_s, jpdom_unknown, 'vozocrtx', usdta(nis0:nis1,:,nt_x), & 
    1067                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    1068             CALL iom_close ( id_s ) 
    1069             ! 
    1070             CALL iom_open ( cl_obc_sV , id_s ) 
    1071             CALL iom_get  ( id_s, jpdom_unknown, 'vomecrty', vsdta(nis0:nis1,:,nt_x), & 
    1072                &               ktime=ntobc_x , kstart=istart, kcount= icount ) 
    1073             CALL iom_close ( id_s ) 
    1074  
    1075             ! mask the boundary values 
    1076             tsdta(:,:,nt_x) = tsdta(:,:,nt_x)*tsmsk(:,:) ;  ssdta(:,:,nt_x) = ssdta(:,:,nt_x)*tsmsk(:,:) 
    1077             usdta(:,:,nt_x) = usdta(:,:,nt_x)*usmsk(:,:) ;  vsdta(:,:,nt_x) = vsdta(:,:,nt_x)*vsmsk(:,:) 
    1078  
    1079             ! check any outliers 
    1080             zmin=MINVAL( ssdta(:,:,nt_x), mask=ltsmsk ) ; zmax=MAXVAL(ssdta(:,:,nt_x), mask=ltsmsk) 
    1081             IF (  zmin < 5 .OR. zmax > 50)   THEN 
    1082                CALL ctl_stop('Error in ssdta',' routine obcdta') 
    1083             ENDIF 
    1084             zmin=MINVAL( tsdta(:,:,nt_x), mask=ltsmsk ) ; zmax=MAXVAL(tsdta(:,:,nt_x), mask=ltsmsk) 
    1085             IF (  zmin < -10. .OR. zmax > 40)   THEN 
    1086                CALL ctl_stop('Error in tsdta',' routine obcdta') 
    1087             ENDIF 
    1088             zmin=MINVAL( usdta(:,:,nt_x), mask=lusmsk ) ; zmax=MAXVAL(usdta(:,:,nt_x), mask=lusmsk) 
    1089             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    1090                CALL ctl_stop('Error in usdta',' routine obcdta') 
    1091             ENDIF 
    1092             zmin=MINVAL( vsdta(:,:,nt_x), mask=lvsmsk ) ; zmax=MAXVAL(vsdta(:,:,nt_x), mask=lvsmsk) 
    1093             IF (  zmin < -5. .OR. zmax > 5.)   THEN 
    1094                CALL ctl_stop('Error in vsdta',' routine obcdta') 
    1095             ENDIF 
    1096  
    1097             IF ( lwp .AND.  ( kt == nit000 .OR. nprint /= 0 )  ) THEN 
    1098                WRITE(numout,*) 
    1099                WRITE(numout,*) ' Read South OBC data records ', ntobc_x 
    1100                ikprint = jpi/20 +1 
    1101                WRITE(numout,*) ' Temperature  record 1 - printout every 3 level' 
    1102                CALL prihre( tsdta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1103                WRITE(numout,*) 
    1104                WRITE(numout,*) ' Salinity  record 1 - printout every 3 level' 
    1105                CALL prihre( ssdta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1106                WRITE(numout,*) 
    1107                WRITE(numout,*) ' Normal velocity V  record 1  - printout every 3 level' 
    1108                CALL prihre( vsdta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1109                WRITE(numout,*) 
    1110                WRITE(numout,*) ' Tangential velocity U  record 1  - printout every 3 level' 
    1111                CALL prihre( usdta(:,:,nt_x), jpi, jpk, 1, jpi, ikprint, jpk, 1, -3, 1., numout ) 
    1112             ENDIF 
    1113          ENDIF 
    1114       ENDIF 
    1115  
    1116 # if defined key_dynspg_ts || defined key_dynspg_exp 
    1117       CALL obc_depth_average(nt_x)   ! computation of depth-averaged velocity 
    1118 # endif 
    1119  
    1120 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    1121    END SUBROUTINE obc_read 
    1122  
    1123  
    1124    INTEGER FUNCTION nrecbef() 
    1125       !!----------------------------------------------------------------------- 
    1126       !!                     ***    FUNCTION nrecbef   *** 
    1127       !! 
    1128       !!  Purpose : - provide the before record number in files, with respect to zjcnes 
    1129       !! 
    1130       !!    History : 2008-04 : ( J.M. Molines ) Original code 
    1131       !!----------------------------------------------------------------------- 
    1132  
    1133       INTEGER :: it , idum 
    1134  
    1135       idum = itobc 
    1136       DO it =1, itobc 
    1137          IF ( ztcobc(it) > zjcnes ) THEN ;  idum = it - 1 ; EXIT ;  ENDIF 
    1138          ENDDO 
    1139          ! idum can be 0 (climato, before first record) 
    1140          IF ( idum == 0 ) THEN 
    1141             IF ( ln_obc_clim ) THEN 
    1142                idum = itobc 
    1143             ELSE 
    1144                ctmp1='obc_dta: find ntobc == 0 for  non climatological file ' 
    1145                ctmp2='consider adding a first record in your data file ' 
    1146                CALL ctl_stop(ctmp1, ctmp2) 
    1147             ENDIF 
    1148          ENDIF 
    1149          ! idum can be itobc ( zjcnes > ztcobc (itobc) ) 
    1150          !  This is not a problem ... 
    1151          nrecbef = idum 
    1152  
    1153       END FUNCTION nrecbef 
    1154  
    1155  
    1156       SUBROUTINE obc_depth_average(nt_x) 
    1157          !!----------------------------------------------------------------------- 
    1158          !!                     ***    ROUTINE obc_depth_average   *** 
    1159          !! 
    1160          !!  Purpose : - compute the depth-averaged velocity from depth-dependent OBC frames 
    1161          !! 
    1162          !!    History : 2009-01 : ( Fred Dupont ) Original code 
    1163          !!----------------------------------------------------------------------- 
    1164  
    1165          ! * Arguments 
    1166          INTEGER, INTENT( in ) :: nt_x 
    1167  
    1168          ! * Local variables 
    1169          INTEGER :: ji, jj, jk 
    1170  
    1171  
    1172          IF( lp_obc_east ) THEN 
    1173             ! initialisation to zero 
    1174             ubtedta(:,nt_x) = 0.e0 
    1175             vbtedta(:,nt_x) = 0.e0 
    1176             DO ji = nie0, nie1 
    1177                DO jj = 1, jpj 
    1178                   DO jk = 1, jpkm1 
    1179                      ubtedta(jj,nt_x) = ubtedta(jj,nt_x) + uedta(jj,jk,nt_x)*fse3u(ji,jj,jk) 
    1180                      vbtedta(jj,nt_x) = vbtedta(jj,nt_x) + vedta(jj,jk,nt_x)*fse3v(ji+1,jj,jk) 
    1181                   END DO 
    1182                END DO 
    1183             END DO 
    1184          ENDIF 
    1185  
    1186          IF( lp_obc_west) THEN 
    1187             ! initialisation to zero 
    1188             ubtwdta(:,nt_x) = 0.e0 
    1189             vbtwdta(:,nt_x) = 0.e0 
    1190             DO ji = niw0, niw1 
    1191                DO jj = 1, jpj 
    1192                   DO jk = 1, jpkm1 
    1193                      ubtwdta(jj,nt_x) = ubtwdta(jj,nt_x) + uwdta(jj,jk,nt_x)*fse3u(ji,jj,jk) 
    1194                      vbtwdta(jj,nt_x) = vbtwdta(jj,nt_x) + vwdta(jj,jk,nt_x)*fse3v(ji,jj,jk) 
    1195                   END DO 
    1196                END DO 
    1197             END DO 
    1198          ENDIF 
    1199  
    1200          IF( lp_obc_north) THEN 
    1201             ! initialisation to zero 
    1202             ubtndta(:,nt_x) = 0.e0 
    1203             vbtndta(:,nt_x) = 0.e0 
    1204             DO jj = njn0, njn1 
    1205                DO ji = 1, jpi 
    1206                   DO jk = 1, jpkm1 
    1207                      ubtndta(ji,nt_x) = ubtndta(ji,nt_x) + undta(ji,jk,nt_x)*fse3u(ji,jj+1,jk) 
    1208                      vbtndta(ji,nt_x) = vbtndta(ji,nt_x) + vndta(ji,jk,nt_x)*fse3v(ji,jj,jk) 
    1209                   END DO 
    1210                END DO 
    1211             END DO 
    1212          ENDIF 
    1213  
    1214          IF( lp_obc_south) THEN 
    1215             ! initialisation to zero 
    1216             ubtsdta(:,nt_x) = 0.e0 
    1217             vbtsdta(:,nt_x) = 0.e0 
    1218             DO jj = njs0, njs1 
    1219                DO ji = nis0, nis1 
    1220                   DO jk = 1, jpkm1 
    1221                      ubtsdta(ji,nt_x) = ubtsdta(ji,nt_x) + usdta(ji,jk,nt_x)*fse3u(ji,jj,jk) 
    1222                      vbtsdta(ji,nt_x) = vbtsdta(ji,nt_x) + vsdta(ji,jk,nt_x)*fse3v(ji,jj,jk) 
    1223                   END DO 
    1224                END DO 
    1225             END DO 
    1226          ENDIF 
    1227  
    1228       END SUBROUTINE obc_depth_average 
    1229  
    1230 #else 
    1231       !!------------------------------------------------------------------------------ 
    1232       !!   default option:           Dummy module          NO Open Boundary Conditions 
    1233       !!------------------------------------------------------------------------------ 
    1234    CONTAINS 
    1235       SUBROUTINE obc_dta( kt )             ! Dummy routine 
    1236          INTEGER, INTENT (in) :: kt 
    1237          WRITE(*,*) 'obc_dta: You should not have seen this print! error?', kt 
    1238       END SUBROUTINE obc_dta 
    1239 #endif 
     482   SUBROUTINE obc_dta_init()                  ! Empty routine 
     483      WRITE(*,*) 'obc_dta_init: You should not have seen this print! error?' 
     484   END SUBROUTINE obc_dta_init 
     485#endif 
     486 
    1240487   !!============================================================================== 
    1241    END MODULE obcdta 
     488END MODULE obcdta 
Note: See TracChangeset for help on using the changeset viewer.