Ignore:
Timestamp:
Nov 18, 2010, 1:01:24 PM (14 years ago)
Author:
Laurent Fairhead
Message:

Merge of LMDZ5V1.0-dev branch r1453 into LMDZ5 trunk r1434


Fusion entre la version r1453 de la branche de développement LMDZ5V1.0-dev
et le tronc LMDZ5 (r1434)

Location:
LMDZ5/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk

  • LMDZ5/trunk/libf/dyn3d/friction.F

    r1403 r1454  
    66
    77      USE control_mod
    8  
     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     
    915      IMPLICIT NONE
    1016
    11 c=======================================================================
    12 c
    13 c
    14 c   Objet:
    15 c   ------
    16 c
    17 c  ***********
    18 c    Friction
    19 c  ***********
    20 c
    21 c=======================================================================
     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!=======================================================================
    2228
    2329#include "dimensions.h"
     
    2531#include "comgeom2.h"
    2632#include "comconst.h"
     33#include "iniprint.h"
     34#include "academic.h"
    2735
    28       REAL pdt
     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
    2943      REAL modv(iip1,jjp1),zco,zsi
    3044      REAL vpn,vps,upoln,upols,vpols,vpoln
    3145      REAL u2(iip1,jjp1),v2(iip1,jjm)
    32       REAL ucov( iip1,jjp1,llm ),vcov( iip1,jjm,llm )
    33       INTEGER  i,j
    34       REAL cfric
    35       parameter (cfric=1.e-5)
     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
    3663
    37 
     64      if (friction_type.eq.0) then
    3865c   calcul des composantes au carre du vent naturel
    3966      do j=1,jjp1
     
    96123         vcov(iip1,j,1)=vcov(1,j,1)
    97124      enddo
     125      endif ! of if (friction_type.eq.0)
    98126
     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     
    99134      RETURN
    100135      END
Note: See TracChangeset for help on using the changeset viewer.