*IF DEF,CONTROL,AND,DEF,OCEAN                                              BOUNDVO1.2      
C ******************************COPYRIGHT******************************    GTS2F400.613    
C (c) CROWN COPYRIGHT 1995, METEOROLOGICAL OFFICE, All Rights Reserved.    GTS2F400.614    
C                                                                          GTS2F400.615    
C Use, duplication or disclosure of this code is subject to the            GTS2F400.616    
C restrictions as set forth in the contract.                               GTS2F400.617    
C                                                                          GTS2F400.618    
C                Meteorological Office                                     GTS2F400.619    
C                London Road                                               GTS2F400.620    
C                BRACKNELL                                                 GTS2F400.621    
C                Berkshire UK                                              GTS2F400.622    
C                RG12 2SZ                                                  GTS2F400.623    
C                                                                          GTS2F400.624    
C If no contract has been raised with this copy of the code, the use,      GTS2F400.625    
C duplication or disclosure of it is strictly prohibited.  Permission      GTS2F400.626    
C to do so must first be obtained in writing from the Head of Numerical    GTS2F400.627    
C Modelling at the above address.                                          GTS2F400.628    
C ******************************COPYRIGHT******************************    GTS2F400.629    
C                                                                          GTS2F400.630    
CLL -------------- SUBROUTINE BOUNDVOL ---------------------------------   BOUNDVO1.3      
CLL                                                                        BOUNDVO1.4      
CLL Purpose: New version of BOUNDVOL at vn4.5 onwards.                     OSI1F405.124    
CLL          Main subroutine for open ocean boundary conditions.           OSI1F405.125    
CLL          Firstly calculates the present boundary values then           OSI1F405.126    
CLL          updates the model values with the present boundary            OSI1F405.127    
CLL          condition using one of three schemes (Gill's, FRS or          OSI1F405.128    
CLL          Steven's) and for any lateral boundaries.                     OSI1F405.129    
CLL                                                                        OSI1F405.130    
CLL Author:  C.Jones                                                       OSI1F405.131    
CLL                                                                        BOUNDVO1.14     
CLL  Model            Modification history from model version 3.0:         BOUNDVO1.15     
CLL version  Date                                                          BOUNDVO1.16     
CLL  3.2  07/06/93  Dynamic allocation changes - R.T.H.Barnes.             @DYALLOC.688    
CLL 3.4  16/6/94 : Change CHARACTER*(*) to CHARACTER*(80) N.Farnon         ANF0F304.7      
CLL  4.5  01/09/97 Rewritten routine for more flexibility.                 OSI1F405.132    
CLL                C. G. Jones                                             OSI1F405.133    
CLL                                                                        BOUNDVO1.17     
CLL Logical components covered: C72 (part)                                 BOUNDVO1.18     
CLL                                                                        BOUNDVO1.19     
CLL Project task: C7                                                       BOUNDVO1.20     
CLL                                                                        BOUNDVO1.21     
CLL External documentation:                                                BOUNDVO1.22     
CLL                                                                        BOUNDVO1.23     
CLLEND                                                                     BOUNDVO1.24     
c                                                                          OSI1F405.134    

      subroutine boundvol(                                                  1,8OSI1F405.135    
                                                                           OSI1F405.136    
*CALL ARGSIZE                                                              OSI1F405.137    
*CALL ARGOINDX                                                             OSI1F405.138    
*CALL ARGD1                                                                OSI1F405.139    
*CALL ARGDUMO     ! just need fkmp from here                               OSI1F405.140    
*CALL ARGPTRO                                                              OSI1F405.141    
*CALL ARGBND                                                               OSI1F405.142    
*CALL ARGOCONE                                                             OSI1F405.143    
*CALL ARGOCFLD    ! just need fkmq from here                               OSI1F405.144    
*CALL ARGOCFLW    ! for isz and ise                                        OSI1F405.145    
     &     icode,cmessage)                                                 OSI1F405.146    
                                                                           OSI1F405.147    
      implicit none                                                        OSI1F405.148    
                                                                           OSI1F405.149    
*CALL TYPSIZE                                                              OSI1F405.150    
*CALL TYPOINDX                                                             OSI1F405.151    
*CALL TYPD1                                                                OSI1F405.152    
*CALL TYPDUMO    ! needed for compression arrays                           OSI1F405.153    
*CALL TYPPTRO                                                              OSI1F405.154    
*CALL TYPBND                                                               OSI1F405.155    
*CALL OARRYSIZ                                                             OSI1F405.156    
*CALL TYPOCFLD                                                             OSI1F405.157    
*CALL TYPOCFLW   ! for isz and ise                                         OSI1F405.158    
*CALL TYPOCONE                                                             OSI1F405.159    
*CALL CSMID      ! for o_im                                                OSI1F405.160    
*CALL UMSCALAR                                                             OSI1F405.161    
*CALL CSUBMMAX   ! for internal_id_max                                     OSI1F405.162    
*CALL CMAXSIZE                                                             OSI1F405.163    
*CALL CTIME                                                                OSI1F405.164    
*CALL CNTLOCN                                                              OSI1F405.165    
                                                                           OSI1F405.166    
      integer icode              ! Return code                             OSI1F405.167    
      character*(256) cmessage   ! Error message                           OSI1F405.168    
                                                                           OSI1F405.169    
*CALL PARPARM                                                              OSI1F405.170    
*IF -DEF,MPP                                                               OSI1F405.171    
                                                                           OSI1F405.172    
      INTEGER                                                              OSI1F405.173    
     &   fld_type_p           ! indicates a grid on P points               OSI1F405.174    
     &,  fld_type_u           ! indicates a grid on U points               OSI1F405.175    
     &,  fld_type_unknown     ! indicates a non-standard grid.             OSI1F405.176    
      PARAMETER (                                                          OSI1F405.177    
     &   fld_type_p=1                                                      OSI1F405.178    
     &,  fld_type_u=2                                                      OSI1F405.179    
     &,  fld_type_unknown=-1)                                              OSI1F405.180    
*ENDIF                                                                     OSI1F405.181    
                                                                           OSI1F405.182    
C Local arrays and scalars                                                 OSI1F405.183    
                                                                           OSI1F405.184    
      real DTEMP_BOUND(lenrimdata_o)  ! temporary array with length        OSI1F405.185    
                                      ! for a single timestep              OSI1F405.186    
C local scalars                                                            OSI1F405.187    
      integer i               ! loop counter                               OSI1F405.188    
      integer k               ! loop counter                               OSI1F405.189    
      integer f_type          ! local indicator of field type              OSI1F405.190    
      integer land_val        ! value to set in field at land points       OSI1F405.191    
                                                                           OSI1F405.192    
      real dummy              ! argument in subroutine call                OSI1F405.193    
                              ! which will not be used                     OSI1F405.194    
      logical l_apply_lsm     ! T => apply lsm at boundaries               OSI1F405.195    
                                                                           OSI1F405.196    
CL 1.0 Calculate the boundary condition valid for the present timestep     OSI1F405.197    
CL     from the previous and next timestep information stored in the       OSI1F405.198    
CL     D1 array.  Write this into a local temporary array (DTEMP_BOUND).   OSI1F405.199    
CL     The timestep is now valid at the forward step; we update fields     OSI1F405.200    
CL     at the timestep before.                                             OSI1F405.201    
                                                                           OSI1F405.202    
      do i=0,LENRIMDATA_O-1                                                OSI1F405.203    
                                                                           OSI1F405.204    
            DTEMP_BOUND(i+1)=                                              OSI1F405.205    
     &   ( D1(joc_bounds_next + i) - D1(joc_bounds_prev + i) )             OSI1F405.206    
     & * (STEPim(o_im)-1-O_BDY_STEP_PREV )/REAL(RIM_STEPSO)                OSI1F405.207    
     & +   D1(joc_bounds_prev + i)                                         OSI1F405.208    
                                                                           OSI1F405.209    
      enddo                                                                OSI1F405.210    
                                                                           OSI1F405.211    
CL 2. Call the subroutine o_set_bound to update the tracers first if       OSI1F405.212    
CL     the tracers are to be updated.  Need to loop over the number of     OSI1F405.213    
CL     tracers(NT) and the number of levels.  Also include the levels      OSI1F405.214    
CL     dataset for tracers.                                                OSI1F405.215    
                                                                           OSI1F405.216    
      do i = 1,NT                                                          OSI1F405.217    
                                                                           OSI1F405.218    
        do k = 1,KM                                                        OSI1F405.219    
          if (l_obdy_tracer) then                                          OSI1F405.220    
                                                                           OSI1F405.221    
            f_type=fld_type_p                                              OSI1F405.222    
            land_val = 0.0                                                 OSI1F405.223    
            l_apply_lsm = .true.                                           OSI1F405.224    
                                                                           OSI1F405.225    
            call o_set_bound(imt,jmt,km,k,                                 OSI1F405.226    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.227    
     &           DTEMP_BOUND(joc_bdy_tracer(i) + (k-1)*LENRIMO),           OSI1F405.228    
     &           FKMP, DXT, DYT,                                           OSI1F405.229    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.230    
     &           lseg,isz,iez,                                             OSI1F405.231    
     &           D1(joc_tracer(i,1)+(k-1)*imt*jmt),                        OSI1F405.232    
     &           icode,cmessage)                                           OSI1F405.233    
                                                                           OSI1F405.234    
          endif                                                            OSI1F405.235    
        enddo                                                              OSI1F405.236    
      enddo                                                                OSI1F405.237    
                                                                           OSI1F405.238    
CL 3.0 Call the subroutine o_set_bound to update the velocities if they    OSI1F405.239    
CL     are to be updated.  Note velocity grids have one less row. Also     OSI1F405.240    
CL     include the levels dataset for velocities.                          OSI1F405.241    
                                                                           OSI1F405.242    
      do k = 1,KM                                                          OSI1F405.243    
        if (l_obdy_uv) then                                                OSI1F405.244    
                                                                           OSI1F405.245    
          f_type=fld_type_u                                                OSI1F405.246    
          land_val = 0.0                                                   OSI1F405.247    
          l_apply_lsm = .true.                                             OSI1F405.248    
                                                                           OSI1F405.249    
          call o_set_bound(imt,jmt,km,k,                                   OSI1F405.250    
     &           LENRIMO_U, RIMWIDTHO, RIMWEIGHTSO,                        OSI1F405.251    
     &           DTEMP_BOUND(joc_bdy_u + (k-1)*LENRIMO_U),                 OSI1F405.252    
     &           FKMQ, DXU, DYU,                                           OSI1F405.253    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.254    
     &           lseg,isz,iez,                                             OSI1F405.255    
     &           D1(joc_u(1)+(k-1)*imt*jmt),                               OSI1F405.256    
     &           icode,cmessage)                                           OSI1F405.257    
                                                                           OSI1F405.258    
          call o_set_bound(imt,jmt,km,k,                                   OSI1F405.259    
     &           LENRIMO_U, RIMWIDTHO, RIMWEIGHTSO,                        OSI1F405.260    
     &           DTEMP_BOUND(joc_bdy_v + (k-1) * LENRIMO_U),               OSI1F405.261    
     &           FKMQ, DXU, DYU,                                           OSI1F405.262    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.263    
     &           lseg,isz,iez,                                             OSI1F405.264    
     &           D1(joc_v(1)+(k-1)*imt*jmt),                               OSI1F405.265    
     &           icode,cmessage)                                           OSI1F405.266    
                                                                           OSI1F405.267    
        endif                                                              OSI1F405.268    
      enddo                                                                OSI1F405.269    
                                                                           OSI1F405.270    
CL 4.0 Do the same for the streamfunction and the streamfunction           OSI1F405.271    
CL     tendency and the source function for the streamfn (ZTD)             OSI1F405.272    
CL                                                                         OSI1F405.273    
                                                                           OSI1F405.274    
      if (l_obdy_stream) then                                              OSI1F405.275    
                                                                           OSI1F405.276    
        f_type=fld_type_p                                                  OSI1F405.277    
        land_val=0.0                                                       OSI1F405.278    
        l_apply_lsm = .false.                                              OSI1F405.279    
                                                                           OSI1F405.280    
        call o_set_bound(imt,jmt,1,1,                                      OSI1F405.281    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.282    
     &           DTEMP_BOUND(joc_bdy_stream),                              OSI1F405.283    
     &           FKMP, DXT, DYT,                                           OSI1F405.284    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.285    
     &           lseg,isz,iez,                                             OSI1F405.286    
     &           D1(joc_stream(1)),                                        OSI1F405.287    
     &           icode,cmessage)                                           OSI1F405.288    
                                                                           OSI1F405.289    
        call o_set_bound(imt,jmt,1,1,                                      OSI1F405.290    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.291    
     &           DTEMP_BOUND(joc_bdy_tend),                                OSI1F405.292    
     &           FKMP, DXT, DYT,                                           OSI1F405.293    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.294    
     &           lseg,isz,iez,                                             OSI1F405.295    
     &           D1(joc_tend(1)),                                          OSI1F405.296    
     &           icode,cmessage)                                           OSI1F405.297    
                                                                           OSI1F405.298    
!        f_type=fld_type_i                                                 OSI1F405.299    
                                                                           OSI1F405.300    
!        call o_set_bound(imt,jmt,1,1,                                     OSI1F405.301    
!     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                         OSI1F405.302    
!     &           DTEMP_BOUND(joc_bdy_ztd),                                OSI1F405.303    
!     &           FKMP, DXT, DYT,                                          OSI1F405.304    
!     &           f_type, land_val, l_apply_lsm,                           OSI1F405.305    
!     &           lseg,isz,iez,                                            OSI1F405.306    
!     &           D1(joc_ztd),                                             OSI1F405.307    
!     &           icode,cmessage)                                          OSI1F405.308    
                                                                           OSI1F405.309    
      end if  ! l_obdy_stream                                              OSI1F405.310    
                                                                           OSI1F405.311    
CL 5.0 Update sea-ice fields; use tracer land-sea mask                     OSI1F405.312    
                                                                           OSI1F405.313    
      if (l_obdy_ice) then                                                 OSI1F405.314    
                                                                           OSI1F405.315    
        f_type=fld_type_p                                                  OSI1F405.316    
        land_val=0.0                                                       OSI1F405.317    
        l_apply_lsm = .true.    ! ?????                                    OSI1F405.318    
                                                                           OSI1F405.319    
        call o_set_bound(imt,jmt,1,1,                                      OSI1F405.320    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.321    
     &           DTEMP_BOUND(joc_bdy_snow),                                OSI1F405.322    
     &           FKMP, DXT, DYT,                                           OSI1F405.323    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.324    
     &           lseg,isz,iez,                                             OSI1F405.325    
     &           D1(joc_snow),                                             OSI1F405.326    
     &           icode,cmessage)                                           OSI1F405.327    
                                                                           OSI1F405.328    
        call o_set_bound(imt,jmt,1,1,                                      OSI1F405.329    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.330    
     &           DTEMP_BOUND(joc_bdy_aice),                                OSI1F405.331    
     &           FKMP, DXT, DYT,                                           OSI1F405.332    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.333    
     &           lseg,isz,iez,                                             OSI1F405.334    
     &           D1(joc_icecon),                                           OSI1F405.335    
     &           icode,cmessage)                                           OSI1F405.336    
                                                                           OSI1F405.337    
        call o_set_bound(imt,jmt,1,1,                                      OSI1F405.338    
     &           LENRIMO, RIMWIDTHO, RIMWEIGHTSO,                          OSI1F405.339    
     &           DTEMP_BOUND(joc_bdy_hice),                                OSI1F405.340    
     &           FKMP, DXT, DYT,                                           OSI1F405.341    
     &           f_type, land_val, l_apply_lsm,                            OSI1F405.342    
     &           lseg,isz,iez,                                             OSI1F405.343    
     &           D1(joc_icedep),                                           OSI1F405.344    
     &           icode,cmessage)                                           OSI1F405.345    
                                                                           OSI1F405.346    
       end if ! l_obdy_ice                                                 OSI1F405.347    
                                                                           OSI1F405.348    
       return                                                              OSI1F405.349    
                                                                           OSI1F405.350    
       end                                                                 OSI1F405.351    
*ENDIF                                                                     BOUNDVO1.55