Changeset 3466 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Oct 21, 2024, 5:42:40 PM (4 weeks ago)
Author:
emillour
Message:

Mars PCM:
More tidying in aeronomars:

  • remove unused "inv.F" and remove "dtridgl.F" which is not used here and is a duplicate of the "dtridgl" routine in phymars/swr_toon.F
  • turn aeronomars routines to modules, for those which aren't in modules yet.

EM

Location:
trunk/LMDZ.MARS
Files:
2 deleted
19 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3465 r3466  
    47214721- Small update in "analyse_netcdf.py".
    47224722- Putting the 1D launching scripts back to the "deftank" folder.
     4723
     4724== 21/10/2024 == EM
     4725More tidying in aeronomars:
     4726- remove unused "inv.F" and remove "dtridgl.F" which is not used here and
     4727  is a duplicate of the "dtridgl" routine in phymars/swr_toon.F
     4728- turn aeronomars routines to modules, for those which aren't in modules yet.
  • trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90

    r3464 r3466  
    3232      use comcstfi_h, only: pi
    3333      use chemthermos_mod, only: chemthermos
     34      use chemthermos_readini_mod, only: chemthermos_readini
    3435      use photochemistry_mod, only: photochemistry
     36      use deposition_mod, only: deposition
     37      use perosat_mod, only: perosat
    3538      use chemistrydata_mod, only: read_phototable
    3639      use photolysis_mod, only: init_photolysis, nphot
  • trunk/LMDZ.MARS/libf/aeronomars/chemthermos_readini.F

    r1266 r3466  
     1      module chemthermos_readini_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine chemthermos_readini
    28
     
    2632      else
    2733         write(*,*)
    28          write(*,*) 'Cannot find file chemthermos_reactionrates.def'
    29          stop
     34         call abort_physic("chemthermos_readini",
     35     &               'Cannot find file chemthermos_reactionrates.def',1)
    3036      endif
    3137     
    32       end
     38      end subroutine chemthermos_readini
     39
     40      end module chemthermos_readini_mod
  • trunk/LMDZ.MARS/libf/aeronomars/conduction.F

    r3158 r3466  
    1        SUBROUTINE conduction(ngrid,nlayer,ptimestep,pplay,pplev,pt,pdt,
     1      MODULE conduction_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
     7      SUBROUTINE conduction(ngrid,nlayer,ptimestep,pplay,pplev,pt,pdt,
    28     $                   tsurf,zzlev,zzlay,zdtconduc)
    39
     
    162168      enddo ! of do ig=1,ngrid
    163169
    164       RETURN
    165       END
     170      END SUBROUTINE conduction
     171     
     172      END MODULE conduction_mod
  • trunk/LMDZ.MARS/libf/aeronomars/deposition.F

    r1266 r3466  
     1      module deposition_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine deposition(ngrid, nlayer, nq,
    28     &                      ig, ig_vl1, pplay, pplev, zzlay, zzlev,
     
    173179c     end if
    174180c
    175       return
    176       end
     181      end subroutine deposition
     182
     183      end module deposition_mod
  • trunk/LMDZ.MARS/libf/aeronomars/inichim_newstart.F90

    r2672 r3466  
    1313      USE datafile_mod, ONLY: datadir
    1414      use dust_param_mod, only: doubleq, submicron, dustbin
     15      use intrplf_mod, only: intrplf
    1516      implicit none
    1617
  • trunk/LMDZ.MARS/libf/aeronomars/intrplf.F

    r38 r3466  
     1      MODULE intrplf_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17c******************************************************
    28      SUBROUTINE intrplf(x,y,xd,yd,nd)
     
    915c --------------------
    1016c  Arguments :
    11       real x,y
    12       real xd(nd),yd(nd)
    13       integer nd
     17      real,intent(in) :: x
     18      real,intent(out) :: y
     19      real,intent(in) :: xd(nd),yd(nd)
     20      integer,intent(in) :: nd
    1421c  internal
    1522      integer i,j
     
    3946 
    4047 99   continue
    41       return
    42       end                   
     48
     49      END SUBROUTINE intrplf
     50
     51      END MODULE intrplf_mod
  • trunk/LMDZ.MARS/libf/aeronomars/moldiff.F

    r3158 r3466  
     1      module moldiff_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine moldiff(ngrid,nlayer,nq,
    28     &                   pplay,pplev,pt,pdt,pq,pdq,ptimestep,
     
    814     &                      igcm_h2o_vap, mmol
    915      use conc_mod, only: rnew, mmean
    10       USE comcstfi_h
     16      use comcstfi_h, only: g
     17      use moldiffcoeff_mod, only: moldiffcoeff
    1118      implicit none
    1219
     
    452459      enddo             ! ig loop
    453460
    454       return
    455       end
     461      end subroutine moldiff
    456462
    457463c    ********************************************************************
     
    462468c      parameter (nmax=100)
    463469c      dimension gam(nmax),a(n),b(n),c(n),r(n),u(n)
    464       real gam(n),a(n),b(n),c(n),r(n),u(n)
     470      integer,intent(in) :: n
     471      real,intent(in) :: a(n),b(n),c(n),r(n)
     472      real,intent(out) :: u(n)
     473      real :: gam(n),bet
     474      integer :: j
    465475      if(b(1).eq.0.)then
    466476        stop 'tridag_sp: error: b(1)=0 !!! '
     
    468478      bet=b(1)
    469479      u(1)=r(1)/bet
    470       do 11 j=2,n
     480      do j=2,n
    471481        gam(j)=c(j-1)/bet
    472482        bet=b(j)-a(j)*gam(j)
     
    475485        endif
    476486        u(j)=(r(j)-a(j)*u(j-1))/bet
    477 11    continue
    478       do 12 j=n-1,1,-1
     487      enddo
     488      do j=n-1,1,-1
    479489        u(j)=u(j)-gam(j+1)*u(j+1)
    480 12    continue
    481       return
    482       end
     490      enddo
     491
     492      end subroutine tridag_sp
    483493
    484494c    ********************************************************************
     
    518528        B(I)=SUM/A(I,I)
    51952914    CONTINUE
    520       RETURN
    521       END
     530
     531      END SUBROUTINE LUBKSB_SP
    522532
    523533c    ********************************************************************
     
    603613      IF(A(N,N).EQ.0.)A(N,N)=TINY
    604614      ierr =0
    605       RETURN
    606       END
    607 
     615
     616      END SUBROUTINE LUDCMP_SP
     617
     618      end module moldiff_mod
  • trunk/LMDZ.MARS/libf/aeronomars/moldiffcoeff.F

    r2615 r3466  
     1      module moldiffcoeff_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine moldiffcoeff(dij)
    28
     
    218224      close(56)
    219225
    220 
    221       return   
    222       end
     226      end subroutine moldiffcoeff
     227
     228      end module moldiffcoeff_mod
  • trunk/LMDZ.MARS/libf/aeronomars/molvis.F

    r3158 r3466  
    1        SUBROUTINE molvis(ngrid,nlayer,ptimestep,
     1      MODULE molvis_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6
     7      SUBROUTINE molvis(ngrid,nlayer,ptimestep,
    28     &            pplay,pplev,pt,pdteuv,pdtconduc
    39     $           ,pvel,tsurf,zzlev,zzlay,zdvelmolvis)
     
    176182      ENDDO             ! boucle sur ngrid
    177183
    178       RETURN
    179       END
     184      END SUBROUTINE molvis
     185
     186      END MODULE molvis_mod
  • trunk/LMDZ.MARS/libf/aeronomars/param_read.F

    r2610 r3466  
     1      module param_read_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine param_read
    28
     
    422428      call bcast(p2)
    423429
    424       return
    425 
    426 
    427       end
    428 
     430
     431      end subroutine param_read
     432
     433      end module param_read_mod
  • trunk/LMDZ.MARS/libf/aeronomars/param_read_e107.F

    r2921 r3466  
     1      module param_read_e107_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine param_read_e107
    28
     
    547553
    548554
    549       return
    550 
    551 
    552       end
    553 
     555      end subroutine param_read_e107
     556
     557      end module param_read_e107_mod
  • trunk/LMDZ.MARS/libf/aeronomars/perosat.F

    r2615 r3466  
     1      MODULE perosat_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE perosat(ngrid,nlayer,nq,ig, ptimestep,
    28     $                   pplev, pplay, zt,
     
    143149        end do
    144150
    145       RETURN
    146       END
     151      END SUBROUTINE perosat
     152     
     153      END MODULE perosat_mod
  • trunk/LMDZ.MARS/libf/aeronomars/photochemistry.F90

    r3464 r3466  
    3131use jthermcalc_e107_mod, only: jthermcalc_e107
    3232use paramfoto_compact_mod, only: phdisrate
     33use photolysis_module, only: photolysis
     34use photolysis_online_mod, only: photolysis_online
    3335
    3436implicit none
  • trunk/LMDZ.MARS/libf/aeronomars/photolysis.F90

    r3012 r3466  
     1      module photolysis_module
     2     
     3      implicit none
     4     
     5      contains
     6     
    17!==========================================================================
    28
     
    340346      end do
    341347
    342       return
    343       end
     348      end subroutine photolysis
    344349
    345350!*****************************************************************
     351
     352      end module photolysis_module
  • trunk/LMDZ.MARS/libf/aeronomars/photolysis_online.F

    r2968 r3466  
     1      module photolysis_online_mod
     2     
     3      implicit none
     4     
     5      contains
     6
    17!==============================================================================
    28
     
    15641570
    15651571      end subroutine photolysis_online
     1572     
     1573      end module photolysis_online_mod
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r2615 r3466  
     1      module surfacearea_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17      subroutine surfacearea(ngrid, nlay, naerkind, ptimestep,
    28     $                       pplay, pzlay,
     
    126132     $            "micron2 cm-3",3,surfice*1.e6)
    127133
    128       end
     134      end subroutine surfacearea
     135
     136      end module surfacearea_mod
  • trunk/LMDZ.MARS/libf/aeronomars/thermosphere.F

    r3464 r3466  
    1919      use moldiff_MPF_mod, only: moldiff_MPF ! new molecular diffusion scheme
    2020      use euvheat_mod, only: euvheat
     21      use conduction_mod, only: conduction
     22      use molvis_mod, only: molvis
    2123      use conc_mod, only: rnew, cpnew
    2224      USE comcstfi_h, only: r, cpp
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3393 r3466  
    2929      use nlthermeq_mod, only: nlthermeq
    3030      use thermosphere_mod, only: thermosphere
     31      use param_read_e107_mod, only: param_read_e107
    3132      use tracer_mod, only: noms, mmol, igcm_co2, igcm_n2, igcm_co2_ice,
    3233     &                      igcm_co, igcm_o, igcm_h2o_vap, igcm_h2o_ice,
     
    6263      use nirdata_mod, only: NIR_leedat
    6364      use nirco2abs_mod, only: nirco2abs
     65      use surfacearea_mod, only: surfacearea
    6466      use slope_mod, only: theta_sl, psi_sl, getslopes, param_slope
    6567      use conc_mod, only: init_r_cp_mu, update_r_cp_mu_ak, rnew,
Note: See TracChangeset for help on using the changeset viewer.