Ignore:
Timestamp:
Jul 24, 2024, 1:17:08 PM (4 months ago)
Author:
abarral
Message:

Rename modules in misc from *_mod > lmdz_*
Put cbrt.f90, ch*.f90, pch*.f90 in new lmdz_libmath_pch.f90

Location:
LMDZ6/branches/Amaury_dev/libf/dyn3d_common
Files:
22 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/com_io_dyn_mod.F90

    r5099 r5113  
    44module com_io_dyn_mod
    55
    6   implicit none
     6  IMPLICIT NONE
    77
    88! Names of various files for outputs (in the dynamics)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/conf_dat_m.F90

    r5099 r5113  
    2424!  * interbar is TRUE for barycentric interpolation.
    2525!-------------------------------------------------------------------------------
    26   USE assert_eq_m, ONLY: assert_eq
     26  USE lmdz_assert_eq, ONLY: assert_eq
    2727  IMPLICIT NONE
    2828!-------------------------------------------------------------------------------
     
    128128!  * interbar is TRUE for barycentric interpolation.
    129129!-------------------------------------------------------------------------------
    130   USE assert_eq_m, ONLY: assert_eq
     130  USE lmdz_assert_eq, ONLY: assert_eq
    131131  IMPLICIT NONE
    132132!-------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/disvert.F90

    r5103 r5113  
    55  use ioipsl, only: getin
    66  use new_unit_m, only: new_unit
    7   use assert_m, only: assert
     7  use lmdz_assert, only: assert
    88  USE comvert_mod, ONLY: ap, bp, aps, bps, nivsigs, nivsig, dpres, presnivs, &
    99                         pseudoalt, pa, preff, scaleheight, presinter
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/disvert_noterre.f90

    r5105 r5113  
    295295
    296296
    297   implicit none
     297  IMPLICIT NONE
    298298  real :: x1, x2, sig,pa,preff, newsig, F
    299299  integer :: j
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/fxhyp_m.F90

    r5101 r5113  
    1818    ! 1., taux=0., clon=0.) est à - 180 degrés.
    1919
    20     use arth_m, only: arth
     20    use lmdz_arth, only: arth
    2121    use invert_zoom_x_m, only: invert_zoom_x, nmax
    2222    use nrtype, only: pi, pi_d, twopi, twopi_d, k8
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gr_int_dyn.f90

    r5105 r5113  
    33
    44SUBROUTINE gr_int_dyn(champin,champdyn,iim,jp1)
    5   implicit none
     5  IMPLICIT NONE
    66  !=======================================================================
    77  !   passage d'un champ interpole a un champ sur grille scalaire
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inigrads.f90

    r5105 r5113  
    55        , dt, file, titlel)
    66
    7   implicit none
     7  IMPLICIT NONE
    88
    99  integer :: if, im, jm, lm, i, j, l
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initdynav.F90

    r5103 r5113  
    1111  USE temps_mod, ONLY: itau_dyn
    1212 
    13   implicit none
     13  IMPLICIT NONE
    1414
    1515
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initfluxsto.f90

    r5105 r5113  
    1111  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    1212
    13   implicit none
     13  IMPLICIT NONE
    1414
    1515  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inithist.F90

    r5103 r5113  
    1111  USE temps_mod, ONLY: itau_dyn
    1212
    13   implicit none
     13  IMPLICIT NONE
    1414
    1515  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inter_barxy_m.F90

    r5101 r5113  
    66  ! Authors: Robert SADOURNY, Phu LE VAN, Lionel GUEZ
    77
    8   implicit none
    9 
    10   private
     8  IMPLICIT NONE
     9
     10  PRIVATE
    1111  public inter_barxy
    1212
     
    1515  SUBROUTINE inter_barxy(dlonid, dlatid, champ, rlonimod, rlatimod, champint)
    1616
    17     use assert_eq_m, only: assert_eq
    18     use assert_m, only: assert
     17    use lmdz_assert_eq, only: assert_eq
     18    use lmdz_assert, only: assert
    1919
    2020    include "dimensions.h"
     
    117117    !      ( Les abscisses sont exprimees en degres)
    118118
    119     use assert_eq_m, only: assert_eq
     119    use lmdz_assert_eq, only: assert_eq
    120120
    121121    IMPLICIT NONE
     
    299299    ! L'indice 1 correspond à l'interface maille 1 -- maille 2.
    300300
    301     use assert_m, only: assert
     301    use lmdz_assert, only: assert
    302302
    303303    IMPLICIT NONE
     
    373373    ! Finally, the procedure adds 90° as the last value of the array.
    374374
    375     use assert_eq_m, only: assert_eq
     375    use lmdz_assert_eq, only: assert_eq
    376376    use comconst_mod, only: pi
    377377
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/interpost.f90

    r5105 r5113  
    44  SUBROUTINE interpost(q,qppm)
    55
    6    implicit none
     6   IMPLICIT NONE
    77
    88
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/interpre.f90

    r5105 r5113  
    99  USE comvert_mod, ONLY: ap, bp
    1010
    11    implicit none
     11   IMPLICIT NONE
    1212
    1313  include "dimensions.h"
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/invert_zoom_x_m.F90

    r5103 r5113  
    11module invert_zoom_x_m
    22
    3   implicit none
     3  IMPLICIT NONE
    44
    55  INTEGER, PARAMETER:: nmax = 30000
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/iso_verif_dyn.f90

    r5105 r5113  
    11  function iso_verif_noNaN_nostop(x,err_msg)
    2     implicit none
    3     ! ! si x est NaN, on affiche message
    4     ! ! d'erreur et return 1 si erreur
     2    IMPLICIT NONE
     3    ! si x est NaN, on affiche message
     4    ! d'erreur et return 1 si erreur
    55
    6     ! ! input:
     6    ! input:
    77    real :: x
    88    character(len=*) :: err_msg ! message d''erreur à afficher
    99
    10     ! ! output
     10    ! output
    1111    real :: borne
    1212    parameter (borne=1e19)
     
    2727  function iso_verif_egalite_nostop &
    2828          (a,b,err_msg)
    29     implicit none
    30     ! ! compare a et b. Si pas egal, on affiche message
    31     ! ! d'erreur et stoppe
    32     ! ! pour egalite, on verifie erreur absolue et arreur relative
     29    IMPLICIT NONE
     30    ! compare a et b. Si pas egal, on affiche message
     31    ! d'erreur et stoppe
     32    ! pour egalite, on verifie erreur absolue et arreur relative
    3333
    34     ! ! input:
     34    ! input:
    3535    real :: a, b
    3636    character(len=*) :: err_msg ! message d''erreur à afficher
    3737
    38     ! ! locals
     38    ! locals
    3939    real :: errmax ! erreur maximale en absolu.
    4040    real :: errmaxrel ! erreur maximale en relatif autorisée
     
    4242    parameter (errmaxrel=1e-3)
    4343
    44     ! ! output
     44    ! output
    4545    integer :: iso_verif_egalite_nostop
    4646
     
    6565          (x,iso,q,err_msg)
    6666    USE infotrac, ONLY: isoName, getKey
    67     implicit none
     67    IMPLICIT NONE
    6868
    69     ! ! input:
     69    ! input:
    7070    real :: x,q
    7171    integer :: iso ! 2=HDO, 1=O18
    7272    character(len=*) :: err_msg ! message d''erreur à afficher
    7373
    74     ! ! locals
     74    ! locals
    7575    real :: qmin,deltaD
    7676    real :: deltaDmax,deltaDmin,tnat
     
    7878    parameter (deltaDmax=200.0,deltaDmin=-999.9)
    7979
    80     ! ! output
     80    ! output
    8181    integer :: iso_verif_aberrant_nostop
    8282
    8383    iso_verif_aberrant_nostop=0
    8484
    85     ! ! verifier que HDO est raisonable
     85    ! verifier que HDO est raisonable
    8686     if (q>qmin) then
    8787         IF(getKey('tnat', tnat, isoName(iso))) THEN
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/ppm3d.f90

    r5106 r5113  
    6565        JNP,j1,NLAY,AP,BP,PT,AE,fill,dum,Umax)
    6666
    67   implicit none
     67  IMPLICIT NONE
    6868
    6969  ! rajout de déclarations
     
    791791SUBROUTINE FZPPM(IMR,JNP,NLAY,j1,DQ,WZ,P,DC,DQDT,AR,AL,A6, &
    792792        flux,wk1,wk2,wz2,delp,KORD)
    793   implicit none
     793  IMPLICIT NONE
    794794  integer,parameter :: kmax = 150
    795795  real,parameter :: R23 = 2./3., R3 = 1./3.
     
    966966SUBROUTINE xtp(IMR,JNP,IML,j1,j2,JN,JS,PU,DQ,Q,UC, &
    967967        fx1,xmass,IORD)
    968   implicit none
     968  IMPLICIT NONE
    969969  integer :: IMR,JNP,IML,j1,j2,JN,JS,IORD
    970970  real :: PU,DQ,Q,UC,fx1,xmass
     
    10881088!
    10891089SUBROUTINE fxppm(IMR,IML,UT,P,DC,flux,IORD)
    1090   implicit none
     1090  IMPLICIT NONE
    10911091  integer :: IMR,IML,IORD
    10921092  real :: UT,P,DC,flux
     
    11511151!
    11521152SUBROUTINE xmist(IMR,IML,P,DC)
    1153   implicit none
     1153  IMPLICIT NONE
    11541154  integer :: IMR,IML
    11551155  real,parameter :: R24 = 1./24.
     
    11691169SUBROUTINE ytp(IMR,JNP,j1,j2,acosp,RCAP,DQ,P,VC,DC2 &
    11701170        ,ymass,fx,A6,AR,AL,JORD)
    1171   implicit none
     1171  IMPLICIT NONE
    11721172  integer :: IMR,JNP,j1,j2,JORD
    11731173  real :: acosp,RCAP,DQ,P,VC,DC2,ymass,fx,A6,AR,AL
     
    12391239!
    12401240subroutine  ymist(IMR,JNP,j1,P,DC,ID)
    1241   implicit none
     1241  IMPLICIT NONE
    12421242  integer :: IMR,JNP,j1,ID
    12431243  real,parameter :: R24 = 1./24.
     
    13211321!
    13221322SUBROUTINE fyppm(VC,P,DC,flux,IMR,JNP,j1,j2,A6,AR,AL,JORD)
    1323   implicit none
     1323  IMPLICIT NONE
    13241324  integer :: IMR,JNP,j1,j2,JORD
    13251325  real,parameter :: R3 = 1./3., R23 = 2./3.
     
    14011401!
    14021402  SUBROUTINE yadv(IMR,JNP,j1,j2,p,VA,ady,wk,IAD)
    1403     implicit none
     1403    IMPLICIT NONE
    14041404    integer :: IMR,JNP,j1,j2,IAD
    14051405    REAL :: p(IMR,JNP),ady(IMR,JNP),VA(IMR,JNP)
     
    14911491!
    14921492  SUBROUTINE xadv(IMR,JNP,j1,j2,p,UA,JS,JN,IML,adx,IAD)
    1493     implicit none
     1493    IMPLICIT NONE
    14941494    INTEGER :: IMR,JNP,j1,j2,JS,JN,IML,IAD
    14951495    REAL :: p(IMR,JNP),adx(IMR,JNP),qtmp(-IMR:IMR+IMR),UA(IMR,JNP)
     
    15841584!
    15851585SUBROUTINE lmtppm(DC,A6,AR,AL,P,IM,LMT)
    1586   implicit none
     1586  IMPLICIT NONE
    15871587  !
    15881588  ! A6 =  CURVATURE OF THE TEST PARABOLA
     
    16651665!
    16661666SUBROUTINE A2C(U,V,IMR,JMR,j1,j2,CRX,CRY,dtdx5,DTDY5)
    1667   implicit none
     1667  IMPLICIT NONE
    16681668  integer :: IMR,JMR,j1,j2
    16691669  real :: U(IMR,*),V(IMR,*),CRX(IMR,*),CRY(IMR,*),DTDX5(*),DTDY5
     
    16871687!
    16881688SUBROUTINE cosa(cosp,cose,JNP,PI,DP)
    1689   implicit none
     1689  IMPLICIT NONE
    16901690  integer :: JNP
    16911691  real :: cosp(*),cose(*),PI,DP
     
    17201720!
    17211721SUBROUTINE cosc(cosp,cose,JNP,PI,DP)
    1722   implicit none
     1722  IMPLICIT NONE
    17231723  integer :: JNP
    17241724  real :: cosp(*),cose(*),PI,DP
     
    18531853!
    18541854SUBROUTINE filcr(q,IMR,JNP,j1,j2,cosp,acosp,icr,tiny)
    1855   implicit none
     1855  IMPLICIT NONE
    18561856  integer :: IMR,JNP,j1,j2,icr
    18571857  real :: q(IMR,*),cosp(*),acosp(*),tiny
     
    19561956!
    19571957SUBROUTINE filns(q,IMR,JNP,j1,j2,cosp,acosp,ipy,tiny)
    1958   implicit none
     1958  IMPLICIT NONE
    19591959  integer :: IMR,JNP,j1,j2,ipy
    19601960  real :: q(IMR,*),cosp(*),acosp(*),tiny
     
    20432043!
    20442044SUBROUTINE filew(q,qtmp,IMR,JNP,j1,j2,ipx,tiny)
    2045   implicit none
     2045  IMPLICIT NONE
    20462046  integer :: IMR,JNP,j1,j2,ipx
    20472047  real :: q(IMR,*),qtmp(JNP,IMR),tiny
     
    21252125!
    21262126SUBROUTINE zflip(q,im,km,nc)
    2127   implicit none
     2127  IMPLICIT NONE
    21282128  ! This routine flip the array q (in the vertical).
    21292129  integer :: im,km,nc
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/principal_cshift_m.F90

    r5103 r5113  
    11module principal_cshift_m
    22
    3   implicit none
     3  IMPLICIT NONE
    44
    55contains
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/sortvarc.f90

    r5106 r5113  
    160160  END IF
    161161
    162   ! ! compute relative changes in etot,... (except if 'reference' values
    163   ! ! are zero, which can happen when using iniacademic)
     162  ! compute relative changes in etot,... (except if 'reference' values
     163  ! are zero, which can happen when using iniacademic)
    164164  if (etot0/=0) then
    165165    etot= etot/etot0
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/traceurpole.f90

    r5105 r5113  
    44    SUBROUTINE traceurpole(q,masse)
    55
    6       implicit none
     6      IMPLICIT NONE
    77
    88  include "dimensions.h"
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/ugeostr.F90

    r5103 r5113  
    1313  use comconst_mod, only: omeg, rad
    1414 
    15   implicit none
     15  IMPLICIT NONE
    1616
    1717  include "dimensions.h"
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writedynav.F90

    r5103 r5113  
    99  USE temps_mod, ONLY: itau_dyn
    1010
    11   implicit none
     11  IMPLICIT NONE
    1212
    1313  !   Ecriture du fichier histoire au format IOIPSL
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writehist.f90

    r5105 r5113  
    99  USE temps_mod, ONLY: itau_dyn
    1010
    11   implicit none
     11  IMPLICIT NONE
    1212
    1313  !
Note: See TracChangeset for help on using the changeset viewer.