Ignore:
Timestamp:
Oct 24, 2024, 1:55:38 PM (37 hours ago)
Author:
abarral
Message:

Replace F77 netcdf library by F90 netcdf library

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/Dust/read_surface.f90

    r5268 r5270  
    1010       USE mod_phys_lmdz_para
    1111       USE iophy
    12        USE netcdf, ONLY: nf90_get_var
     12       USE netcdf, ONLY: nf90_inq_varid,nf90_noerr,nf90_get_var,nf90_nowrite,nf90_inq_varid,nf90_open
    1313       IMPLICIT NONE
    14 
    15        INCLUDE "netcdf.inc"
    1614       INCLUDE "dimensions.h"
    1715       INCLUDE "paramet.h"
     
    3129       real surfa_glo(klon_glo,5)
    3230!
    33        integer ncid
    34        integer varid
    35        real rcode
     31       integer ncid, varid, rcode
    3632       integer start(2),count(2),status
    3733       integer i,j,l,ig
     
    4339      real, dimension(jjp1) :: lats
    4440      real, dimension(nbp_lat) :: lats_glo
    45       real :: rcode2
    4641      integer, dimension(1) :: startj,endj
    4742!JE20140526>>
     
    5045
    5146       print*,'Lecture du fichier donnees_lisa.nc'
    52        ncid=NCOPN('donnees_lisa.nc',NCNOWRIT,rcode)
     47       ncid=nf90_open('donnees_lisa.nc',nf90_nowrite,rcode)
    5348
    5449!JE20140526<<: check if are inversed or not the latitude grid in donnes_lisa
     
    6257       if (i==4) aux4s='Latu'
    6358       if (i==5) aux4s='latU'
    64        status = NF_INQ_VARID (ncid, aux4s, rcode)
     59       status = nf90_inq_varid(ncid, aux4s, rcode)
    6560!       print *,'stat,i',status,i,outcycle,aux4s
    66 !       print *,'ifclause',status.NE. NF_NOERR ,outcycle == .false.
    67        IF ((.not.(status.NE. NF_NOERR) ).and.( .not. outcycle )) THEN
     61!       print *,'ifclause',status.NE. nf90_noerr ,outcycle == .false.
     62       IF ((.not.(status.NE. nf90_noerr) ).and.( .not. outcycle )) THEN
    6863         outcycle=.true.
    6964         latstr=aux4s
     
    7368!      endj(1)=jjp1
    7469      endj(1)=nbp_lat
    75       varid=NCVID(ncid,latstr,rcode)
     70      varid=nf90_inq_varid(ncid,latstr,rcode)
    7671
    7772          status = nf90_get_var(ncid, varid, lats_glo, startj, endj)
    7873!      print *,latstr,varid,status,jjp1,rcode
    79 !      IF (status .NE. NF_NOERR) print*,'NOOOOOOO'
     74!      IF (status .NE. nf90_noerr) print*,'NOOOOOOO'
    8075!      print *,lats
    8176!stop
     
    9085          varname=trim(name)//str1
    9186       print*,'lecture variable:',varname
    92           varid=NCVID(ncid,trim(varname),rcode)
    93 !          varid=NCVID(ncid,varname,rcode)
     87          varid=nf90_inq_varid(ncid,trim(varname),rcode)
     88!          varid=nf90_inq_varid(ncid,varname,rcode)
    9489
    9590!  dimensions pour les champs scalaires et le vent zonal
Note: See TracChangeset for help on using the changeset viewer.