| Directory: | ./ |
|---|---|
| File: | dyn3d_common/enercin.f90 |
| Date: | 2022-01-11 19:19:34 |
| Exec | Total | Coverage | |
|---|---|---|---|
| Lines: | 14 | 14 | 100.0% |
| Branches: | 18 | 18 | 100.0% |
| Line | Branch | Exec | Source |
|---|---|---|---|
| 1 | 3841 | SUBROUTINE enercin ( vcov, ucov, vcont, ucont, ecin ) | |
| 2 | ! | ||
| 3 | !------------------------------------------------------------------------------- | ||
| 4 | ! Authors: P. Le Van. | ||
| 5 | !------------------------------------------------------------------------------- | ||
| 6 | ! Purpose: Compute kinetic energy at sigma levels. | ||
| 7 | IMPLICIT NONE | ||
| 8 | include "dimensions.h" | ||
| 9 | include "paramet.h" | ||
| 10 | include "comgeom.h" | ||
| 11 | !=============================================================================== | ||
| 12 | ! Arguments: | ||
| 13 | REAL, INTENT(IN) :: vcov (ip1jm, llm) | ||
| 14 | REAL, INTENT(IN) :: ucov (ip1jmp1,llm) | ||
| 15 | REAL, INTENT(IN) :: vcont (ip1jm, llm) | ||
| 16 | REAL, INTENT(IN) :: ucont (ip1jmp1,llm) | ||
| 17 | REAL, INTENT(OUT) :: ecin (ip1jmp1,llm) | ||
| 18 | !=============================================================================== | ||
| 19 | ! Notes: | ||
| 20 | ! . V | ||
| 21 | ! i,j-1 | ||
| 22 | ! | ||
| 23 | ! alpha4 . . alpha1 | ||
| 24 | ! | ||
| 25 | ! | ||
| 26 | ! U . . P . U | ||
| 27 | ! i-1,j i,j i,j | ||
| 28 | ! | ||
| 29 | ! alpha3 . . alpha2 | ||
| 30 | ! | ||
| 31 | ! | ||
| 32 | ! . V | ||
| 33 | ! i,j | ||
| 34 | ! | ||
| 35 | ! Kinetic energy at scalar point P(i,j) (excluding poles) is: | ||
| 36 | ! Ecin = 0.5 * U(i-1,j)**2 *( alpha3 + alpha4 ) + | ||
| 37 | ! 0.5 * U(i ,j)**2 *( alpha1 + alpha2 ) + | ||
| 38 | ! 0.5 * V(i,j-1)**2 *( alpha1 + alpha4 ) + | ||
| 39 | ! 0.5 * V(i, j)**2 *( alpha2 + alpha3 ) | ||
| 40 | !=============================================================================== | ||
| 41 | ! Local variables: | ||
| 42 | INTEGER :: l, ij, i | ||
| 43 | REAL :: ecinni(iip1), ecinsi(iip1), ecinpn, ecinps | ||
| 44 | !=============================================================================== | ||
| 45 |
2/2✓ Branch 0 taken 149799 times.
✓ Branch 1 taken 3841 times.
|
153640 | DO l=1,llm |
| 46 |
2/2✓ Branch 0 taken 153094578 times.
✓ Branch 1 taken 149799 times.
|
153244377 | DO ij = iip2, ip1jm -1 |
| 47 | ecin(ij+1,l)=0.5*(ucov(ij ,l)*ucont(ij ,l)*alpha3p4(ij +1) & | ||
| 48 | + ucov(ij+1 ,l)*ucont(ij+1 ,l)*alpha1p2(ij +1) & | ||
| 49 | + vcov(ij-iim,l)*vcont(ij-iim,l)*alpha1p4(ij +1) & | ||
| 50 | 153244377 | + vcov(ij+1 ,l)*vcont(ij+1 ,l)*alpha2p3(ij +1) ) | |
| 51 | END DO | ||
| 52 | !--- Correction: ecin(1,j,l)= ecin(iip1,j,l) | ||
| 53 |
2/2✓ Branch 0 taken 4493970 times.
✓ Branch 1 taken 149799 times.
|
4643769 | DO ij=iip2,ip1jm,iip1; ecin(ij,l) = ecin(ij+iim,l); END DO |
| 54 | |||
| 55 | !--- North pole | ||
| 56 |
2/2✓ Branch 0 taken 149799 times.
✓ Branch 1 taken 4793568 times.
|
4943367 | DO i=1,iim |
| 57 | 4943367 | ecinni(i) = vcov(i,l)*vcont(i,l)*aire(i) | |
| 58 | END DO | ||
| 59 |
2/2✓ Branch 0 taken 4793568 times.
✓ Branch 1 taken 149799 times.
|
4943367 | ecinpn = 0.5*SUM(ecinni(1:iim))/apoln |
| 60 |
2/2✓ Branch 0 taken 149799 times.
✓ Branch 1 taken 4943367 times.
|
5093166 | DO ij=1,iip1; ecin(ij,l)=ecinpn; END DO |
| 61 | |||
| 62 | !--- South pole | ||
| 63 |
2/2✓ Branch 0 taken 149799 times.
✓ Branch 1 taken 4793568 times.
|
4943367 | DO i=1,iim |
| 64 | 4943367 | ecinsi(i) = vcov(i+ip1jmi1,l)*vcont(i+ip1jmi1,l)*aire(i+ip1jm) | |
| 65 | END DO | ||
| 66 |
2/2✓ Branch 0 taken 4793568 times.
✓ Branch 1 taken 149799 times.
|
4943367 | ecinps = 0.5*SUM(ecinsi(1:iim))/apols |
| 67 |
2/2✓ Branch 0 taken 4943367 times.
✓ Branch 1 taken 149799 times.
|
5097007 | DO ij=1,iip1; ecin(ij+ip1jm,l)=ecinps; END DO |
| 68 | END DO | ||
| 69 | |||
| 70 | 3841 | END SUBROUTINE enercin | |
| 71 | |||
| 72 |