!> subroutine dat2netcdf !! convertion of a ZBL file to an netcdf one !! @param nxx dimension along x !! @param nyy dimension along y !! @param filename !! @return Tab the value of Tab(nxx,nyy): Warning it is a real subroutine dat2netcdf(nxx,nyy,numcol,base_name,filename,fil_sortie) use netcdf use io_netcdf_grisli implicit none integer,intent(in) :: nxx !< dimension along x integer,intent(in) :: nyy !< dimension along y integer,intent(in) :: numcol !< column number character(len=*), intent(in) :: base_name !< base name of the variable to write character(len=20) :: base_name1 !< base name of the variable to write character(len=*),intent(in) :: filename !< name of the file character(len=*)::fil_sortie real*8,dimension(:,:),pointer :: Tab1,Tab2,Tab3 !< the array that is read and returned integer :: i,j !< working integers integer :: lx,ly !< nxx, nyy read in the file real,dimension(3) :: a !< working tab logical,save :: init integer ncid1,status1 character(len=20),dimension(2) :: dimnames2d !< dimensions pour netcdf pour tableau 2d if ((index(filename,'no') .eq. 0)) then if (.not. init) then status1 = nf90_create(trim(fil_sortie),NF90_WRITE,ncid1) ! ouverture du fichier status1 = nf90_close(ncid1) ! fermeture call init_ncdf(nxx,nyy,fil_sortie,dimnames2d) init= .true. end if open(22,file=trim(filename)) read(22,*) lx,ly if ((lx.ne.nxx).or.(ly.ne.nyy)) then write(6,*) 'wrong dimension of the file', filename write(6,*) 'in the file',lx,ly write(6,*) 'should be',nxx,nyy stop end if if (numcol .eq. 1) then allocate(Tab1(nxx,nyy)) do j=1,nyy do i=1,nxx read(22,*) a(1) Tab1(i,j)=a(1) end do end do base_name1= trim(base_name)//'_1' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab1,'double') deallocate(Tab1) endif if (numcol .eq. 2) then allocate(Tab1(nxx,nyy),Tab2(nxx,nyy)) do j=1,nyy do i=1,nxx read(22,*) a(1),a(2) Tab1(i,j)=a(1) Tab2(i,j)=a(2) end do end do base_name1= trim(base_name)//'_1' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab1,'double') base_name1=trim(base_name)//'_2' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab2,'double') deallocate(Tab1,Tab2) endif if (numcol .eq. 3) then allocate(Tab1(nxx,nyy),Tab2(nxx,nyy),Tab3(nxx,nyy)) do j=1,nyy do i=1,nxx read(22,*) a(1),a(2),a(3) Tab1(i,j)=a(1) Tab2(i,j)=a(2) Tab3(i,j)=a(3) end do end do base_name1= trim(base_name)//'_1' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab1,'double') base_name1=trim(base_name)//'_2' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab2,'double') base_name1=trim(base_name)//'_3' call Write_Ncdf_var(base_name1,dimnames2d,trim(fil_sortie),Tab3,'double') deallocate(Tab1,Tab2,Tab3) endif close(22) end if end subroutine dat2netcdf !> subroutine init_ncdf !! Initialise the netcdf file !! @param nxx dimension along x !! @param nyy dimension along y !! @param fil_sortie name of the file to initialise !! @ param dimnames2d dimensions for netcdf subroutine init_ncdf(nxx,nyy,fil_sortie,dimnames2d) use netcdf use io_netcdf_grisli implicit none integer,intent(in) :: nxx !< dimension along x integer,intent(in) :: nyy !< dimension along y character(len=*)::fil_sortie character(len=20),dimension(2) :: dimnames2d !< dimensions pour netcdf pour tableau 2d ! initialisation call write_ncdf_dim('x',trim(fil_sortie),nxx) ! dimensions des tableaux call write_ncdf_dim('y',trim(fil_sortie),nyy) ! ecriture d'un tableau tab 2D dimnames2d(1)='x' dimnames2d(2)='y' end subroutine init_ncdf !> subroutine lect_ncfile !! Read the nc file given !! @param varname The name of the variable to read !! @param filename File to read from !! @return Tab The value of Tab: Warning it is a real subroutine lect_ncfile(varname,Tab,filename) use netcdf use io_netcdf_grisli implicit none character(*),intent(in) :: varname !< Var name to read real,dimension(:,:),intent(inout) :: Tab !< Array to read in character(*),intent(in) :: filename !< File to read from real*8, dimension(:,:), pointer :: tabvar if(.not. associated(tabvar)) then allocate(tabvar(size(Tab,1),size(Tab,2))) else ! to nullify the pointer if undefined if (any(shape(tabvar).ne.(/size(Tab,1),size(Tab,2)/)) ) then tabvar => null() end if end if call read_ncdf_var(varname,filename,tabvar) Tab(:,:)= tabvar(:,:) !write(6,*) filename,varname,Tab(154,123) end subroutine lect_ncfile !> subroutine lect_input !! Read the file given !! @param numcol Column number !! @param basename Base name of the variable to read !! @param col The column to read !! @param filename File to read from !! @param ncfileout File out in case of .dat file to read !! @return tabvar The value of Tab(nxx,nyy): Warning it is a real subroutine lect_input (numcol,basename,col,tabvar,filename,ncfileout) !use netcdf !use io_netcdf_grisli implicit none integer,intent(in) :: numcol !< column number character(len=*), intent(in) :: basename !< base name of the variable to read integer,intent(in) :: col !< column 1->average, 2->minval 3->maxval ! ??? double emploi avec numcol real,dimension(:,:),intent(inout) :: tabvar !< array to read in the variable character(len=*),intent(in) :: filename !< name of the file to read character(len=*)::ncfileout !< name of the nc file to create interface !<<<<<<<<<<<<<<<<<<< subroutine lect_ncfile(varname,Tab,filename) character(*),intent(in) :: varname real,dimension(:,:),intent(inout) :: Tab character(*),intent(in) :: filename real*8, dimension(:,:), pointer :: tabvar end subroutine lect_ncfile end interface !<<<<<<<<<<<<<<<<<<< character(1) xcol write( xcol,'(i1)') col if (index(filename,'.dat') .ne.0) then ! file in is a .dat call dat2netcdf(size(tabvar,1),size(tabvar,2),numcol,basename,filename,ncfileout) call lect_ncfile(trim(basename)//'_'//xcol,tabvar,ncfileout) else if(index(filename,'.grd') .ne.0) then ! file in is a .grd call lect_ncfile('z',tabvar,filename) else ! file in is a .nc if(index(filename,'.nc') .ne.0) then call lect_ncfile(basename,tabvar,filename) endif endif endif end subroutine lect_input