source: LMDZ6/branches/Amaury_dev/libf/dyn3d/friction.F90 @ 5158

Last change on this file since 5158 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.8 KB
Line 
1! $Id: friction.F90 5158 2024-08-02 12:12:03Z abarral $
2
3!=======================================================================
4SUBROUTINE friction(ucov, vcov, pdt)
5
6  USE control_mod
7  USE IOIPSL
8  USE comconst_mod, ONLY: pi
9  USE lmdz_iniprint, ONLY: lunout, prt_level
10  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
11  USE lmdz_comgeom2
12
13  IMPLICIT NONE
14
15  !=======================================================================
16
17  !   Friction for the Newtonian case:
18  !   --------------------------------
19  !    2 possibilities (depending on flag 'friction_type'
20  ! friction_type=0 : A friction that is only applied to the lowermost
21  !                   atmospheric layer
22  ! friction_type=1 : Friction applied on all atmospheric layer (but
23  !   (default)       with stronger magnitude near the surface; see
24  !                   iniacademic.F)
25  !=======================================================================
26
27  INCLUDE "dimensions.h"
28  INCLUDE "paramet.h"
29
30  ! arguments:
31  REAL, INTENT(OUT) :: ucov(iip1, jjp1, llm)
32  REAL, INTENT(OUT) :: vcov(iip1, jjm, llm)
33  REAL, INTENT(IN) :: pdt ! time step
34
35  ! local variables:
36
37  REAL :: modv(iip1, jjp1), zco, zsi
38  REAL :: vpn, vps, upoln, upols, vpols, vpoln
39  REAL :: u2(iip1, jjp1), v2(iip1, jjm)
40  INTEGER :: i, j, l
41  REAL, PARAMETER :: cfric = 1.e-5
42  LOGICAL, SAVE :: firstcall = .TRUE.
43  INTEGER, SAVE :: friction_type = 1
44  CHARACTER(len = 20) :: modname = "friction"
45  CHARACTER(len = 80) :: abort_message
46
47  IF (firstcall) THEN
48    ! set friction type
49    CALL getin("friction_type", friction_type)
50    IF ((friction_type<0).OR.(friction_type>1)) THEN
51      abort_message = "wrong friction type"
52      WRITE(lunout, *)'Friction: wrong friction type', friction_type
53      CALL abort_gcm(modname, abort_message, 42)
54    endif
55    firstcall = .FALSE.
56  ENDIF
57
58  IF (friction_type==0) THEN
59    !   calcul des composantes au carre du vent naturel
60    DO j = 1, jjp1
61      DO i = 1, iip1
62        u2(i, j) = ucov(i, j, 1) * ucov(i, j, 1) * unscu2(i, j)
63      enddo
64    enddo
65    DO j = 1, jjm
66      DO i = 1, iip1
67        v2(i, j) = vcov(i, j, 1) * vcov(i, j, 1) * unscv2(i, j)
68      enddo
69    enddo
70
71    !   calcul du module de V en dehors des poles
72    DO j = 2, jjm
73      DO i = 2, iip1
74        modv(i, j) = sqrt(0.5 * (u2(i - 1, j) + u2(i, j) + v2(i, j - 1) + v2(i, j)))
75      enddo
76      modv(1, j) = modv(iip1, j)
77    enddo
78
79    !   les deux composantes du vent au pole sont obtenues comme
80    !   premiers modes de fourier de v pres du pole
81    upoln = 0.
82    vpoln = 0.
83    upols = 0.
84    vpols = 0.
85    DO i = 2, iip1
86      zco = cos(rlonv(i)) * (rlonu(i) - rlonu(i - 1))
87      zsi = sin(rlonv(i)) * (rlonu(i) - rlonu(i - 1))
88      vpn = vcov(i, 1, 1) / cv(i, 1)
89      vps = vcov(i, jjm, 1) / cv(i, jjm)
90      upoln = upoln + zco * vpn
91      vpoln = vpoln + zsi * vpn
92      upols = upols + zco * vps
93      vpols = vpols + zsi * vps
94    enddo
95    vpn = sqrt(upoln * upoln + vpoln * vpoln) / pi
96    vps = sqrt(upols * upols + vpols * vpols) / pi
97    DO i = 1, iip1
98      ! modv(i,1)=vpn
99      ! modv(i,jjp1)=vps
100      modv(i, 1) = modv(i, 2)
101      modv(i, jjp1) = modv(i, jjm)
102    enddo
103
104    !   calcul du frottement au sol.
105    DO j = 2, jjm
106      DO i = 1, iim
107        ucov(i, j, 1) = ucov(i, j, 1) &
108                - cfric * pdt * 0.5 * (modv(i + 1, j) + modv(i, j)) * ucov(i, j, 1)
109      enddo
110      ucov(iip1, j, 1) = ucov(1, j, 1)
111    enddo
112    DO j = 1, jjm
113      DO i = 1, iip1
114        vcov(i, j, 1) = vcov(i, j, 1) &
115                - cfric * pdt * 0.5 * (modv(i, j + 1) + modv(i, j)) * vcov(i, j, 1)
116      enddo
117      vcov(iip1, j, 1) = vcov(1, j, 1)
118    enddo
119  ENDIF ! of if (friction_type.EQ.0)
120
121  IF (friction_type==1) THEN
122    DO l = 1, llm
123      ucov(:, :, l) = ucov(:, :, l) * (1. - pdt * kfrict(l))
124      vcov(:, :, l) = vcov(:, :, l) * (1. - pdt * kfrict(l))
125    enddo
126  ENDIF
127
128END SUBROUTINE friction
129
Note: See TracBrowser for help on using the repository browser.