Changeset 4216 for dynamico_lmdz


Ignore:
Timestamp:
Jan 7, 2020, 6:27:58 PM (5 years ago)
Author:
dubos
Message:

simple_physics : reworked comgeomfi

Location:
dynamico_lmdz/simple_physics/phyparam/param
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/phyparam/param/comgeomfi.F90

    r4212 r4216  
    33  SAVE
    44
    5   REAL, allocatable :: long(:), lati(:), area(:), &
    6        sinlon(:), coslon(:), sinlat(:), coslat(:)
    7   REAL :: totarea
    8   INTEGER :: ngridmax,nlayermx,nsoilmx
    9 !$OMP THREADPRIVATE(long,lati,area,sinlon,coslon,sinlat,coslat,totarea)
     5  REAL, ALLOCATABLE :: long(:), lati(:), sinlon(:), coslon(:), sinlat(:), coslat(:)
     6  INTEGER :: ngridmax, nlayermx, nsoilmx
     7!$OMP THREADPRIVATE(long,lati,sinlon,coslon,sinlat,coslat,totarea)
    108!$OMP THREADPRIVATE(ngridmax,nlayermx,nsoilmx)
    119
    1210CONTAINS
    1311   
    14   SUBROUTINE InitComgeomfi
    15     USE mod_phys_lmdz_para
    16     USE dimphy, ONLY : klon,klev
    17     USE geometry_mod, ONLY : latitude_deg,longitude_deg
    18    
    19     print*,'Dans initcomgeomfi '
    20     ngridmax=klon_omp
     12  SUBROUTINE init_comgeomfi(klon, klev, longitude, latitude)
     13    INTEGER, INTENT(IN) :: klon, klev
     14    REAL, INTENT(IN) :: longitude(klon), latitude(klon) ! in radians
     15    ngridmax=klon
    2116    nlayermx=klev
    2217    nsoilmx=10
    23     print*,'ngridmax,nlayermx',ngridmax,nlayermx
    24  
    25     allocate(long(klon_omp))
    26     allocate(lati(klon_omp))
    27     long=longitude_deg
    28     lati=latitude_deg
    29     allocate(area(klon_omp))
    30     allocate(sinlon(klon_omp))
    31     allocate(coslon(klon_omp))
    32     allocate(sinlat(klon_omp))
    33     allocate(coslat(klon_omp))
    34 
    35   END SUBROUTINE InitComgeomfi
     18    allocate(long(klon))
     19    allocate(lati(klon))
     20    allocate(sinlon(klon))
     21    allocate(coslon(klon))
     22    allocate(sinlat(klon))
     23    allocate(coslat(klon))
     24    long(:) = longitude(:)
     25    lati(:) = latitude(:)
     26    sinlat(:)=sin(lati(:))
     27    coslat(:)=cos(lati(:))
     28    sinlon(:)=sin(long(:))
     29    coslon(:)=cos(long(:))
     30  END SUBROUTINE init_comgeomfi
    3631 
    3732END MODULE comgeomfi
  • dynamico_lmdz/simple_physics/phyparam/param/iniphyparam.F

    r4215 r4216  
    6262 
    6363      REAL ptimestep
    64       INTEGER ig,ierr,offset
    6564 
    6665      EXTERNAL inifrict
    6766 
    6867      print*,'INIPHYPARAM'
    69       CALL InitComgeomfi
     68
     69      CALL init_comgeomfi(klon_omp, klev, longitude, latitude)
    7070
    7171      IF (klon.NE.klon_omp) THEN
    7272         PRINT*,'STOP in iniphyparam'
    73          PRINT*,'Probleme de dimenesions :'
     73         PRINT*,'Probleme de dimensions :'
    7474         PRINT*,'klon     = ',klon
    7575         PRINT*,'klon_omp   = ',klon_omp
     
    7979      IF (nlayer.NE.nlayermx) THEN
    8080         PRINT*,'STOP in iniphyparam'
    81          PRINT*,'Probleme de dimenesions :'
     81         PRINT*,'Probleme de dimensions :'
    8282         PRINT*,'nlayer     = ',nlayer
    8383         PRINT*,'nlayermx   = ',nlayermx
     
    8787      IF (ngrid.NE.klon_glo) THEN
    8888         PRINT*,'STOP in iniphyparam'
    89          PRINT*,'Probleme de dimenesions :'
     89         PRINT*,'Probleme de dimensions :'
    9090         PRINT*,'ngrid     = ',ngrid
    9191         PRINT*,'ngridmax   = ',klon_glo
    92 !        STOP
     92        STOP
    9393      ENDIF
    9494
     
    180180c-----------------------------------------------------------------------
    181181
    182       offset=klon_mpi_begin-1
    183 
    184182      print*,'latitude0  ohe',latitude(1:3),latitude(klon_omp)
    185 !      long(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
    186 !      lati(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
    187 !      area(1:klon_omp)=parea(offset+klon_omp_begin:offset+klon_omp_end)
    188       long(1:klon_omp)=longitude(1:klon_omp)
    189       lati(1:klon_omp)=latitude(1:klon_omp)
    190       area(1:klon_omp)=cell_area(1:klon_omp)
    191       totarea=sum(cell_area,ngrid)
    192183      print*,'OK17 AAA'
    193 
    194       sinlat(:)=sin(lati(:))
    195       coslat(:)=cos(lati(:))
    196       sinlon(:)=sin(long(:))
    197       coslon(:)=cos(long(:))
    198184
    199185      prad=planet_rad
Note: See TracChangeset for help on using the changeset viewer.