Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (2 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/read_surface.F90

    r5116 r5117  
    1818       character*10 varname
    1919
    20        real tmp_dyn(iip1,jjp1)
    21        real tmp_dyn_glo(nbp_lon+1,nbp_lat)
     20       REAL tmp_dyn(iip1,jjp1)
     21       REAL tmp_dyn_glo(nbp_lon+1,nbp_lat)
    2222       REAL tmp_dyn_invers(iip1,jjp1)
    23        real tmp_dyn_invers_glo(nbp_lon+1,nbp_lat)
    24        real tmp_fi(klon)
    25        real tmp_fi_glo(klon_glo)
    26        real surfa(klon,5)
    27        real surfa_glo(klon_glo,5)
     23       REAL tmp_dyn_invers_glo(nbp_lon+1,nbp_lat)
     24       REAL tmp_fi(klon)
     25       REAL tmp_fi_glo(klon_glo)
     26       REAL surfa(klon,5)
     27       REAL surfa_glo(klon_glo,5)
    2828
    29        integer ncid
    30        integer varid
    31        integer rcode
    32        integer start(2),count(2),status
    33        integer i,j,l,ig
     29       INTEGER ncid
     30       INTEGER varid
     31       INTEGER rcode
     32       INTEGER start(2),count(2),status
     33       INTEGER i,j,l,ig
    3434       character*1 str1
    3535
    3636!JE20140526<<
    3737      character*4 ::  latstr,aux4s
    38       logical :: outcycle, isinversed
    39       real, dimension(jjp1) :: lats
    40       real, dimension(nbp_lat) :: lats_glo
     38      LOGICAL :: outcycle, isinversed
     39      REAL, DIMENSION(jjp1) :: lats
     40      REAL, DIMENSION(nbp_lat) :: lats_glo
    4141      REAL :: rcode2
    42       integer, dimension(1) :: startj,endj
     42      INTEGER, DIMENSION(1) :: startj,endj
    4343!JE20140526>>
    4444!$OMP MASTER
     
    5353      isinversed=.FALSE.
    5454      do i=1,5
    55        if (i==1) aux4s='latu'
    56        if (i==2) aux4s='LATU'
    57        if (i==3) aux4s='LatU'
    58        if (i==4) aux4s='Latu'
    59        if (i==5) aux4s='latU'
     55       IF (i==1) aux4s='latu'
     56       IF (i==2) aux4s='LATU'
     57       IF (i==3) aux4s='LatU'
     58       IF (i==4) aux4s='Latu'
     59       IF (i==5) aux4s='latU'
    6060       status = nf90_inq_varid (ncid, aux4s, rcode)
    6161!       print *,'stat,i',status,i,outcycle,aux4s
    6262!       print *,'ifclause',status.NE. nf90_noerr ,outcycle == .FALSE.
    63        IF ((.not.(status/= nf90_noerr) ).and.( .not. outcycle )) THEN
     63       IF ((.NOT.(status/= nf90_noerr) ).AND.( .NOT. outcycle )) THEN
    6464         outcycle=.TRUE.
    6565         latstr=aux4s
     
    7878
    7979! check if netcdf is latitude inversed or not.
    80       if (lats_glo(1)<lats_glo(2)) isinversed=.TRUE.
     80      IF (lats_glo(1)<lats_glo(2)) isinversed=.TRUE.
    8181! JE20140526>>
    8282
     
    118118!JE20140526<<
    119119!              CALL gr_dyn_fi(1, iip1, jjp1, klon, tmp_dyn_invers, tmp_fi)
    120            if (isinversed) THEN
     120           IF (isinversed) THEN
    121121                        CALL gr_dyn_fi(1, nbp_lon+1, nbp_lat, klon_glo, &
    122122   tmp_dyn_invers_glo, tmp_fi_glo)
Note: See TracChangeset for help on using the changeset viewer.