Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:41:06 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
8e4c181d69 Jean*0001 #     include "GAD_OPTIONS.h"
                0002 
                0003       SUBROUTINE GAD_PQM_HAT_X(bi,bj,kk,iy,
                0004      &           method,mask,fbar,edge,
                0005      &           ohat,fhat,myThid)
                0006 C     |================================================================|
                0007 C     | PQM_HAT_X: reconstruct grid-cell PQM polynomials.              |
                0008 C     |================================================================|
                0009 
                0010           implicit none
                0011 
                0012 C     =============================================== global variables
                0013 #         include "SIZE.h"
                0014 #         include "GRID.h"
                0015 #         include "GAD.h"
                0016 
                0017 C     ====================================================== arguments
                0018 C       bi,bj     :: tile indices.
                0019 C       kk        :: r-index.
                0020 C       iy        :: y-index.
                0021 C       method    :: advection scheme.
                0022 C       mask      :: row of cell-wise mask values.
                0023 C       fbar      :: row of cell-wise values.
                0024 C       edge      :: row of edge-wise values/slopes.
                0025 C                    - EDGE(1,:) = VALUE.
                0026 C                    - EDGE(2,:) = DF/DX.
                0027 C       ohat      :: row of oscl. coeff.
                0028 C                    - OHAT(1,:) = D^1F/DS^1.
                0029 C                    - OHAT(2,:) = D^2F/DS^2.
                0030 C       fhat      :: row of poly. coeff.
                0031 C                    - FHAT(:,I) = PQM coeff.
                0032 C       myThid    :: thread number.
                0033 C     ================================================================
                0034           integer bi,bj,kk,iy
                0035           integer method
                0036           _RL mask(1-OLx:sNx+OLx)
                0037           _RL fbar(1-OLx:sNx+OLx)
                0038           _RL edge(1:2,
                0039      &             1-OLx:sNx+OLx)
                0040           _RL ohat(1:2,
                0041      &             1-OLx:sNx+OLx)
                0042           _RL fhat(1:5,
                0043      &             1-OLx:sNx+OLx)
                0044           integer myThid
                0045 
                0046 C     ====================================================== variables
                0047 C       ii,ix     :: local x-indexing.
                0048 C       ff00      :: centre-biased cell value.
                0049 C       ffll,ffrr :: left-, and right-biased cell values.
                0050 C       xhat      :: local coord. scaling.
                0051 C       fell,ferr :: left-, and right-biased edge values.
                0052 C       dell,derr :: left-, and right-biased edge slopes.
                0053 C       dfds      :: linear slope estimates.
                0054 C       uhat      :: "NULL" limited poly. coeff.
                0055 C       lhat      :: "MONO" limited poly. coeff.
                0056 C       scal      :: "WENO" weights.
                0057 C       fmag,fdel :: local perturbation indicators.
                0058 C     ================================================================
                0059           integer ii,ix
                0060           _RL ff00
                0061           _RL ffll,ffrr
                0062           _RL xhat
                0063           _RL fell,ferr
                0064           _RL dell,derr
                0065           _RL dfds(-1:+1)
                0066           _RL uhat(+1:+5)
                0067           _RL lhat(+1:+5)
                0068           _RL scal(+1:+2)
                0069           _RL fmag,fdel
                0070           integer  mono
                0071 
                0072           do  ix = 1-OLx+3, sNx+OLx-3
                0073 
                0074               if (mask(ix) .gt. 0. _d 0) then
                0075 
                0076 C     =============================== scale to local grid-cell co-ords
                0077               xhat = dxF(ix,iy,bi,bj) * 0.5 _d 0
                0078 
                0079 C     =============================== assemble cell mean + edge values
                0080               ff00 = fbar(ix+0)
                0081               ffll = ff00
                0082      &          + mask(ix-1)*(fbar(ix-1)-ff00)
                0083               ffrr = ff00
                0084      &          + mask(ix+1)*(fbar(ix+1)-ff00)
                0085 
                0086               fell = edge(+1,ix-0)
                0087               ferr = edge(+1,ix+1)
                0088 
                0089               dell = edge(+2,ix-0)
                0090               derr = edge(+2,ix+1)
                0091 
                0092               dell = dell * xhat
                0093               derr = derr * xhat
                0094 
                0095 c             select case(method)
                0096 c             case(ENUM_PQM_NULL_LIMIT)
                0097               if ( method.eq.ENUM_PQM_NULL_LIMIT ) then
                0098 C     =============================== "NULL" limited grid-cell profile
                0099               CALL GAD_PQM_FUN_NULL ( ff00,
                0100      &             fell,ferr,dell,derr,lhat,mono)
                0101 
                0102 c             case(ENUM_PQM_MONO_LIMIT)
                0103               elseif ( method.eq.ENUM_PQM_MONO_LIMIT ) then
                0104 C     =============================== "MONO" limited grid-cell profile
                0105               CALL GAD_PLM_FUN_U(ffll,ff00,ffrr,dfds)
                0106 
                0107               CALL GAD_PQM_FUN_MONO ( ff00,ffll,ffrr,
                0108      &             fell,ferr,dell,derr,dfds,lhat,
                0109      &             mono)
                0110 
                0111 c             case(ENUM_PQM_WENO_LIMIT)
                0112               elseif ( method.eq.ENUM_PQM_WENO_LIMIT ) then
                0113 C     =============================== "WENO" limited grid-cell profile
                0114               CALL GAD_PLM_FUN_U(ffll,ff00,ffrr,dfds)
                0115 
                0116               CALL GAD_PQM_FUN_NULL ( ff00,
                0117      &             fell,ferr,dell,derr,uhat,mono)
                0118 
                0119               CALL GAD_PQM_FUN_MONO ( ff00,ffll,ffrr,
                0120      &             fell,ferr,dell,derr,dfds,lhat,
                0121      &             mono)
                0122 
                0123               if ( mono .gt. 0) then
                0124 
                0125 C     =============================== only apply WENO if it is worth it
                0126               fdel = abs(ffrr-ff00)+abs(ff00-ffll)
                0127               fmag = abs(ffll)+abs(ff00)+abs(ffrr)
                0128 
                0129               if (fdel .gt. 1. _d -6 * fmag) then
                0130 
                0131 C     =============================== calc. WENO oscillation weighting
                0132                   CALL GAD_OSC_MUL_X(ix,+2,mask,
                0133      &                 ohat,scal)
                0134 
                0135                   do  ii = +1, +5
                0136 C     =============================== blend limited/un-limited profile
                0137                   lhat(ii) = scal(1) * uhat(ii)
                0138      &                     + scal(2) * lhat(ii)
                0139                   end do
                0140 
                0141               end if
                0142 
                0143               end if
                0144 
                0145 c             end select
                0146               endif
                0147 
                0148               do  ii = +1, +5
                0149 C     =============================== copy polynomial onto output data
                0150                   fhat(ii,ix) = lhat(ii)
                0151               end do
                0152 
                0153               else
                0154 
                0155               do  ii = +1, +5
                0156                   fhat(ii,ix) = 0.0 _d 0
                0157               end do
                0158 
                0159               end if
                0160 
                0161           end do
                0162 
                0163           return
                0164 
                0165 c     end subroutine GAD_PQM_HAT_X
                0166       end