Ignore:
Timestamp:
Apr 4, 2018, 8:04:13 AM (7 years ago)
Author:
emillour
Message:

Mars GCM:

  • Forgotten in previous commit: gwprofil.F -> gwprofil_mod.F (here also the

size of an argument, rho, was incorrect in caller orodrag).

  • Turned newsedim.F into a module newsedim_mod.F
  • Adapted co2cloud.F and improvedCO2clouds.F to not use "newunit" to open file

(it is perfectly legitimate F2008 Fortran, but older compiler such as gfortran
on local LMD machines are not there yet).
EM

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
4 edited
2 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/callsedim.F

    r1779 r1913  
    1313     &                      igcm_ccnco2_mass, igcm_ccnco2_number,
    1414     &                      igcm_co2_ice
    15       USE comcstfi_h
     15      USE newsedim_mod, ONLY: newsedim
     16      USE comcstfi_h, ONLY: g
    1617      IMPLICIT NONE
    1718
     
    3738c   -------------
    3839     
    39 #include "callkeys.h"
     40      include "callkeys.h"
    4041
    4142c
     
    371372         
    372373               call newsedim(ngrid,nlay,1,1,ptimestep,
    373      &         pplev,masse,epaisseur,zt,rd(ir),rho_dust,qr(1,1,ir),
     374     &         pplev,masse,epaisseur,zt,rd(ir),(/rho_dust/),qr(1,1,ir),
    374375     &         wq,0.5)
    375376
  • trunk/LMDZ.MARS/libf/phymars/co2cloud.F

    r1911 r1913  
    1818     &     rho_dust, nuiceco2_sed, nuiceco2_ref,
    1919     &     rho_ice_co2,r3n_q,rho_ice,nuice_sed
    20      
     20      USE newsedim_mod, ONLY: newsedim
    2121      IMPLICIT NONE
    2222
     
    156156      double precision :: Qtemp
    157157      double precision :: ltemp1(10000),ltemp2(10000)
    158       integer :: nelem,lebon1,lebon2,uQext
     158      integer :: nelem,lebon1,lebon2
     159      integer,parameter :: uQext=555
    159160      DOUBLE PRECISION n_aer(nbinco2_cld),Rn,No,n_derf,dev2
    160161      DOUBLE PRECISION Qext1bins2(ngrid,nlay)   
     
    254255           STOP
    255256        endif
    256         open(newunit=uQext,file=trim(datafile)//
     257!        open(newunit=uQext,file=trim(datafile)//
     258        open(unit=uQext,file=trim(datafile)//
    257259     &       '/optprop_co2ice_1mic.dat'
    258260     &       ,FORM='formatted')
  • trunk/LMDZ.MARS/libf/phymars/gwprofil_mod.F

    r1911 r1913  
     1      MODULE gwprofil_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE GWPROFIL
    28     *         ( klon, klev
     
    211217 531  CONTINUE       
    212218
    213       RETURN
    214       END
     219      END SUBROUTINE GWPROFIL
     220
     221      END MODULE gwprofil_mod
  • trunk/LMDZ.MARS/libf/phymars/improvedCO2clouds.F

    r1911 r1913  
    167167      integer nelem,lebon1,lebon2
    168168      double precision :: ltemp1(130),ltemp2(130)
    169       integer ibin,uMeteor,j
     169      integer ibin,j
     170      integer,parameter :: uMeteor=666
    170171
    171172      IF (firstcall) THEN
     
    254255           endif
    255256!used Variables
    256            open(newunit=uMeteor,file=trim(datafile)//
     257!           open(newunit=uMeteor,file=trim(datafile)//
     258           open(unit=uMeteor,file=trim(datafile)//
    257259     &          '/Meteo_flux_Plane.dat'
    258260     &          ,FORM='formatted')
  • trunk/LMDZ.MARS/libf/phymars/newsedim_mod.F

    r1911 r1913  
     1      MODULE newsedim_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6
    17      SUBROUTINE newsedim(ngrid,nlay,naersize,nrhosize,ptimestep,
    28     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,beta)
    3       USE comcstfi_h
     9      USE comcstfi_h, ONLY: r,g
    410      IMPLICIT NONE
    511
     
    209215
    210216
    211       RETURN
    212       END
    213 
     217      END SUBROUTINE newsedim
     218     
     219      END MODULE newsedim_mod
     220
  • trunk/LMDZ.MARS/libf/phymars/orodrag_mod.F

    r1912 r1913  
    7878      use dimradmars_mod, only: ndlo2
    7979      USE gwstress_mod, ONLY: gwstress
     80      USE gwprofil_mod, ONLY: gwprofil
    8081      USE comcstfi_h, ONLY: g, cpp
    8182      implicit none
     
    123124      integer ji,jk,jl,klevm1,ilevp1
    124125C      real gkwake
    125       real ztmst,pvar(NDLO2,4),ztauf,zrtmst,zdelp,zb,zc,zbet
     126      real ztmst,pvar(NDLO2,4),ztauf(NDLO2,klev+1)
     127      real zrtmst,zdelp,zb,zc,zbet
    126128      real zconb,zabsv,zzd1,ratio,zust,zvst,zdis,ztemp
    127129C
Note: See TracChangeset for help on using the changeset viewer.