source: LMDZ5/trunk/libf/dyn3d/friction.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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!
2! $Id: friction.F 1907 2013-11-26 13:10:46Z lguez $
3!
4c=======================================================================
5      SUBROUTINE friction(ucov,vcov,pdt)
6
7      USE control_mod
8#ifdef CPP_IOIPSL
9      USE IOIPSL
10#else
11! if not using IOIPSL, we still need to use (a local version of) getin
12      USE ioipsl_getincom
13#endif
14     
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#include "dimensions.h"
30#include "paramet.h"
31#include "comgeom2.h"
32#include "comconst.h"
33#include "iniprint.h"
34#include "academic.h"
35
36! arguments:
37      REAL,INTENT(out) :: ucov( iip1,jjp1,llm )
38      REAL,INTENT(out) :: vcov( iip1,jjm,llm )
39      REAL,INTENT(in) :: pdt ! time step
40
41! local variables:
42
43      REAL modv(iip1,jjp1),zco,zsi
44      REAL vpn,vps,upoln,upols,vpols,vpoln
45      REAL u2(iip1,jjp1),v2(iip1,jjm)
46      INTEGER  i,j,l
47      REAL,PARAMETER :: cfric=1.e-5
48      LOGICAL,SAVE :: firstcall=.true.
49      INTEGER,SAVE :: friction_type=1
50      CHARACTER(len=20) :: modname="friction"
51      CHARACTER(len=80) :: abort_message
52     
53      IF (firstcall) THEN
54        ! set friction type
55        call getin("friction_type",friction_type)
56        if ((friction_type.lt.0).or.(friction_type.gt.1)) then
57          abort_message="wrong friction type"
58          write(lunout,*)'Friction: wrong friction type',friction_type
59          call abort_gcm(modname,abort_message,42)
60        endif
61        firstcall=.false.
62      ENDIF
63
64      if (friction_type.eq.0) then
65c   calcul des composantes au carre du vent naturel
66      do j=1,jjp1
67         do i=1,iip1
68            u2(i,j)=ucov(i,j,1)*ucov(i,j,1)*unscu2(i,j)
69         enddo
70      enddo
71      do j=1,jjm
72         do i=1,iip1
73            v2(i,j)=vcov(i,j,1)*vcov(i,j,1)*unscv2(i,j)
74         enddo
75      enddo
76
77c   calcul du module de V en dehors des poles
78      do j=2,jjm
79         do i=2,iip1
80            modv(i,j)=sqrt(0.5*(u2(i-1,j)+u2(i,j)+v2(i,j-1)+v2(i,j)))
81         enddo
82         modv(1,j)=modv(iip1,j)
83      enddo
84
85c   les deux composantes du vent au pole sont obtenues comme
86c   premiers modes de fourier de v pres du pole
87      upoln=0.
88      vpoln=0.
89      upols=0.
90      vpols=0.
91      do i=2,iip1
92         zco=cos(rlonv(i))*(rlonu(i)-rlonu(i-1))
93         zsi=sin(rlonv(i))*(rlonu(i)-rlonu(i-1))
94         vpn=vcov(i,1,1)/cv(i,1)
95         vps=vcov(i,jjm,1)/cv(i,jjm)
96         upoln=upoln+zco*vpn
97         vpoln=vpoln+zsi*vpn
98         upols=upols+zco*vps
99         vpols=vpols+zsi*vps
100      enddo
101      vpn=sqrt(upoln*upoln+vpoln*vpoln)/pi
102      vps=sqrt(upols*upols+vpols*vpols)/pi
103      do i=1,iip1
104c        modv(i,1)=vpn
105c        modv(i,jjp1)=vps
106         modv(i,1)=modv(i,2)
107         modv(i,jjp1)=modv(i,jjm)
108      enddo
109
110c   calcul du frottement au sol.
111      do j=2,jjm
112         do i=1,iim
113            ucov(i,j,1)=ucov(i,j,1)
114     s      -cfric*pdt*0.5*(modv(i+1,j)+modv(i,j))*ucov(i,j,1)
115         enddo
116         ucov(iip1,j,1)=ucov(1,j,1)
117      enddo
118      do j=1,jjm
119         do i=1,iip1
120            vcov(i,j,1)=vcov(i,j,1)
121     s      -cfric*pdt*0.5*(modv(i,j+1)+modv(i,j))*vcov(i,j,1)
122         enddo
123         vcov(iip1,j,1)=vcov(1,j,1)
124      enddo
125      endif ! of if (friction_type.eq.0)
126
127      if (friction_type.eq.1) then
128        do l=1,llm
129          ucov(:,:,l)=ucov(:,:,l)*(1.-pdt*kfrict(l))
130          vcov(:,:,l)=vcov(:,:,l)*(1.-pdt*kfrict(l))
131        enddo
132      endif
133     
134      RETURN
135      END
136
Note: See TracBrowser for help on using the repository browser.