Ignore:
Timestamp:
Jul 23, 2024, 3:29:36 PM (8 weeks ago)
Author:
abarral
Message:

Handle CPP_INLANDSIS in lmdz_cppkeys_wrapper.F90
Remove obsolete key wrgrads_thermcell, _ADV_HALO, _ADV_HALLO, isminmax
Remove redundant uses of CPPKEY_INCA (thanks acozic)
Remove obsolete misc/write_field.F90
Remove unused ioipsl_* wrappers
Remove calls to WriteField_u with wrong signature
Convert .F -> .[fF]90
(lint) uppercase fortran operators
[note: 1d and iso still broken - working on it]

File:
1 edited

Legend:

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

    r5101 r5103  
    1212  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nptabij
    1313  INTEGER, SAVE :: itau_iophy
    14   LOGICAL :: check_dim = .false.
     14  LOGICAL :: check_dim = .FALSE.
    1515
    1616!$OMP THREADPRIVATE(itau_iophy)
     
    4343  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
    4444  USE print_control_mod, ONLY: prt_level,lunout
    45 #ifdef CPP_IOIPSL
    4645    USE ioipsl, ONLY: flio_dom_set
    47 #endif
    4846  use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init, using_xios
    4947    IMPLICIT NONE
     
    200198   
    201199#ifndef CPP_IOIPSL_NO_OUTPUT
    202     call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
     200    CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
    203201                      'APPLE',phys_domain_id)
    204202#endif
     
    324322    DO i=1,pim
    325323
    326 !    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
     324!    PRINT*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
    327325
    328326     plon_bounds(i,1)=rlon_glo(tabij(i)-1)
     
    346344     plat_bounds(i,2)=rlat_glo(tabij(i)+nbp_lon)
    347345
    348 !    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
    349 !    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat_glo(tabij(i)),plat_bounds(i,2)
     346!    PRINT*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
     347!    PRINT*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat_glo(tabij(i)),plat_bounds(i,2)
    350348
    351349    ENDDO
     
    370368
    371369    DO i=1,pim
    372 !    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
     370!    PRINT*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
    373371
    374372     plon_bounds(i,1)=zx_lon(ipt(i)-1,jpt(i))
     
    397395     ENDIF
    398396
    399 !    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon(tabij(i)),plon_bounds(i,2)
    400 !    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat(tabij(i)),plat_bounds(i,2)
     397!    PRINT*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon(tabij(i)),plon_bounds(i,2)
     398!    PRINT*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat(tabij(i)),plat_bounds(i,2)
    401399
    402400    ENDDO
     
    417415      ENDIF
    418416     ENDDO
    419 !    print*,'CFMIP_iophy mpi_rank npstn',mpi_rank,npstn
     417!    PRINT*,'CFMIP_iophy mpi_rank npstn',mpi_rank,npstn
    420418     IF(.NOT. ALLOCATED(nptabij)) THEN
    421419      ALLOCATE(nptabij(npstn))
     
    428426       npproc=npproc+1
    429427       nptabij(npproc)=tabij(ip)
    430 !      print*,'mpi_rank npproc ip plon plat tabij=',mpi_rank,npproc,ip, &
     428!      PRINT*,'mpi_rank npproc ip plon plat tabij=',mpi_rank,npproc,ip, &
    431429!      plon(ip),plat(ip),tabij(ip)
    432430       npplon(npproc)=plon(ip)
     
    439437!!! print qui sert a reordonner les points stations selon l'ordre CFMIP
    440438!!! ne pas enlever
    441         print*,'iophy_mpi rank ip lon lat',mpi_rank,ip,plon(ip),plat(ip)
     439        PRINT*,'iophy_mpi rank ip lon lat',mpi_rank,ip,plon(ip),plat(ip)
    442440!!!
    443441      ENDIF
     
    638636            var%description, var%unit, var%flag(iff), typeecrit)
    639637            IF (prt_level >= 10) THEN
    640               WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
     638              WRITE(lunout,*) 'histdef2d: CALL wxios_add_field_to_file var%name iff: ', &
    641639                              trim(var%name),iff
    642640            ENDIF
     
    753751          var%description, var%unit, var%flag(iff), typeecrit)
    754752            IF (prt_level >= 10) THEN
    755               WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
     753              WRITE(lunout,*) 'histdef3d: CALL wxios_add_field_to_file var%name iff: ', &
    756754                              trim(var%name),iff
    757755            ENDIF
     
    851849     ELSE
    852850      DO ip=1, npstn
    853 !     print*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
     851!     PRINT*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
    854852       IF(nptabij(ip)>=klon_mpi_begin.AND. &
    855853          nptabij(ip)<=klon_mpi_end) THEN
     
    975973  INTEGER :: ip
    976974  REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
    977   logical, save :: is_active = .true.
     975  logical, save :: is_active = .TRUE.
    978976
    979977  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy for ',trim(var%name)
     
    10191017        !$omp barrier
    10201018        !$omp master
    1021         is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1019        is_active = xios_field_is_active(var%name, at_current_timestep_arg=.FALSE.)
    10221020        !$omp end master
    10231021        !$omp barrier
     
    10441042
    10451043! La boucle sur les fichiers:
    1046       firstx=.true.
     1044      firstx=.TRUE.
    10471045
    10481046      IF (ok_all_xml) THEN
     
    10821080                      write(lunout,*)'Dans iophy histwrite2D,iff,var%name ',&
    10831081                                     iff,trim(var%name)                       
    1084                       write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
     1082                      write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, CALL xios_send_field"
    10851083                   ENDIF
    10861084                   IF (grid_type==regular_lonlat) THEN
     
    10981096                   ENDIF
    10991097
    1100                    firstx=.false.
     1098                   firstx=.FALSE.
    11011099                ENDIF
    11021100              ENDIF
     
    11111109!                        IF (iff == iff_beg) THEN
    11121110!                          IF (prt_level >= 10) THEN
    1113 !                            write(lunout,*)"histwrite2d_phy: .NOT.clef_stations(iff) and iff==iff_beg, call xios_send_field"
     1111!                            write(lunout,*)"histwrite2d_phy: .NOT.clef_stations(iff) and iff==iff_beg, CALL xios_send_field"
    11141112!                          ENDIF
    11151113!                          CALL xios_send_field(var%name, Field2d)
     
    11351133#ifndef CPP_IOIPSL_NO_OUTPUT
    11361134                       IF (prt_level >= 10) THEN
    1137                          write(lunout,*)"histwrite2d_phy: clef_stations(iff) and iff==iff_beg, call wxios_write_2D"
     1135                         write(lunout,*)"histwrite2d_phy: clef_stations(iff) and iff==iff_beg, CALL wxios_write_2D"
    11381136                       ENDIF
    11391137                       CALL histwrite(nid_files(iff),var%name,itau_iophy,fieldok,npstn,index2d)
     
    11851183  INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
    11861184  REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
    1187   logical, save :: is_active = .true.
     1185  logical, save :: is_active = .TRUE.
    11881186
    11891187  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name)
     
    12171215        !$omp barrier
    12181216        !$omp master
    1219         is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.)
     1217        is_active = xios_field_is_active(var%name, at_current_timestep_arg=.FALSE.)
    12201218        !$omp end master
    12211219        !$omp barrier
     
    12471245
    12481246! BOUCLE SUR LES FICHIERS
    1249     firstx=.true.
     1247    firstx=.TRUE.
    12501248
    12511249    IF (ok_all_xml) THEN
     
    12811279                  write(lunout,*)'Dans iophy, histwrite3D iff nlev klev firstx', &
    12821280                                  iff,nlev,klev, firstx                       
    1283                   write(lunout,*)'histwrite3d_phy: call xios_send_field for ', &
     1281                  write(lunout,*)'histwrite3d_phy: CALL xios_send_field for ', &
    12841282                                  trim(var%name), ' with iim jjm nlevx = ', &
    12851283                                  nbp_lon,jj_nb,nlevx
     
    12991297                ENDIF
    13001298
    1301                 firstx=.false.
     1299                firstx=.FALSE.
    13021300              ENDIF
    13031301            ENDIF
Note: See TracChangeset for help on using the changeset viewer.