Changeset 4202


Ignore:
Timestamp:
Dec 20, 2019, 2:40:30 PM (5 years ago)
Author:
dubos
Message:

simple_physics : cleanup

Location:
dynamico_lmdz/simple_physics
Files:
2 added
1 deleted
5 edited
3 moved

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/config/LMDZ/build_lmdz_phyparam.sh

    r4181 r4202  
    3636}
    3737
     38function cmd_full()
     39{
     40    cd $LMDZ
     41    echo "./makelmdz_fcm -rrtm false  -v false -arch local -j 8 -p param -d 32x32x39 -full gcm" > compile.sh
     42    chmod +x compile.sh
     43    ./compile.sh
     44}
     45
    3846function cmd_()
    3947{
  • dynamico_lmdz/simple_physics/phyparam/param/coefdifv.F

    r4193 r4202  
    33     $               pcdzv,pcdzh)
    44      USE constlim, ONLY : ccdzh, cdzmin, cpgam, cdzconst, dgcdrag
    5       USE vdif_mod, ONLY : lmixmin
     5      USE turbulence, ONLY : lmixmin
    66      USE phys_const, ONLY : g
    77      IMPLICIT NONE
  • dynamico_lmdz/simple_physics/phyparam/param/inifrict.F90

    r4196 r4202  
    1       SUBROUTINE inifrict(timestep)
    2       USE comgeomfi, ONLY : ngridmax,nlayermx
    3       USE constlim
    4       USE phys_const
    5       IMPLICIT NONE
    6 c=======================================================================
    7 c
    8 c   Calcul des coefficients de ls diffusion verticale
    9 c
    10 c=======================================================================
    11 c-----------------------------------------------------------------------
    12 c   Declarations:
    13 c   -------------
    14      
    15 
    16 c   local:
    17 c   ------
    18 
    19       REAL dgrad,cpr,rl2,rrr,timestep
    20       INTEGER l,ij
    21 
    22 c-----------------------------------------------------------------------
    23 
    24       call initconstlim
    25 
    26       dtradia=timestep
    27       PRINT*,'DTPHYS',dtradia
    28       lmixmin=100.
    29       ais1    = 1.
    30       ais2    = ais1 - 1.
    31       print*,'ais1',ais1,'ais2',ais2
    32       cdzmin  = 1.e-6
    33       OPEN(99,file='cdzmin',status='old',err=9999)
    34       READ(99,*) cdzmin
    35 9999  CLOSE(99)
    36       PRINT*,'cdzmin=',cdzmin
    37 
    38       cpr     = cpp/ r
    39       ccdzh   = 2.5*g
    40 c!!!  cpgam   = 5.e-3*cpp
    41       cpgam=0.
    42 
    43 c-----------------------------------------------------------------------
    44 c   coefficient de diffusion dans l'atmosphere:
    45 c   -------------------------------------------
    46 
    47       rl2=lmixmin**2
    48       cdzconst(1)= 0.
    49       DO 15 l=1,nlayermx - 1
    50          cdzconst(l+1)= dtradia*g*g*cpr*rl2
    51          print*,'cdzconst(',l+1,')  =  ',cdzconst(l+1)
    52   15  CONTINUE
    53 
    54 c-----------------------------------------------------------------------
    55 c   couche limite de surface:
    56 c   -------------------------
    57 
    58       cdrat   = 2.e-3
    59       dgrad   = dtradia*g*cpp/r
    60       DO 16 ij = 1, ngridmax
    61          dgcdrag( ij ) = cdrat * dgrad
    62   16  CONTINUE
    63 
    64       RETURN
    65       END
     1      SUBROUTINE inifrict(timestep) 
     2      USE comgeomfi, ONLY : ngridmax,nlayermx 
     3      USE constlim 
     4      USE phys_const 
     5      IMPLICIT NONE 
     6!=======================================================================
     7!                                                                       
     8!   Calcul des coefficients de ls diffusion verticale                   
     9!                                                                       
     10!=======================================================================
     11!-----------------------------------------------------------------------
     12!   Declarations:                                                       
     13!   -------------                                                       
     14                                                                       
     15                                                                       
     16!   local:                                                             
     17!   ------                                                             
     18                                                                       
     19      REAL dgrad,cpr,rl2,rrr,timestep 
     20      INTEGER l,ij 
     21                                                                       
     22!-----------------------------------------------------------------------
     23                                                                       
     24      call initconstlim 
     25                                                                       
     26      dtradia=timestep 
     27      PRINT*,'DTPHYS',dtradia 
     28      lmixmin=100. 
     29      ais1    = 1. 
     30      ais2    = ais1 - 1. 
     31      print*,'ais1',ais1,'ais2',ais2 
     32      cdzmin  = 1.e-6 
     33      OPEN(99,file='cdzmin',status='old',err=9999) 
     34      READ(99,*) cdzmin 
     35 9999 CLOSE(99)
     36      PRINT*,'cdzmin=',cdzmin 
     37                                                                       
     38      cpr     = cpp/ r 
     39      ccdzh   = 2.5*g 
     40!!!!  cpgam   = 5.e-3*cpp                                               
     41      cpgam=0. 
     42                                                                       
     43!-----------------------------------------------------------------------
     44!   coefficient de diffusion dans l'atmosphere:                         
     45!   -------------------------------------------                         
     46                                                                       
     47      rl2=lmixmin**2 
     48      cdzconst(1)= 0. 
     49      DO 15 l=1,nlayermx - 1 
     50         cdzconst(l+1)= dtradia*g*g*cpr*rl2 
     51         print*,'cdzconst(',l+1,')  =  ',cdzconst(l+1) 
     52   15 END DO
     53                                                                       
     54!-----------------------------------------------------------------------
     55!   couche limite de surface:                                           
     56!   -------------------------                                           
     57                                                                       
     58      cdrat   = 2.e-3 
     59      dgrad   = dtradia*g*cpp/r 
     60      DO 16 ij = 1, ngridmax 
     61         dgcdrag( ij ) = cdrat * dgrad 
     62   16 END DO
     63                                                                       
     64      RETURN 
     65      END                                           
  • dynamico_lmdz/simple_physics/phyparam/param/iniphyparam.F

    r4192 r4202  
    1414      USE planet, ONLY : coefir, coefvis
    1515      USE astronomy
    16       USE vdif_mod, ONLY : lmixmin, emin_turb
     16      USE turbulence, ONLY : lmixmin, emin_turb
    1717      IMPLICIT NONE
    1818
  • dynamico_lmdz/simple_physics/phyparam/param/paramdef.F

    r4190 r4202  
    11      SUBROUTINE paramdef(ngrid,rnatur,albedo,inertie,emissiv,z0)
    22      USE comgeomfi, ONLY : lati,sinlat,coslat
    3       USE vdif_mod, ONLY : lmixmin, emin_turb
     3      USE turbulence, ONLY : lmixmin, emin_turb
    44      USE planet, ONLY : coefir, coefvis
    55      USE astronomy
  • dynamico_lmdz/simple_physics/phyparam/param/phyparam.F

    r4201 r4202  
    1313      USE planet
    1414      USE astronomy
    15       USE vdif_mod, ONLY : vdif
     15      USE turbulence, ONLY : vdif
    1616      USE solar, ONLY : solang, zenang, mucorr
    1717      USE radiative_sw, ONLY : sw
  • dynamico_lmdz/simple_physics/phyparam/physics/turbulence.F90

    r4199 r4202  
    1 MODULE vdif_mod
     1MODULE turbulence
    22 
    33#include "use_logging.h"
     
    444444  END SUBROUTINE vdif
    445445 
    446 END MODULE vdif_mod
     446END MODULE turbulence
Note: See TracChangeset for help on using the changeset viewer.