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

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

Put dimensions.h and paramet.h into modules

  • 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 5159 2024-08-02 19:58:25Z fairhead $
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  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
14  USE lmdz_paramet
15  IMPLICIT NONE
16
17  !=======================================================================
18
19  !   Friction for the Newtonian case:
20  !   --------------------------------
21  !    2 possibilities (depending on flag 'friction_type'
22  ! friction_type=0 : A friction that is only applied to the lowermost
23  !                   atmospheric layer
24  ! friction_type=1 : Friction applied on all atmospheric layer (but
25  !   (default)       with stronger magnitude near the surface; see
26  !                   iniacademic.F)
27  !=======================================================================
28
29
30
31
32  ! arguments:
33  REAL, INTENT(OUT) :: ucov(iip1, jjp1, llm)
34  REAL, INTENT(OUT) :: vcov(iip1, jjm, llm)
35  REAL, INTENT(IN) :: pdt ! time step
36
37  ! local variables:
38
39  REAL :: modv(iip1, jjp1), zco, zsi
40  REAL :: vpn, vps, upoln, upols, vpols, vpoln
41  REAL :: u2(iip1, jjp1), v2(iip1, jjm)
42  INTEGER :: i, j, l
43  REAL, PARAMETER :: cfric = 1.e-5
44  LOGICAL, SAVE :: firstcall = .TRUE.
45  INTEGER, SAVE :: friction_type = 1
46  CHARACTER(len = 20) :: modname = "friction"
47  CHARACTER(len = 80) :: abort_message
48
49  IF (firstcall) THEN
50    ! set friction type
51    CALL getin("friction_type", friction_type)
52    IF ((friction_type<0).OR.(friction_type>1)) THEN
53      abort_message = "wrong friction type"
54      WRITE(lunout, *)'Friction: wrong friction type', friction_type
55      CALL abort_gcm(modname, abort_message, 42)
56    endif
57    firstcall = .FALSE.
58  ENDIF
59
60  IF (friction_type==0) THEN
61    !   calcul des composantes au carre du vent naturel
62    DO j = 1, jjp1
63      DO i = 1, iip1
64        u2(i, j) = ucov(i, j, 1) * ucov(i, j, 1) * unscu2(i, j)
65      enddo
66    enddo
67    DO j = 1, jjm
68      DO i = 1, iip1
69        v2(i, j) = vcov(i, j, 1) * vcov(i, j, 1) * unscv2(i, j)
70      enddo
71    enddo
72
73    !   calcul du module de V en dehors des poles
74    DO j = 2, jjm
75      DO i = 2, iip1
76        modv(i, j) = sqrt(0.5 * (u2(i - 1, j) + u2(i, j) + v2(i, j - 1) + v2(i, j)))
77      enddo
78      modv(1, j) = modv(iip1, j)
79    enddo
80
81    !   les deux composantes du vent au pole sont obtenues comme
82    !   premiers modes de fourier de v pres du pole
83    upoln = 0.
84    vpoln = 0.
85    upols = 0.
86    vpols = 0.
87    DO i = 2, iip1
88      zco = cos(rlonv(i)) * (rlonu(i) - rlonu(i - 1))
89      zsi = sin(rlonv(i)) * (rlonu(i) - rlonu(i - 1))
90      vpn = vcov(i, 1, 1) / cv(i, 1)
91      vps = vcov(i, jjm, 1) / cv(i, jjm)
92      upoln = upoln + zco * vpn
93      vpoln = vpoln + zsi * vpn
94      upols = upols + zco * vps
95      vpols = vpols + zsi * vps
96    enddo
97    vpn = sqrt(upoln * upoln + vpoln * vpoln) / pi
98    vps = sqrt(upols * upols + vpols * vpols) / pi
99    DO i = 1, iip1
100      ! modv(i,1)=vpn
101      ! modv(i,jjp1)=vps
102      modv(i, 1) = modv(i, 2)
103      modv(i, jjp1) = modv(i, jjm)
104    enddo
105
106    !   calcul du frottement au sol.
107    DO j = 2, jjm
108      DO i = 1, iim
109        ucov(i, j, 1) = ucov(i, j, 1) &
110                - cfric * pdt * 0.5 * (modv(i + 1, j) + modv(i, j)) * ucov(i, j, 1)
111      enddo
112      ucov(iip1, j, 1) = ucov(1, j, 1)
113    enddo
114    DO j = 1, jjm
115      DO i = 1, iip1
116        vcov(i, j, 1) = vcov(i, j, 1) &
117                - cfric * pdt * 0.5 * (modv(i, j + 1) + modv(i, j)) * vcov(i, j, 1)
118      enddo
119      vcov(iip1, j, 1) = vcov(1, j, 1)
120    enddo
121  ENDIF ! of if (friction_type.EQ.0)
122
123  IF (friction_type==1) THEN
124    DO l = 1, llm
125      ucov(:, :, l) = ucov(:, :, l) * (1. - pdt * kfrict(l))
126      vcov(:, :, l) = vcov(:, :, l) * (1. - pdt * kfrict(l))
127    enddo
128  ENDIF
129
130END SUBROUTINE friction
131
Note: See TracBrowser for help on using the repository browser.