Ignore:
Timestamp:
07/27/12 16:04:22 (12 years ago)
Author:
ymipsl
Message:

externalize earth constant in run.def and add scalling factor functionnality

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/earth_const.f90

    r12 r32  
    33  USE math_const 
    44   
    5   REAL(rstd),PARAMETER :: radius=6.37122E6 
    6 !  REAL(rstd),PARAMETER :: radius=1. 
    7   REAL(rstd),PARAMETER :: g=9.80616 
     5  REAL(rstd),SAVE :: radius=6.37122E6 
     6  REAL(rstd),SAVE :: g=9.80616 
    87  REAL(rstd),PARAMETER :: daysec=86400 
    9 !  REAL(rstd),PARAMETER :: omega=2*Pi/daysec 
    10   REAL(rstd),PARAMETER :: omega=7.292E-5 
    11 !  REAL(rstd),PARAMETER :: omega=0 
    12   REAL(rstd),PARAMETER :: kappa=0.2857143 
    13   REAL(rstd),PARAMETER :: cpp=1004.70885 
    14   REAL(rstd),PARAMETER :: preff=101325. 
    15   REAL(rstd),PARAMETER :: pa=50000.   
     8  REAL(rstd),SAVE :: omega=7.292E-5 
     9  REAL(rstd),SAVE :: kappa=0.2857143 
     10  REAL(rstd),SAVE :: cpp=1004.70885 
     11  REAL(rstd),SAVE :: preff=101325. 
     12  REAL(rstd),SAVE :: pa=50000. 
     13  REAL(rstd),SAVE :: scale_factor=1. 
    1614 
     15CONTAINS 
     16   
     17  SUBROUTINE init_earth_const 
     18  USE ioipsl 
     19  IMPLICIT NONE 
     20  REAL(rstd) :: X=1 
     21   
     22    CALL getin("radius",radius) 
     23    CALL getin("g",g) 
     24    CALL getin("X",scale_factor) 
     25    CALL getin("omega",omega)   
     26    CALL getin("kappa",kappa)   
     27    CALL getin("cpp",cpp)   
     28    CALL getin("preff",preff)   
     29     
     30    radius=radius/scale_factor 
     31    omega=omega/scale_factor 
     32    PRINT *,"radius = ",radius 
     33     
     34  END SUBROUTINE init_earth_const 
     35   
     36   
    1737END MODULE earth_const 
    1838   
Note: See TracChangeset for help on using the changeset viewer.