/[MITgcm]/MITgcm/pkg/kpp/kpp_routines.F
ViewVC logotype

Diff of /MITgcm/pkg/kpp/kpp_routines.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.27 by dimitri, Mon Apr 23 21:09:19 2007 UTC revision 1.32 by heimbach, Mon Jun 4 18:47:35 2007 UTC
# Line 19  C--  o STATEKPP    - Compute buoyancy-re Line 19  C--  o STATEKPP    - Compute buoyancy-re
19  c***********************************************************************  c***********************************************************************
20    
21        SUBROUTINE KPPMIX (        SUBROUTINE KPPMIX (
22       I       mytime, mythid       I       kmtj, shsq, dvsq, ustar, msk
      I     , kmtj, shsq, dvsq, ustar  
23       I     , bo, bosol, dbloc, Ritop, coriol       I     , bo, bosol, dbloc, Ritop, coriol
24       I     , diffusKzS, diffusKzT       I     , diffusKzS, diffusKzT
25       I     , ikppkey       I     , ikppkey
26       O     , diffus       O     , diffus
27       U     , ghat       U     , ghat
28       O     , hbl )       O     , hbl
29         I     , myTime, myIter, myThid )
30    
31  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
32  c  c
# Line 50  c--------------------------------------- Line 50  c---------------------------------------
50  #include "KPP_PARAMS.h"  #include "KPP_PARAMS.h"
51    
52  c input  c input
53  c     myTime           - current time in simulation  c   myTime :: Current time in simulation
54  c     myThid           - thread number for this instance of the routine  c   myIter :: Current iteration number in simulation
55    c   myThid :: My Thread Id. number
56  c     kmtj   (imt)     - number of vertical layers on this row  c     kmtj   (imt)     - number of vertical layers on this row
57    c     msk    (imt)     - surface mask (=1 if water, =0 otherwise)
58  c     shsq   (imt,Nr)  - (local velocity shear)^2                     ((m/s)^2)  c     shsq   (imt,Nr)  - (local velocity shear)^2                     ((m/s)^2)
59  c     dvsq   (imt,Nr)  - (velocity shear re sfc)^2                    ((m/s)^2)  c     dvsq   (imt,Nr)  - (velocity shear re sfc)^2                    ((m/s)^2)
60  c     ustar  (imt)     - surface friction velocity                        (m/s)  c     ustar  (imt)     - surface friction velocity                        (m/s)
# Line 70  c     note: there is a conversion from 2 Line 72  c     note: there is a conversion from 2
72  c           e.g., hbl(sNx,sNy) -> hbl(imt),  c           e.g., hbl(sNx,sNy) -> hbl(imt),
73  c           where hbl(i,j) -> hbl((j-1)*sNx+i)  c           where hbl(i,j) -> hbl((j-1)*sNx+i)
74    
75        _RL     mytime        _RL     myTime
76        integer mythid        integer myIter
77          integer myThid
78        integer kmtj (imt   )        integer kmtj (imt   )
79        _RL shsq     (imt,Nr)        _RL shsq     (imt,Nr)
80        _RL dvsq     (imt,Nr)        _RL dvsq     (imt,Nr)
# Line 81  c           where hbl(i,j) -> hbl((j-1)* Line 84  c           where hbl(i,j) -> hbl((j-1)*
84        _RL dbloc    (imt,Nr)        _RL dbloc    (imt,Nr)
85        _RL Ritop    (imt,Nr)        _RL Ritop    (imt,Nr)
86        _RL coriol   (imt   )        _RL coriol   (imt   )
87          _RS msk      (imt   )
88        _RL diffusKzS(imt,Nr)        _RL diffusKzS(imt,Nr)
89        _RL diffusKzT(imt,Nr)        _RL diffusKzT(imt,Nr)
90    
# Line 136  cph) Line 140  cph)
140       I       kmtj, shsq, dbloc, ghat       I       kmtj, shsq, dbloc, ghat
141       I     , diffusKzS, diffusKzT       I     , diffusKzS, diffusKzT
142       I     , ikppkey       I     , ikppkey
143       O     , diffus )       O     , diffus, myThid )
144    
145  cph(  cph(
146  cph these storings avoid recomp. of Ri_iwmix  cph these storings avoid recomp. of Ri_iwmix
# Line 167  c diagnose the new boundary layer depth Line 171  c diagnose the new boundary layer depth
171  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
172    
173        call bldepth (        call bldepth (
174       I       mytime, mythid       I       kmtj
      I     , kmtj  
175       I     , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol       I     , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol
176       I     , ikppkey       I     , ikppkey
177       O     , hbl, bfsfc, stable, casea, kbl, Rib, sigma       O     , hbl, bfsfc, stable, casea, kbl, Rib, sigma
178       &     )       I     , myTime, myIter, myThid )
179    
180  CADJ STORE hbl,bfsfc,stable,casea,kbl = comlev1_kpp, key = ikppkey  CADJ STORE hbl,bfsfc,stable,casea,kbl = comlev1_kpp, key = ikppkey
181    
# Line 183  c--------------------------------------- Line 186  c---------------------------------------
186        call blmix (        call blmix (
187       I       ustar, bfsfc, hbl, stable, casea, diffus, kbl       I       ustar, bfsfc, hbl, stable, casea, diffus, kbl
188       O     , dkm1, blmc, ghat, sigma, ikppkey       O     , dkm1, blmc, ghat, sigma, ikppkey
189       &     )       I     , myThid )
190  cph(  cph(
191  CADJ STORE dkm1,blmc,ghat = comlev1_kpp, key = ikppkey  CADJ STORE dkm1,blmc,ghat = comlev1_kpp, key = ikppkey
192  CADJ STORE hbl, kbl, diffus, casea = comlev1_kpp, key = ikppkey  CADJ STORE hbl, kbl, diffus, casea = comlev1_kpp, key = ikppkey
# Line 196  c--------------------------------------- Line 199  c---------------------------------------
199        call enhance (        call enhance (
200       I       dkm1, hbl, kbl, diffus, casea       I       dkm1, hbl, kbl, diffus, casea
201       U     , ghat       U     , ghat
202       O     , blmc )       O     , blmc
203         I     , myThid )
204    
205  cph(  cph(
206  cph avoids recomp. of enhance  cph avoids recomp. of enhance
# Line 212  c--------------------------------------- Line 216  c---------------------------------------
216        do k = 1, Nr        do k = 1, Nr
217           do i = 1, imt           do i = 1, imt
218              if (k .lt. kbl(i)) then              if (k .lt. kbl(i)) then
219    #ifdef ALLOW_SHELFICE
220    C     when there is shelfice on top (msk(i)=0), reset the boundary layer
221    C     mixing coefficients blmc to pure Ri-number based mixing
222                   blmc(i,k,1) = max ( blmc(i,k,1)*msk(i),
223         &              diffus(i,k,1) )
224                   blmc(i,k,2) = max ( blmc(i,k,2)*msk(i),
225         &              diffus(i,k,2) )
226                   blmc(i,k,3) = max ( blmc(i,k,3)*msk(i),
227         &              diffus(i,k,3) )
228    #endif /* not ALLOW_SHELFICE */
229                 diffus(i,k,1) = max ( blmc(i,k,1), viscAr  )                 diffus(i,k,1) = max ( blmc(i,k,1), viscAr  )
230                 diffus(i,k,2) = max ( blmc(i,k,2), diffusKzS(i,Nr) )                 diffus(i,k,2) = max ( blmc(i,k,2), diffusKzS(i,Nr) )
231                 diffus(i,k,3) = max ( blmc(i,k,3), diffusKzT(i,Nr) )                 diffus(i,k,3) = max ( blmc(i,k,3), diffusKzT(i,Nr) )
# Line 229  c--------------------------------------- Line 243  c---------------------------------------
243  c*************************************************************************  c*************************************************************************
244    
245        subroutine bldepth (        subroutine bldepth (
246       I       mytime, mythid       I       kmtj
      I     , kmtj  
247       I     , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol       I     , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol
248       I     , ikppkey       I     , ikppkey
249       O     , hbl, bfsfc, stable, casea, kbl, Rib, sigma       O     , hbl, bfsfc, stable, casea, kbl, Rib, sigma
250       &     )       I     , myTime, myIter, myThid )
251    
252  c     the oceanic planetary boundary layer depth, hbl, is determined as  c     the oceanic planetary boundary layer depth, hbl, is determined as
253  c     the shallowest depth where the bulk Richardson number is  c     the shallowest depth where the bulk Richardson number is
# Line 264  c Line 277  c
277    
278  c input  c input
279  c------  c------
280  c myTime    : current time in simulation  c   myTime :: Current time in simulation
281  c myThid    : thread number for this instance of the routine  c   myIter :: Current iteration number in simulation
282    c   myThid :: My Thread Id. number
283  c kmtj      : number of vertical layers  c kmtj      : number of vertical layers
284  c dvsq      : (velocity shear re sfc)^2             ((m/s)^2)  c dvsq      : (velocity shear re sfc)^2             ((m/s)^2)
285  c dbloc     : local delta buoyancy across interfaces  (m/s^2)  c dbloc     : local delta buoyancy across interfaces  (m/s^2)
# Line 276  c ustar     : surface friction velocity Line 290  c ustar     : surface friction velocity
290  c bo        : surface turbulent buoyancy forcing    (m^2/s^3)  c bo        : surface turbulent buoyancy forcing    (m^2/s^3)
291  c bosol     : radiative buoyancy forcing            (m^2/s^3)  c bosol     : radiative buoyancy forcing            (m^2/s^3)
292  c coriol    : Coriolis parameter                        (1/s)  c coriol    : Coriolis parameter                        (1/s)
293        _RL     mytime        _RL     myTime
294        integer mythid        integer myIter
295          integer myThid
296        integer kmtj(imt)        integer kmtj(imt)
297        _RL dvsq    (imt,Nr)        _RL dvsq    (imt,Nr)
298        _RL dbloc   (imt,Nr)        _RL dbloc   (imt,Nr)
# Line 351  c     compute bfsfc = sw fraction at hbf Line 366  c     compute bfsfc = sw fraction at hbf
366           end do           end do
367  CADJ store worka = comlev1_kpp_k, key = kkppkey  CADJ store worka = comlev1_kpp_k, key = kkppkey
368           call SWFRAC(           call SWFRAC(
369       I        imt, hbf,       I       imt, hbf,
370       I        mytime, mythid,       U       worka,
371       U        worka )       I       myTime, myIter, myThid )
372  CADJ store worka = comlev1_kpp_k, key = kkppkey  CADJ store worka = comlev1_kpp_k, key = kkppkey
373    
374    
# Line 377  c--------------------------------------- Line 392  c---------------------------------------
392    
393           call wscale (           call wscale (
394       I        sigma, casea, ustar, bfsfc,       I        sigma, casea, ustar, bfsfc,
395       O        wm, ws )       O        wm, ws, myThid )
396  CADJ store ws = comlev1_kpp_k, key = kkppkey  CADJ store ws = comlev1_kpp_k, key = kkppkey
397    
398           do i = 1, imt           do i = 1, imt
# Line 454  c--------------------------------------- Line 469  c---------------------------------------
469  CADJ store worka = comlev1_kpp  CADJ store worka = comlev1_kpp
470  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
471        call SWFRAC(        call SWFRAC(
472       I     imt, minusone,       I       imt, minusone,
473       I     mytime, mythid,       U       worka,
474       U     worka )       I       myTime, myIter, myThid )
475  CADJ store worka = comlev1_kpp  CADJ store worka = comlev1_kpp
476  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
477    
# Line 527  CADJ store worka = comlev1_kpp Line 542  CADJ store worka = comlev1_kpp
542  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
543        call SWFRAC(        call SWFRAC(
544       I     imt, minusone,       I     imt, minusone,
545       I     mytime, mythid,       U     worka,
546       U     worka )       I     myTime, myIter, myThid )
547  CADJ store worka = comlev1_kpp  CADJ store worka = comlev1_kpp
548  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)  CADJ &   , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
549    
# Line 562  c*************************************** Line 577  c***************************************
577    
578        subroutine wscale (        subroutine wscale (
579       I     sigma, hbl, ustar, bfsfc,       I     sigma, hbl, ustar, bfsfc,
580       O     wm, ws )       O     wm, ws,
581         I     myThid )
582    
583  c     compute turbulent velocity scales.  c     compute turbulent velocity scales.
584  c     use a 2D-lookup table for wm and ws as functions of ustar and  c     use a 2D-lookup table for wm and ws as functions of ustar and
# Line 583  c sigma   : normalized depth (d/hbl) Line 599  c sigma   : normalized depth (d/hbl)
599  c hbl     : boundary layer depth (m)  c hbl     : boundary layer depth (m)
600  c ustar   : surface friction velocity         (m/s)  c ustar   : surface friction velocity         (m/s)
601  c bfsfc   : total surface buoyancy flux       (m^2/s^3)  c bfsfc   : total surface buoyancy flux       (m^2/s^3)
602    c myThid  : thread number for this instance of the routine
603          integer myThid
604        _RL sigma(imt)        _RL sigma(imt)
605        _RL hbl  (imt)        _RL hbl  (imt)
606        _RL ustar(imt)        _RL ustar(imt)
# Line 657  c--------------------------------------- Line 675  c---------------------------------------
675  c*************************************************************************  c*************************************************************************
676    
677        subroutine Ri_iwmix (        subroutine Ri_iwmix (
678       I       kmtj, shsq, dbloc, dblocSm       I       kmtj, shsq, dbloc, dblocSm,
679       I     , diffusKzS, diffusKzT       I       diffusKzS, diffusKzT,
680       I     , ikppkey       I       ikppkey,
681       O     , diffus )       O       diffus,
682         I       myThid )
683    
684  c     compute interior viscosity diffusivity coefficients due  c     compute interior viscosity diffusivity coefficients due
685  c     to shear instability (dependent on a local Richardson number),  c     to shear instability (dependent on a local Richardson number),
# Line 681  c     dbloc  (imt,Nr)      local delta b Line 700  c     dbloc  (imt,Nr)      local delta b
700  c     dblocSm(imt,Nr)      horizontally smoothed dbloc              (m/s^2)  c     dblocSm(imt,Nr)      horizontally smoothed dbloc              (m/s^2)
701  c     diffusKzS(imt,Nr)- background vertical diffusivity for scalars    (m^2/s)  c     diffusKzS(imt,Nr)- background vertical diffusivity for scalars    (m^2/s)
702  c     diffusKzT(imt,Nr)- background vertical diffusivity for theta      (m^2/s)  c     diffusKzT(imt,Nr)- background vertical diffusivity for theta      (m^2/s)
703    c     myThid :: My Thread Id. number
704        integer kmtj (imt)        integer kmtj (imt)
705        _RL shsq     (imt,Nr)        _RL shsq     (imt,Nr)
706        _RL dbloc    (imt,Nr)        _RL dbloc    (imt,Nr)
# Line 688  c     diffusKzT(imt,Nr)- background vert Line 708  c     diffusKzT(imt,Nr)- background vert
708        _RL diffusKzS(imt,Nr)        _RL diffusKzS(imt,Nr)
709        _RL diffusKzT(imt,Nr)        _RL diffusKzT(imt,Nr)
710        integer ikppkey        integer ikppkey
711          integer myThid
712    
713  c output  c output
714  c     diffus(imt,0:Nrp1,1)  vertical viscosivity coefficient        (m^2/s)  c     diffus(imt,0:Nrp1,1)  vertical viscosivity coefficient        (m^2/s)
# Line 760  CADJ store diffus(:,:,1) = kpp_ri_tape_m Line 781  CADJ store diffus(:,:,1) = kpp_ri_tape_m
781  CADJ &  , key=mr, shape=(/ (sNx+2*OLx)*(sNy+2*OLy),Nr+2 /)  CADJ &  , key=mr, shape=(/ (sNx+2*OLx)*(sNy+2*OLy),Nr+2 /)
782    
783           call z121 (           call z121 (
784       U     diffus(1,0,1))       U     diffus(1,0,1)
785         I     myThid )
786        end do        end do
787  #endif  #endif
788    
# Line 824  c         set surface values to 0.0 Line 846  c         set surface values to 0.0
846  c*************************************************************************  c*************************************************************************
847    
848        subroutine z121 (        subroutine z121 (
849       U     v )       U     v,
850         I     myThid )
851    
852  c     Apply 121 smoothing in k to 2-d array V(i,k=1,Nr)  c     Apply 121 smoothing in k to 2-d array V(i,k=1,Nr)
853  c     top (0) value is used as a dummy  c     top (0) value is used as a dummy
# Line 842  c     penetrative convection. Line 865  c     penetrative convection.
865  c input/output  c input/output
866  c-------------  c-------------
867  c v     : 2-D array to be smoothed in Nrp1 direction  c v     : 2-D array to be smoothed in Nrp1 direction
868    c myThid: thread number for this instance of the routine
869          integer myThid
870        _RL v(imt,0:Nrp1)        _RL v(imt,0:Nrp1)
871    
872  #ifdef ALLOW_KPP  #ifdef ALLOW_KPP
# Line 907  c*************************************** Line 932  c***************************************
932    
933        subroutine smooth_horiz (        subroutine smooth_horiz (
934       I     k, bi, bj,       I     k, bi, bj,
935       U     fld )       U     fld,
936         I     myThid )
937    
938  c     Apply horizontal smoothing to global _RL 2-D array  c     Apply horizontal smoothing to global _RL 2-D array
939    
# Line 919  c     Apply horizontal smoothing to glob Line 945  c     Apply horizontal smoothing to glob
945  c     input  c     input
946  c     bi, bj : array indices  c     bi, bj : array indices
947  c     k      : vertical index used for masking  c     k      : vertical index used for masking
948    c     myThid : thread number for this instance of the routine
949          INTEGER myThid
950        integer k, bi, bj        integer k, bi, bj
951    
952  c     input/output  c     input/output
# Line 989  c*************************************** Line 1017  c***************************************
1017        subroutine blmix (        subroutine blmix (
1018       I       ustar, bfsfc, hbl, stable, casea, diffus, kbl       I       ustar, bfsfc, hbl, stable, casea, diffus, kbl
1019       O     , dkm1, blmc, ghat, sigma, ikppkey       O     , dkm1, blmc, ghat, sigma, ikppkey
1020       &     )       I     , myThid )
1021    
1022  c     mixing coefficients within boundary layer depend on surface  c     mixing coefficients within boundary layer depend on surface
1023  c     forcing and the magnitude and gradient of interior mixing below  c     forcing and the magnitude and gradient of interior mixing below
# Line 1012  c     stable(imt)                 = 1 in Line 1040  c     stable(imt)                 = 1 in
1040  c     casea (imt)                 = 1 in case A  c     casea (imt)                 = 1 in case A
1041  c     diffus(imt,0:Nrp1,mdiff)    vertical diffusivities              (m^2/s)  c     diffus(imt,0:Nrp1,mdiff)    vertical diffusivities              (m^2/s)
1042  c     kbl   (imt)                 -1 of first grid level below hbl  c     kbl   (imt)                 -1 of first grid level below hbl
1043    c     myThid               thread number for this instance of the routine
1044          integer myThid
1045        _RL ustar (imt)        _RL ustar (imt)
1046        _RL bfsfc (imt)        _RL bfsfc (imt)
1047        _RL hbl   (imt)        _RL hbl   (imt)
# Line 1061  c--------------------------------------- Line 1091  c---------------------------------------
1091  CADJ STORE sigma = comlev1_kpp, key = ikppkey  CADJ STORE sigma = comlev1_kpp, key = ikppkey
1092        call wscale (        call wscale (
1093       I        sigma, hbl, ustar, bfsfc,       I        sigma, hbl, ustar, bfsfc,
1094       O        wm, ws )       O        wm, ws, myThid )
1095  CADJ STORE wm = comlev1_kpp, key = ikppkey  CADJ STORE wm = comlev1_kpp, key = ikppkey
1096  CADJ STORE ws = comlev1_kpp, key = ikppkey  CADJ STORE ws = comlev1_kpp, key = ikppkey
1097    
# Line 1154  CADJ STORE ws = comlev1_kpp_k, key = kkp Line 1184  CADJ STORE ws = comlev1_kpp_k, key = kkp
1184  CADJ STORE sigma = comlev1_kpp_k, key = kkppkey  CADJ STORE sigma = comlev1_kpp_k, key = kkppkey
1185           call wscale (           call wscale (
1186       I        sigma, hbl, ustar, bfsfc,       I        sigma, hbl, ustar, bfsfc,
1187       O        wm, ws )       O        wm, ws, myThid )
1188  CADJ STORE wm = comlev1_kpp_k, key = kkppkey  CADJ STORE wm = comlev1_kpp_k, key = kkppkey
1189  CADJ STORE ws = comlev1_kpp_k, key = kkppkey  CADJ STORE ws = comlev1_kpp_k, key = kkppkey
1190    
# Line 1207  CADJ STORE ws = comlev1_kpp, key = ikppk Line 1237  CADJ STORE ws = comlev1_kpp, key = ikppk
1237  CADJ STORE sigma = comlev1_kpp, key = ikppkey  CADJ STORE sigma = comlev1_kpp, key = ikppkey
1238        call wscale (        call wscale (
1239       I        sigma, hbl, ustar, bfsfc,       I        sigma, hbl, ustar, bfsfc,
1240       O        wm, ws )       O        wm, ws, myThid )
1241  CADJ STORE wm = comlev1_kpp, key = ikppkey  CADJ STORE wm = comlev1_kpp, key = ikppkey
1242  CADJ STORE ws = comlev1_kpp, key = ikppkey  CADJ STORE ws = comlev1_kpp, key = ikppkey
1243    
# Line 1235  c*************************************** Line 1265  c***************************************
1265       I       dkm1, hbl, kbl, diffus, casea       I       dkm1, hbl, kbl, diffus, casea
1266       U     , ghat       U     , ghat
1267       O     , blmc       O     , blmc
1268       &     )       &     , myThid )
1269    
1270  c enhance the diffusivity at the kbl-.5 interface  c enhance the diffusivity at the kbl-.5 interface
1271    
# Line 1250  c     hbl(imt)                  boundary Line 1280  c     hbl(imt)                  boundary
1280  c     kbl(imt)                  grid above hbl  c     kbl(imt)                  grid above hbl
1281  c     diffus(imt,0:Nrp1,mdiff) vertical diffusivities           (m^2/s)  c     diffus(imt,0:Nrp1,mdiff) vertical diffusivities           (m^2/s)
1282  c     casea(imt)                = 1 in caseA, = 0 in case B  c     casea(imt)                = 1 in caseA, = 0 in case B
1283    c     myThid                    thread number for this instance of the routine
1284          integer   myThid
1285        _RL dkm1  (imt,mdiff)        _RL dkm1  (imt,mdiff)
1286        _RL hbl   (imt)        _RL hbl   (imt)
1287        integer kbl   (imt)        integer kbl   (imt)
# Line 1296  c     fraction hbl lies beteen zgrid nei Line 1328  c     fraction hbl lies beteen zgrid nei
1328  c*************************************************************************  c*************************************************************************
1329    
1330        SUBROUTINE STATEKPP (        SUBROUTINE STATEKPP (
1331       I     ikppkey, bi, bj, myThid,       O     RHO1, DBLOC, DBSFC, TTALPHA, SSBETA,
1332       O     RHO1, DBLOC, DBSFC, TTALPHA, SSBETA)       I     ikppkey, bi, bj, myThid )
1333  c  c
1334  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
1335  c     "statekpp" computes all necessary input arrays  c     "statekpp" computes all necessary input arrays
# Line 1389  CADJ STORE salt (:,:,1,bi,bj) = comlev1_ Line 1421  CADJ STORE salt (:,:,1,bi,bj) = comlev1_
1421    
1422        call FIND_ALPHA(        call FIND_ALPHA(
1423       I     bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,       I     bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,
1424       O     WORK2 )       O     WORK2, myThid )
1425    
1426        call FIND_BETA(        call FIND_BETA(
1427       I     bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,       I     bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,
1428       O     WORK3 )       O     WORK3, myThid )
1429    
1430        DO J = 1-OLy, sNy+OLy        DO J = 1-OLy, sNy+OLy
1431           DO I = 1-OLx, sNx+OLx           DO I = 1-OLx, sNx+OLx
# Line 1461  CADJ STORE rho1k (:,:)          = comlev Line 1493  CADJ STORE rho1k (:,:)          = comlev
1493    
1494           call FIND_ALPHA(           call FIND_ALPHA(
1495       I        bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,       I        bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,
1496       O        WORK1 )       O        WORK1, myThid )
1497    
1498           call FIND_BETA(           call FIND_BETA(
1499       I        bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,       I        bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,
1500       O        WORK2 )       O        WORK2, myThid )
1501    
1502           DO J = 1-OLy, sNy+OLy           DO J = 1-OLy, sNy+OLy
1503              DO I = 1-OLx, sNx+OLx              DO I = 1-OLx, sNx+OLx

Legend:
Removed from v.1.27  
changed lines
  Added in v.1.32

  ViewVC Help
Powered by ViewVC 1.1.22