Changeset 2910 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Mar 10, 2023, 6:05:41 PM (21 months ago)
Author:
emillour
Message:

Mars PCM:
Make subslope_mola a module and turn (extremely) large static arrays into
allocated ones and assume that the "mola64.nc" file is in "datadir" rather
than a hard coded location.
EM

Location:
trunk/LMDZ.MARS
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2909 r2910  
    39313931It can create start with 1, 5 or 7 subslope abd needs mola64.nc to do so.
    39323932Correction in compute_mesh_avg for nslope=1: no average is done only a copy.
     3933
     3934== 10/03/2023 == EM
     3935Make subslope_mola a module and turn (extremely) large static arrays into
     3936allocated ones and assume that the "mola64.nc" file is in "datadir" rather
     3937than a hard coded location.
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/newstart.F

    r2909 r2910  
    5555      use comslope_mod, ONLY: nslope,def_slope,def_slope_mean,
    5656     &             subslope_dist,end_comslope_h,ini_comslope_h
     57      USE subslope_mola_mod, ONLY: subslope_mola
     58     
    5759      implicit none
    5860
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/subslope_mola.F90

    r2909 r2910  
     1MODULE subslope_mola_mod
     2
     3IMPLICIT NONE
     4
     5CONTAINS
     6
    17SUBROUTINE subslope_mola(ngridmx,nslope,def_slope,subslope_dist)
    28
     
    612                                 north_east, north_west, &
    713                                 south_west, south_east
     14USE datafile_mod, ONLY: datadir
    815
    916IMPLICIT NONE
     
    1522      integer :: jjm_mola, iim_mola
    1623      parameter(jjm_mola=180*resol, iim_mola=2*jjm_mola)
    17       character*(*) dset ! Path to MCD datafiles
    18       parameter(dset ='/ccc/scratch/cont003/gen10391/vandemer/test_pem2_watercap/datadir/')
    1924      integer :: ierr
    2025! returned status code (==0 if OK)
    21       real :: theta_mola(iim_mola,jjm_mola)
     26      real,allocatable :: theta_mola(:,:) !theta_mola(iim_mola,jjm_mola)
    2227!ED18 : slopes inclination (see getslope.F90)
    23       real :: psi_mola(iim_mola,jjm_mola)
     28      real,allocatable :: psi_mola(:,:) !psi_mola(iim_mola,jjm_mola)
    2429!ED18 : slopes orientation (idem)     
    2530      REAL :: lon1, lon2, lat1, lat2 !bounds of the square
     
    3944      LOGICAL,PARAMETER :: rfz = .false.
    4045      INTEGER,PARAMETER :: igps = 1000 !first ig for RFZ location
    41 
     46     
     47      ! allocate big arrays
     48      allocate(theta_mola(iim_mola,jjm_mola),stat=ierr)
     49      if (ierr/=0) then
     50        write(*,*)"subslope_mola: allocation of theta_mola(:,:) failed!"
     51        stop
     52      endif
     53      allocate(psi_mola(iim_mola,jjm_mola),stat=ierr)
     54      if (ierr/=0) then
     55        write(*,*)"subslope_mola: allocation of psi_mola(:,:) failed!"
     56        stop
     57      endif
     58     
     59 
    4260!-------------Building of theta_mola and psi_mola
    43       CALL mola(dset,ierr,theta_mola,psi_mola,resol,iim_mola,jjm_mola)
     61      ! Assume that the mola file is to ben found in "datadir"
     62      CALL mola(trim(datadir)//"/",&
     63                ierr,theta_mola,psi_mola,resol,iim_mola,jjm_mola)
    4464
    4565!-------------Building of distribution
     
    83103              max_crit,max_lon,max_lat
    84104
     105     ! deallocate big arrays (this routine is only called once)
     106     deallocate(theta_mola,psi_mola)
     107     
    85108END SUBROUTINE subslope_mola
    86109
     
    159182                       trim(molafile)
    160183            endif
    161             ierr=15 !set appropriate error code
    162             return
     184            stop
    163185         endif
    164186
     
    174196            write(*,*)"Error in mola: <alt> not found"
    175197           endif
    176            ierr=16 ! set appropriate error code
    177            return
     198           stop
    178199         endif
    179200
     
    364385      INTEGER :: i_lon1, i_lon2
    365386      INTEGER :: j_lat1, j_lat2
    366       REAL :: crit !function
     387!      REAL :: crit !function
    367388      REAL :: val_crit !intermediate for evaluating the criterium
    368389      REAL :: max_crit !indicator for maximum slope criterium computed
     
    531552
    532553
    533 END SUBROUTINE slopes_stat
    534 
     554      CONTAINS
    535555
    536556!***********************************************************************
     
    543563
    544564      REAL crit
    545       REAL theta, psi
     565      REAL,INTENT(IN) :: theta, psi
    546566      real, parameter :: pi = acos(-1.)
    547567
     
    553573
    554574
     575END SUBROUTINE slopes_stat
     576
     577
     578
     579END MODULE subslope_mola_mod
Note: See TracChangeset for help on using the changeset viewer.