From df45494b525e813d29fd8312d597aee239afedca Mon Sep 17 00:00:00 2001 From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr> Date: Tue, 10 Nov 2015 11:28:53 +0100 Subject: [PATCH] lfi2cdf: options are now stored in a structure, command line is read in Fortran instead of C (=> removed newmain.c) --- tools/lfi2cdf/Makefile | 2 +- tools/lfi2cdf/src/lfi2cdf.f90 | 105 ++++----- tools/lfi2cdf/src/mode_options.f90 | 340 +++++++++++++++++++++++++++++ tools/lfi2cdf/src/mode_util.f90 | 66 +++--- tools/lfi2cdf/src/newmain.c | 238 -------------------- 5 files changed, 415 insertions(+), 336 deletions(-) create mode 100644 tools/lfi2cdf/src/mode_options.f90 delete mode 100644 tools/lfi2cdf/src/newmain.c diff --git a/tools/lfi2cdf/Makefile b/tools/lfi2cdf/Makefile index d37681ce5..1fd60ec33 100644 --- a/tools/lfi2cdf/Makefile +++ b/tools/lfi2cdf/Makefile @@ -17,7 +17,7 @@ DIR_COMP = $(DIR_LIB)/COMPRESS LIBCOMP = $(DIR_COMP)/$(ARCH)/liblficomp.a -OBJS = newmain.o lfi2cdf.o modd_ncparam.o mode_dimlist.o fieldtype.o mode_util.o +OBJS = mode_options.o lfi2cdf.o modd_ncparam.o mode_dimlist.o fieldtype.o mode_util.o PROGS = lfi2cdf INC = -I$(DIR_OBJ) -DLFI_INT=$(LFI_INT) diff --git a/tools/lfi2cdf/src/lfi2cdf.f90 b/tools/lfi2cdf/src/lfi2cdf.f90 index ebe4f30b9..a66cc2cf4 100644 --- a/tools/lfi2cdf/src/lfi2cdf.f90 +++ b/tools/lfi2cdf/src/lfi2cdf.f90 @@ -1,14 +1,7 @@ -subroutine LFI2CDFMAIN(hinfile,iiflen,ooutname,houtfile,ioflen,hvarlist,ivlen,ocdf2cdf,olfi2cdf,olfilist,ohdf5,omerge,& - nb_levels,oreduceprecision,osplit,ocompress,compress_level) +program LFI2CDF + USE mode_options USE mode_util IMPLICIT NONE - INTEGER :: iiflen, ioflen, ivlen - INTEGER :: nb_levels !Number of vertical levels to merge (for LFI splitted files) - CHARACTER(LEN=iiflen) :: hinfile - CHARACTER(LEN=ioflen) :: houtfile - CHARACTER(LEN=ivlen) :: hvarlist - LOGICAL :: ooutname, ocdf2cdf, olfi2cdf, olfilist, ohdf5, omerge, oreduceprecision, osplit, ocompress - INTEGER :: compress_level INTEGER :: ibuflen INTEGER :: ji @@ -17,45 +10,30 @@ subroutine LFI2CDFMAIN(hinfile,iiflen,ooutname,houtfile,ioflen,hvarlist,ivlen,o INTEGER :: nbvar_calc ! number of variables to be computed from others INTEGER :: nbvar_tbw ! number of variables to be written INTEGER :: nbvar ! number of defined variables - INTEGER :: first_level, current_level, last_level + INTEGER :: first_level, current_level, last_level, nb_levels + CHARACTER(LEN=:),allocatable :: hvarlist TYPE(filelist_struct) :: infiles, outfiles TYPE(workfield), DIMENSION(:), POINTER :: tzreclist + type(option),dimension(:),allocatable :: options + character(len=:),allocatable :: hinfile, houtfile + integer :: runmode - !Remove level in the filename if merging LFI splitted files - if (.NOT.ooutname) then - if (omerge .AND. .NOT.osplit) then - houtfile=houtfile(1:len(houtfile)-9)//houtfile(len(houtfile)-3:) - end if - if (.NOT.omerge .AND. osplit) then - if (ohdf5) then - ji=4 - else - ji=3 - end if - houtfile=houtfile(1:len(houtfile)-ji) - end if - if (omerge .AND. osplit) then - if (ohdf5) then - ji=9 - else - ji=8 - end if - houtfile=houtfile(1:len(houtfile)-ji) - end if - end if - - CALL OPEN_FILES(infiles, outfiles, hinfile, houtfile, ocdf2cdf, olfi2cdf, olfilist, ohdf5, nbvar_infile, osplit) - IF (olfilist) return - - IF (olfi2cdf .OR. ocdf2cdf) THEN - IF (ivlen > 0) THEN + + call read_commandline(options,hinfile,houtfile,runmode) + + CALL OPEN_FILES(infiles, outfiles, hinfile, houtfile, nbvar_infile, options, runmode) + IF (options(OPTLIST)%set) return + + IF (runmode == MODELFI2CDF .OR. runmode == MODECDF2CDF) THEN + IF (options(OPTVAR)%set) THEN ! nbvar_tbr is computed from number of requested variables ! by counting commas, = and + nbvar_tbr = 0 nbvar_calc = 0 nbvar_tbw = 0 - DO ji=1,ivlen + hvarlist = options(OPTVAR)%cvalue + DO ji=1,len(hvarlist) IF (hvarlist(ji:ji) == ',' .OR.hvarlist(ji:ji) == '+') THEN nbvar_tbr = nbvar_tbr+1 END IF @@ -72,64 +50,66 @@ subroutine LFI2CDFMAIN(hinfile,iiflen,ooutname,houtfile,ioflen,hvarlist,ivlen,o END IF END IF - IF (olfi2cdf) THEN + IF (runmode == MODELFI2CDF) THEN ! Conversion LFI -> NetCDF !Standard treatment (one LFI file only) - IF (.not.omerge) THEN - CALL parse_infiles(infiles,hvarlist,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen) - IF (osplit) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,ohdf5) - CALL def_ncdf(outfiles,tzreclist,nbvar,oreduceprecision,omerge,osplit,ocompress,compress_level) - CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,osplit) + IF (.not.options(OPTMERGE)%set) THEN + CALL parse_infiles(infiles,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,options) + IF (options(OPTSPLIT)%set) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,options) + CALL def_ncdf(outfiles,tzreclist,nbvar,options) + CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,options) ELSE !Treat several LFI files and merge into 1 NC file !Determine first level (eg needed to find suffix of the variable name) read( hinfile(len(hinfile)-6:len(hinfile)-4) , "(I3)" ) first_level + nb_levels = options(OPTMERGE)%ivalue current_level = first_level last_level = first_level + nb_levels - 1 !Read 1st LFI file - CALL parse_infiles(infiles,hvarlist,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,current_level) - IF (osplit) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,ohdf5) + CALL parse_infiles(infiles,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,options,current_level) + IF (options(OPTSPLIT)%set) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,options) !Define NC variables - CALL def_ncdf(outfiles,tzreclist,nbvar,oreduceprecision,omerge,osplit,ocompress,compress_level) + CALL def_ncdf(outfiles,tzreclist,nbvar,options) DO current_level = first_level,last_level print *,'Treating level ',current_level IF (current_level/=first_level) THEN CALL open_split_lfifile_in(infiles,hinfile,current_level) - CALL read_data_lfi(infiles,hvarlist,nbvar,tzreclist,ibuflen,current_level) + CALL read_data_lfi(infiles,nbvar,tzreclist,ibuflen,current_level) END IF - CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,osplit,current_level) + CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,options,current_level) IF (current_level/=last_level) CALL close_files(infiles) END DO END IF - ELSE IF (ocdf2cdf) THEN + ELSE IF (runmode == MODECDF2CDF) THEN ! Conversion netCDF -> netCDF !Standard treatment (one netCDF file only) - IF (.not.omerge) THEN - CALL parse_infiles(infiles,hvarlist,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,current_level) - IF (osplit) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,ohdf5) - CALL def_ncdf(outfiles,tzreclist,nbvar,oreduceprecision,omerge,osplit,ocompress,compress_level) - CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,osplit) + IF (.not.options(OPTMERGE)%set) THEN + CALL parse_infiles(infiles,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,options,current_level) + IF (options(OPTSPLIT)%set) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,options) + CALL def_ncdf(outfiles,tzreclist,nbvar,options) + CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,options) ELSE !Treat several NC files and merge into 1 NC file !Determine first level (eg needed to find suffix of the variable name) read( hinfile(len(hinfile)-5:len(hinfile)-3) , "(I3)" ) first_level + nb_levels = options(OPTMERGE)%ivalue current_level = first_level last_level = first_level + nb_levels - 1 !Read 1st NC file - CALL parse_infiles(infiles,hvarlist,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,current_level) - IF (osplit) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,ohdf5) + CALL parse_infiles(infiles,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,options,current_level) + IF (options(OPTSPLIT)%set) call open_split_ncfiles_out(outfiles,houtfile,nbvar,tzreclist,options) !Define NC variables - CALL def_ncdf(outfiles,tzreclist,nbvar,oreduceprecision,omerge,osplit,ocompress,compress_level) + CALL def_ncdf(outfiles,tzreclist,nbvar,options) DO current_level = first_level,last_level print *,'Treating level ',current_level @@ -137,19 +117,18 @@ subroutine LFI2CDFMAIN(hinfile,iiflen,ooutname,houtfile,ioflen,hvarlist,ivlen,o CALL open_split_ncfile_in(infiles,hinfile,current_level) CALL update_varid_in(infiles,hinfile,tzreclist,nbvar,current_level) END IF - CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,osplit,current_level) + CALL fill_ncdf(infiles,outfiles,tzreclist,nbvar,ibuflen,options,current_level) IF (current_level/=last_level) CALL close_files(infiles) END DO END IF ELSE ! Conversion NetCDF -> LFI - CALL parse_infiles(infiles,hvarlist,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,current_level) + CALL parse_infiles(infiles,nbvar_infile,nbvar_tbr,nbvar_calc,nbvar_tbw,tzreclist,ibuflen,options,current_level) CALL build_lfi(infiles,outfiles,tzreclist,ibuflen) END IF CALL CLOSE_FILES(infiles) CALL CLOSE_FILES(outfiles) -end subroutine LFI2CDFMAIN - +end program LFI2CDF diff --git a/tools/lfi2cdf/src/mode_options.f90 b/tools/lfi2cdf/src/mode_options.f90 new file mode 100644 index 000000000..eeded3e0f --- /dev/null +++ b/tools/lfi2cdf/src/mode_options.f90 @@ -0,0 +1,340 @@ +module mode_options + implicit none + + integer,parameter :: nbavailoptions = 10 + integer,parameter :: TYPEUNDEF = -1, TYPEINT = 1, TYPELOG = 2, TYPEREAL = 3, TYPECHAR = 4 + integer,parameter :: MODEUNDEF = -11, MODECDF2CDF = 11, MODELFI2CDF = 12, MODECDF2LFI = 13 + + integer,parameter :: OPTCDF3 = 1, OPTCDF4 = 2, OPTCOMPRESS = 3 + integer,parameter :: OPTHELP = 4, OPTLIST = 5, OPTMERGE = 6 + integer,parameter :: OPTOUTPUT = 7, OPTREDUCE = 8, OPTSPLIT = 9 + integer,parameter :: OPTVAR = 10 + + type option + logical :: set = .false. + character(len=:),allocatable :: long_name + character :: short_name + logical :: has_argument + integer :: type = TYPEUNDEF + integer :: ivalue + logical :: lvalue + real :: rvalue + character(len=:),allocatable :: cvalue + end type option + +contains +subroutine read_commandline(options,hinfile,houtfile,runmode) + implicit none + + type(option),dimension(:),allocatable,intent(out) :: options + character(len=:),allocatable,intent(out) :: hinfile + character(len=:),allocatable,intent(out) :: houtfile + integer,intent(out) :: runmode + + integer :: idx, ji, nbargs, status, sz + logical :: finished + character(len=:),allocatable :: command, fullcommand + + + call GET_COMMAND_ARGUMENT(NUMBER=0,LENGTH=sz) + allocate(character(len=sz)::fullcommand) + call GET_COMMAND_ARGUMENT(NUMBER=0,VALUE=fullcommand) + + idx = index(fullcommand,'/',back=.true.) + allocate(character(len=sz-idx)::command) + command=fullcommand(idx+1:) + + select case (command) + case ('cdf2cdf') + runmode = MODECDF2CDF + case ('cdf2lfi') + runmode = MODECDF2LFI + case ('lfi2cdf') + runmode = MODELFI2CDF + case default + runmode = MODEUNDEF + print *,'Error: program started with unknown command: ',command + call help() + end select + deallocate(command,fullcommand) + + call init_options(options) + + nbargs = COMMAND_ARGUMENT_COUNT() + + if (nbargs==0) then + print *,'Error: no input file given' + call help() + end if + + if (nbargs>1) then + finished = .false. + do while(.not.finished) + call get_option(options,finished) + end do + end if + + call GET_COMMAND_ARGUMENT(NUMBER=nbargs,LENGTH=sz) + allocate(character(len=sz)::hinfile) + call GET_COMMAND_ARGUMENT(NUMBER=COMMAND_ARGUMENT_COUNT(),VALUE=hinfile) + + call check_options(options,hinfile,runmode) + + houtfile = options(OPTOUTPUT)%cvalue + + !Remove level in the filename if merging LFI splitted files + if (.NOT.options(OPTOUTPUT)%set) then + if (options(OPTMERGE)%set .AND. .NOT.options(OPTSPLIT)%set) then + houtfile=houtfile(1:len(houtfile)-9)//houtfile(len(houtfile)-3:) + end if + if (.NOT.options(OPTMERGE)%set .AND. options(OPTSPLIT)%set) then + if (options(OPTCDF4)%set) then + ji=4 + else + ji=3 + end if + houtfile=houtfile(1:len(houtfile)-ji) + end if + if (options(OPTMERGE)%set .AND. options(OPTSPLIT)%set) then + if (options(OPTCDF4)%set) then + ji=9 + else + ji=8 + end if + houtfile=houtfile(1:len(houtfile)-ji) + end if + end if + +end subroutine read_commandline + +subroutine init_options(options) + implicit none + + type(option),dimension(:),allocatable,intent(out) :: options + + allocate(options(nbavailoptions)) + + options(OPTCDF3)%long_name = "cdf3" + options(OPTCDF3)%short_name = '3' + options(OPTCDF3)%has_argument = .false. + + options(OPTCDF4)%long_name = "cdf4" + options(OPTCDF4)%short_name = '4' + options(OPTCDF4)%has_argument = .false. + + options(OPTCOMPRESS)%long_name = "compress" + options(OPTCOMPRESS)%short_name = 'c' + options(OPTCOMPRESS)%has_argument = .true. + options(OPTCOMPRESS)%type = TYPEINT + + options(OPTHELP)%long_name = "help" + options(OPTHELP)%short_name = 'h' + options(OPTHELP)%has_argument = .false. + + options(OPTLIST)%long_name = "list" + options(OPTLIST)%short_name = 'l' + options(OPTLIST)%has_argument = .false. + + options(OPTMERGE)%long_name = "merge" + options(OPTMERGE)%short_name = 'm' + options(OPTMERGE)%has_argument = .true. + options(OPTMERGE)%type = TYPEINT + + options(OPTOUTPUT)%long_name = "output" + options(OPTOUTPUT)%short_name = 'o' + options(OPTOUTPUT)%has_argument = .true. + options(OPTOUTPUT)%type = TYPECHAR + + options(OPTREDUCE)%long_name = "reduce-precision" + options(OPTREDUCE)%short_name = 'r' + options(OPTREDUCE)%has_argument = .false. + + options(OPTSPLIT)%long_name = "split" + options(OPTSPLIT)%short_name = 's' + options(OPTSPLIT)%has_argument = .false. + + options(OPTVAR)%long_name = "var" + options(OPTVAR)%short_name = 'v' + options(OPTVAR)%has_argument = .true. + options(OPTVAR)%type = TYPECHAR + +end subroutine init_options + +subroutine get_option(options,finished) + implicit none + + integer,parameter :: MAXARGSIZE=512 + + logical,intent(out) :: finished + type(option),dimension(:),intent(inout) :: options + + integer,save :: argnum = 1 + integer :: i, sz + logical :: found + character(len=MAXARGSIZE) :: arg + + found = .false. + call GET_COMMAND_ARGUMENT(NUMBER=argnum,VALUE=arg,LENGTH=sz) + if(sz>MAXARGSIZE) print *,'Error: argument bigger than ',MAXARGSIZE + if ( INDEX(arg,'--')==1 .AND. sz>2) then + do i=1,nbavailoptions + if (options(i)%long_name == trim(arg(3:))) then + found = .true. + exit + end if + end do + else if ( INDEX(arg,'-')==1 ) then + do i=1,nbavailoptions + if (options(i)%short_name == trim(arg(2:))) then + found = .true. + exit + end if + end do + else + print *,'Error: ',trim(arg),' is not an option' + call help() + end if + + if ( .not.found ) then + print *,'Error: unknown option: ',trim(arg) + call help() + end if + + if (options(i)%set) then + print *,'Error: at least 1 option is set several times!' + call help() + end if + + options(i)%set = .true. + if (options(i)%has_argument) then + argnum = argnum + 1 + if (argnum >= COMMAND_ARGUMENT_COUNT()) then + print *,'Error: argument for option ',trim(arg),' not found' + call help() + end if + call GET_COMMAND_ARGUMENT(NUMBER=argnum,VALUE=arg,LENGTH=sz) + if(sz>MAXARGSIZE) print *,'Error: argument bigger than ',MAXARGSIZE + select case (options(i)%type) + case (TYPEINT) + read (arg,*) options(i)%ivalue + case (TYPELOG) + read (arg,*) options(i)%lvalue + case (TYPEREAL) + read (arg,*) options(i)%rvalue + case (TYPECHAR) + options(i)%cvalue = arg + case default + print *,'Error: unknown option type' + call help() + end select + end if + + argnum = argnum + 1 + + if (argnum >= COMMAND_ARGUMENT_COUNT()) finished = .true. + +end subroutine get_option + +subroutine check_options(options,infile,runmode) + implicit none + + type(option),dimension(:),intent(inout) :: options + character(len=:),allocatable,intent(in) :: infile + integer,intent(in) :: runmode + + integer :: idx1, idx2 + + + !Check if help has been asked + if (options(OPTHELP)%set) then + call help() + end if + + !Use NetCF-4 by default + if (.NOT.options(OPTCDF3)%set) then + options(OPTCDF4)%set = .true. + else + if (options(OPTCDF4)%set) then + print *,'Warning: NetCDF-3 and NetCDF-4 options are not compatible' + print *,'NetCDF-4 is forced' + options(OPTCDF3)%set = .false. + end if + end if + + !Check compression level + if (options(OPTCOMPRESS)%set) then + if (options(OPTCOMPRESS)%ivalue < 1 .OR. options(OPTCOMPRESS)%ivalue > 9 ) then + print *,'Error: compression level should in the 1 to 9 interval' + call help() + end if + end if + + !Check list option + if (options(OPTLIST)%set .AND. runmode/=MODELFI2CDF) then + print *,'Error: list option is only valid for lfi2cdf' + call help() + end if + + !Merge flag only supported if -v is set + if (options(OPTMERGE)%set .AND. .NOT.options(OPTVAR)%set) then + print *,'Error: merge option must be used with var option' + call help() + end if + + !Split flag only supported if -v is set + if (options(OPTSPLIT)%set .AND. .NOT.options(OPTVAR)%set) then + options(OPTSPLIT)%set = .false. + print *,"Warning: split option is forced to disable" + end if + + !Determine outfile name if not given + if (.NOT.options(OPTOUTPUT)%set) then + idx1 = index(infile,'/',back=.true.) + idx2 = index(infile,'.',back=.true.) + options(OPTOUTPUT)%cvalue = infile(idx1+1:idx2-1) + end if + +end subroutine check_options + +subroutine help() + implicit none + +!TODO: -l option for cdf2cdf and cdf2lfi + print *,"Usage : lfi2cdf [-h --help] [--cdf4 -4] [-l] [-v --var var1[,...]] [-r --reduce-precision]" + print *," [-m --merge number_of_z_levels] [-s --split] [-o --output output-file.nc]" + print *," [-c --compress compression_level] input-file.lfi" + print *," cdf2cdf [-h --help] [--cdf4 -4] [-v --var var1[,...]] [-r --reduce-precision]" + print *," [-m --merge number_of_z_levels] [-s --split] [-o --output output-file.nc]" + print *," [-c --compress compression_level] input-file.nc" + print *," cdf2lfi [-o --output output-file.lfi] input-file.nc" + print *,"" + print *,"Options:" + print *," --cdf3, -3" + print *," Write netCDF file in netCDF-3 format (cdf2cdf and lfi2cdf only)" + print *," --cdf4, -4 (by default)" + print *," Write netCDF file in netCDF-4 format (HDF5 compatible) (cdf2cdf and lfi2cdf only)" + print *," --compress, -c compression_level" + print *," Compress data. The compression level should be in the 1 to 9 interval." + print *," Only supported with the netCDF-4 format (cdf2cdf and lfi2cdf only)" + print *," --help, -h" + print *," Print this text" + print *," --list, -l" + print *," List all the fields of the LFI file and returns (lfi2cdf only)" + print *," --merge, -m number_of_z_levels" + print *," Merge LFI files which are split by vertical level (cdf2cdf and lfi2cdf only)" + print *," --output, -o" + print *," Name of file for the output" + print *," --reduce-precision, -r" + print *," Reduce the precision of the floating point variables to single precision (cdf2cdf and lfi2cdf only)" + print *," --split, -s" + print *," Split variables specified with the -v option (one per file) (cdf2cdf and lfi2cdf only)" + print *," --var, -v var1[,...]" + print *," List of the variable to write in the output file. Variables names have to be separated by commas (,)." + print *," A variable can be computed from the sum of existing variables (format: new_var=var1+var2[+...])" + print *," (cdf2cdf and lfi2cdf only)" + print *,"" + stop + +end subroutine help + +end module mode_options diff --git a/tools/lfi2cdf/src/mode_util.f90 b/tools/lfi2cdf/src/mode_util.f90 index 31cab4c7e..78c1fc0ce 100644 --- a/tools/lfi2cdf/src/mode_util.f90 +++ b/tools/lfi2cdf/src/mode_util.f90 @@ -1,6 +1,7 @@ MODULE mode_util USE MODE_FIELDTYPE USE mode_dimlist + USE mode_options USE MODD_PARAM USE netcdf @@ -93,12 +94,12 @@ CONTAINS END IF END SUBROUTINE FMREADLFIN1 - SUBROUTINE parse_infiles(infiles, hvarlist, nbvar_infile, nbvar_tbr, nbvar_calc, nbvar_tbw, tpreclist, kbuflen, icurrent_level) + SUBROUTINE parse_infiles(infiles, nbvar_infile, nbvar_tbr, nbvar_calc, nbvar_tbw, tpreclist, kbuflen, options, icurrent_level) TYPE(filelist_struct), INTENT(IN) :: infiles INTEGER, INTENT(IN) :: nbvar_infile, nbvar_tbr, nbvar_calc, nbvar_tbw - CHARACTER(LEN=*), INTENT(IN) :: hvarlist TYPE(workfield), DIMENSION(:), POINTER :: tpreclist INTEGER, INTENT(OUT) :: kbuflen + TYPE(option),DIMENSION(:), INTENT(IN) :: options INTEGER, INTENT(IN), OPTIONAL :: icurrent_level INTEGER :: ji,jj, kcdf_id, itype @@ -119,7 +120,6 @@ CONTAINS !JUAN CYCCL3 INTEGER :: JPHEXT - IF (infiles%files(1)%format == LFI_FORMAT) THEN ilu = infiles%files(1)%lun_id @@ -179,7 +179,7 @@ CONTAINS ! compte un sous-ensemble d'article (liste definie par ! l'utilisateur par exemple) ! - IF (LEN_TRIM(hvarlist) > 0) THEN + IF (options(OPTVAR)%set) THEN #ifndef LOWMEM IF(.NOT.ALLOCATED(lfiart) .AND. infiles%files(1)%format == LFI_FORMAT) ALLOCATE(lfiart(nbvar_tbr+nbvar_calc)) #endif @@ -197,8 +197,9 @@ CONTAINS ndb = 1 idx_var = 1 DO ji=1,nbvar_tbw - nde = INDEX(TRIM(hvarlist(ndb:)),',') - yrecfm = hvarlist(ndb:ndb+nde-2) + !crash compiler GCC 4.2.0: nde = INDEX(TRIM(options(OPTVAR)%cvalue(ndb:)),',') + nde = INDEX(TRIM(options(OPTVAR)%cvalue(ndb:len(trim(options(OPTVAR)%cvalue)))),',') + yrecfm = options(OPTVAR)%cvalue(ndb:ndb+nde-2) !Detect operations on variables (only + is supported now) ndey = INDEX(TRIM(yrecfm),'=') @@ -470,10 +471,9 @@ END DO #endif END SUBROUTINE parse_infiles - SUBROUTINE read_data_lfi(infiles, hvarlist, nbvar, tpreclist, kbuflen, current_level) + SUBROUTINE read_data_lfi(infiles, nbvar, tpreclist, kbuflen, current_level) TYPE(filelist_struct), INTENT(IN) :: infiles INTEGER, INTENT(INOUT) :: nbvar - CHARACTER(LEN=*), intent(IN) :: hvarlist TYPE(workfield), DIMENSION(:), POINTER :: tpreclist INTEGER, INTENT(IN) :: kbuflen INTEGER, INTENT(IN), OPTIONAL :: current_level @@ -532,17 +532,13 @@ END DO END IF END SUBROUTINE HANDLE_ERR - SUBROUTINE def_ncdf(outfiles,tpreclist,nbvar,oreduceprecision,omerge,osplit,ocompress,compress_level) + SUBROUTINE def_ncdf(outfiles,tpreclist,nbvar,options) TYPE(filelist_struct), INTENT(IN) :: outfiles TYPE(workfield),DIMENSION(:),INTENT(INOUT) :: tpreclist INTEGER, INTENT(IN) :: nbvar - LOGICAL, INTENT(IN) :: oreduceprecision - LOGICAL, INTENT(IN) :: omerge - LOGICAl, INTENT(IN) :: osplit - LOGICAL, INTENT(IN) :: ocompress - INTEGER, INTENT(IN) :: compress_level + TYPE(option),DIMENSION(:), INTENT(IN) :: options - INTEGER :: status + INTEGER :: compress_level, status INTEGER :: idx, ji, nbfiles INTEGER:: kcdf_id TYPE(dimCDF), POINTER :: tzdim @@ -554,7 +550,7 @@ END DO nbfiles = outfiles%nbfiles - IF (oreduceprecision) THEN + IF (options(OPTREDUCE)%set) THEN type_float = NF90_REAL ELSE type_float = NF90_DOUBLE @@ -591,7 +587,7 @@ END DO ivdims(1) = tpreclist(ji)%dim%id ELSE invdims = tpreclist(ji)%dim%ndims - IF(omerge) invdims=invdims+1 !when merging variables from LFI splitted files + IF(options(OPTMERGE)%set) invdims=invdims+1 !when merging variables from LFI splitted files SELECT CASE(invdims) CASE(2) ivdims(1)=ptdimx%id @@ -656,7 +652,8 @@ END DO END SELECT ! Compress data (costly operation for the CPU) - IF (ocompress .AND. invdims>0) THEN + IF (options(OPTCOMPRESS)%set .AND. invdims>0) THEN + compress_level = options(OPTCOMPRESS)%ivalue status = NF90_DEF_VAR_DEFLATE(kcdf_id,tpreclist(ji)%id_out,1,1,compress_level) IF (status /= NF90_NOERR) CALL HANDLE_ERR(status,__LINE__) END IF @@ -669,7 +666,7 @@ END DO status = NF90_PUT_ATT(kcdf_id,tpreclist(ji)%id_out,'COMMENT',trim(tpreclist(ji)%comment)) IF (status /= NF90_NOERR) CALL HANDLE_ERR(status,__LINE__) - IF (osplit) idx = idx + 1 + IF (options(OPTSPLIT)%set) idx = idx + 1 END DO DO ji = 1,nbfiles @@ -680,12 +677,12 @@ END DO END SUBROUTINE def_ncdf - SUBROUTINE fill_ncdf(infiles,outfiles,tpreclist,knaf,kbuflen,osplit,current_level) + SUBROUTINE fill_ncdf(infiles,outfiles,tpreclist,knaf,kbuflen,options,current_level) TYPE(filelist_struct), INTENT(IN):: infiles, outfiles TYPE(workfield), DIMENSION(:),INTENT(IN):: tpreclist INTEGER, INTENT(IN):: knaf INTEGER, INTENT(IN):: kbuflen - LOGICAl, INTENT(IN):: osplit + TYPE(option),DIMENSION(:), INTENT(IN):: options INTEGER, INTENT(IN), OPTIONAL :: current_level #ifdef LOWMEM @@ -994,7 +991,7 @@ END DO END SELECT - if (osplit) idx = idx + 1 + if (options(OPTSPLIT)%set) idx = idx + 1 END DO DEALLOCATE(itab,xtab) #if LOWMEM @@ -1150,12 +1147,13 @@ END DO END DO END SUBROUTINE UPDATE_VARID_IN - SUBROUTINE OPEN_FILES(infiles,outfiles,hinfile,houtfile,ocdf2cdf,olfi2cdf,olfilist,ohdf5,nbvar_infile,osplit) + SUBROUTINE OPEN_FILES(infiles,outfiles,hinfile,houtfile,nbvar_infile,options,runmode) TYPE(filelist_struct),INTENT(OUT) :: infiles, outfiles - LOGICAL, INTENT(IN) :: ocdf2cdf, olfi2cdf, olfilist, ohdf5, osplit CHARACTER(LEN=*), INTENT(IN) :: hinfile CHARACTER(LEN=*), INTENT(IN) :: houtfile INTEGER , INTENT(OUT) :: nbvar_infile + TYPE(option),DIMENSION(:),INTENT(IN) :: options + INTEGER , INTENT(IN) :: runmode INTEGER :: extindex INTEGER(KIND=LFI_INT) :: iresp,iverb,inap,inaf @@ -1168,7 +1166,7 @@ END DO CALL init_sysfield() - IF (olfi2cdf) THEN + IF (runmode == MODELFI2CDF) THEN ! Cas LFI -> NetCDF infiles%nbfiles = infiles%nbfiles + 1 idx = infiles%nbfiles @@ -1181,19 +1179,19 @@ END DO nbvar_infile = inaf - IF (olfilist) THEN + IF (options(OPTLIST)%set) THEN CALL LFILAF(iresp,infiles%files(idx)%lun_id,lfalse) CALL LFIFER(iresp,infiles%files(idx)%lun_id,'KEEP') return END IF - IF (.NOT.osplit) THEN + IF (.NOT.options(OPTSPLIT)%set) THEN outfiles%nbfiles = outfiles%nbfiles + 1 idx = outfiles%nbfiles outfiles%files(idx)%format = NETCDF_FORMAT outfiles%files(idx)%status = WRITING - IF (ohdf5) THEN + IF (options(OPTCDF4)%set) THEN status = NF90_CREATE(houtfile, IOR(NF90_CLOBBER,NF90_NETCDF4), outfiles%files(idx)%lun_id) ELSE status = NF90_CREATE(houtfile, IOR(NF90_CLOBBER,NF90_64BIT_OFFSET), outfiles%files(idx)%lun_id) @@ -1214,7 +1212,7 @@ END DO !!$ END SELECT END IF ! .NOT.osplit - ELSE IF (ocdf2cdf) THEN + ELSE IF (runmode == MODECDF2CDF) THEN ! Cas netCDF -> netCDF infiles%nbfiles = infiles%nbfiles + 1 @@ -1229,11 +1227,11 @@ END DO IF (status /= NF90_NOERR) CALL HANDLE_ERR(status,__LINE__) - IF (.NOT.osplit) THEN + IF (.NOT.options(OPTSPLIT)%set) THEN outfiles%nbfiles = outfiles%nbfiles + 1 idx = outfiles%nbfiles - IF (ohdf5) THEN + IF (options(OPTCDF4)%set) THEN status = NF90_CREATE(houtfile, IOR(NF90_CLOBBER,NF90_NETCDF4), outfiles%files(idx)%lun_id) ELSE status = NF90_CREATE(houtfile, IOR(NF90_CLOBBER,NF90_64BIT_OFFSET), outfiles%files(idx)%lun_id) @@ -1322,12 +1320,12 @@ END DO DEALLOCATE(filename) END SUBROUTINE OPEN_SPLIT_NCFILE_IN - SUBROUTINE OPEN_SPLIT_NCFILES_OUT(outfiles,houtfile,nbvar,tpreclist,ohdf5) + SUBROUTINE OPEN_SPLIT_NCFILES_OUT(outfiles,houtfile,nbvar,tpreclist,options) TYPE(filelist_struct), INTENT(INOUT) :: outfiles CHARACTER(LEN=*), INTENT(IN) :: houtfile INTEGER, INTENT(IN) :: nbvar TYPE(workfield), DIMENSION(:), INTENT(IN) :: tpreclist - LOGICAL, INTENT(IN) :: ohdf5 + TYPE(option),DIMENSION(:), INTENT(IN) :: options INTEGER :: ji, idx INTEGER :: status @@ -1344,7 +1342,7 @@ END DO IF (.NOT.tpreclist(ji)%tbw) CYCLE outfiles%files(idx)%var_id = ji - IF (ohdf5) THEN + IF (options(OPTCDF4)%set) THEN filename = trim(houtfile)//'.'//trim(tpreclist(ji)%name)//'.nc4' status = NF90_CREATE(trim(filename), IOR(NF90_CLOBBER,NF90_NETCDF4), outfiles%files(idx)%lun_id) ELSE diff --git a/tools/lfi2cdf/src/newmain.c b/tools/lfi2cdf/src/newmain.c deleted file mode 100644 index 7ed4be3cf..000000000 --- a/tools/lfi2cdf/src/newmain.c +++ /dev/null @@ -1,238 +0,0 @@ -#include <stdio.h> -#include <stdlib.h> -#include <string.h> -#include <getopt.h> - -#define BUFSIZE 4096 - -extern lfi2cdfmain_(char*, int*, int *, char*, int*, char*, int*, int*, int*, int*, int*, int*, int*, int*, int*, int*, int*); - -char *cleancomma(char *varlist) -{ - char *ip, *op; - - op = varlist; - - for (ip=varlist; *ip; ip++) { - if (*ip != ',' || *ip == ',' && *op != ',') - *(++op) = *ip; - } - if (*op != ',') - *(++op) = ','; - - *(op+1) = '\0'; - return varlist+1; -} - -int main(int argc, char **argv) -{ - int ilen; - int list_flag; - int c2c_flag; - int l2c_flag; - int hdf5_flag; - int merge_flag, nb_levels; - int reduceprecision_flag; - int outname_flag; - int compress_flag, compress_level; - int split_flag; - int help_flag; - char *cmd, *infile; - int c; - char buff[BUFSIZE]; - int varlistlen; - char *varlist; - char *p; - int lenopt; - char *outfile=NULL; - int olen=0; - - cmd = strrchr(argv[0], '/'); - if (cmd == NULL) - cmd = argv[0]; - else - cmd++; - l2c_flag = strcmp(cmd, "lfi2cdf") == 0 ? 1 : 0; - c2c_flag = strcmp(cmd, "cdf2cdf") == 0 ? 1 : 0; - - compress_flag = 0; - list_flag = 0; - hdf5_flag = 1; - help_flag = 0; - outname_flag = 0; - reduceprecision_flag = 0; - split_flag = 0; - p = buff; - *p = '\0'; - - /* Default values for merging of LFI splitted files */ - merge_flag = 0; - nb_levels = 1; - - while (1) { - int option_index = 0; - - static struct option long_options[] = { - {"cdf3", no_argument, 0, '3' }, - {"cdf4", no_argument, 0, '4' }, - {"compress", required_argument, 0, 'c' }, - {"help", no_argument, 0, 'h' }, - {"list", no_argument, 0, 'l' }, - {"merge", required_argument, 0, 'm' }, - {"output", required_argument, 0, 'o' }, - {"reduce-precision", no_argument, 0, 'r' }, - {"split", no_argument, 0, 's' }, - {"var", required_argument, 0, 'v' }, - {0, 0, 0, 0 } - }; - - c = getopt_long(argc, argv, "34c:hlm:o:rsv:", - long_options, &option_index); - if (c == -1) - break; - - switch (c) { - case 0: - printf("option %s", long_options[option_index].name); - if (optarg) - printf(" with arg %s", optarg); - printf("\n"); - break; - case 'c': - compress_flag = 1; - compress_level = atoi(optarg); - if(compress_level<1 || compress_level>9) { - printf("Error: compression level should in the 1 to 9 interval\n"); - exit(EXIT_FAILURE); - } - break; - case '3': - hdf5_flag = 0; - break; - case '4': - hdf5_flag = 1; - break; - case 'h': - help_flag = 1; - break; - case 'l': - list_flag = 1; - break; - case 'm': - merge_flag = 1; - nb_levels = atoi(optarg); - break; - case 'o': - outname_flag = 1; - outfile = optarg; - olen = strlen(outfile); - break; - case 'r': - reduceprecision_flag = 1; - break; - case 's': - split_flag = 1; - break; - case 'v': - if (l2c_flag || c2c_flag) { - lenopt = strlen(optarg); - // printf("option v with value '%s'\n", optarg); - if (p+lenopt > buff+BUFSIZE) - printf("%s ignored in list\n", optarg); - else { - *p++ = ','; - strcpy(p, optarg); - p += lenopt; - } - } else - printf("option -v is ignored\n"); - break; - - default: - printf("?? getopt returned character code 0%o ??\n", c); - } - } - - if (optind == argc || help_flag) { -//TODO: -l option for cdf2cdf and cdf2lfi - printf("usage : lfi2cdf [-h --help] [--cdf4 -4] [-l] [-v --var var1[,...]] [-r --reduce-precision] [-m --merge number_of_z_levels] [-s --split] [-o --output output-file.nc] [-c --compress compression_level] input-file.lfi\n"); - printf(" cdf2cdf [-h --help] [--cdf4 -4] [-v --var var1[,...]] [-r --reduce-precision] [-m --merge number_of_z_levels] [-s --split] [-o --output output-file.nc] [-c --compress compression_level] input-file.nc\n"); - printf(" cdf2lfi [-o --output output-file.lfi] input-file.nc\n"); - printf("\nOptions:\n"); - printf(" --cdf3, -3\n"); - printf(" Write netCDF file in netCDF-3 format (cdf2cdf and lfi2cdf only)\n"); - printf(" --cdf4, -4 (by default)\n"); - printf(" Write netCDF file in netCDF-4 format (HDF5 compatible) (cdf2cdf and lfi2cdf only)\n"); - printf(" --compress, -c compression_level\n"); - printf(" Compress data. The compression level should be in the 1 to 9 interval.\n"); - printf(" Only supported with the netCDF-4 format (cdf2cdf and lfi2cdf only)\n"); - printf(" --help, -h\n"); - printf(" Print this text\n"); - printf(" --list, -l\n"); - printf(" List all the fields of the LFI file and returns (lfi2cdf only)\n"); - printf(" --merge, -m number_of_z_levels\n"); - printf(" Merge LFI files which are split by vertical level (cdf2cdf and lfi2cdf only)\n"); - printf(" --output, -o\n"); - printf(" Name of file for the output\n"); - printf(" --reduce-precision, -r\n"); - printf(" Reduce the precision of the floating point variables to single precision (cdf2cdf and lfi2cdf only)\n"); - printf(" --split, -s\n"); - printf(" Split variables specified with the -v option (one per file) (cdf2cdf and lfi2cdf only)\n"); - printf(" --var, -v var1[,...]\n"); - printf(" List of the variable to write in the output file. Variables names have to be separated by commas (,).\n"); - printf(" A variable can be computed from the sum of existing variables (format: new_var=var1+var2[+...])\n"); - printf(" (cdf2cdf and lfi2cdf only)\n"); - printf("\n"); - exit(EXIT_FAILURE); - } - - ilen = strlen(argv[optind]); - infile = argv[optind]; - - varlist = cleancomma(buff); - varlistlen = strlen(buff); - - if (outfile == NULL) { - /* determine outfile name from infile name */ - char *cp, *sp; - cp = strrchr(infile, '/'); - if (cp == 0) /* no delimiter */ - cp = infile; - else /* skip delimeter */ - cp++; - outfile = (char*) malloc((unsigned)(strlen(cp)+5)); - (void) strncpy(outfile, cp, strlen(cp) + 1); - if ((sp = strrchr(outfile, '.')) != NULL) - *sp = '\0'; - if (l2c_flag || c2c_flag){ - char *ncext; - ncext = hdf5_flag ? ".nc4" : ".nc"; - strcat(outfile,ncext); - } else - strcat(outfile,".lfi"); - olen = strlen(outfile); - } - - /* Compression flag only supported if using netCDF4 */ - if (hdf5_flag==0 && compress_flag==1) { - compress_flag = 0; - printf("Warning: compression is forced to disable (only supported from netCDF4).\n"); - } - - /* - printf("cmd=%s; inputfile=%s(%d); outputfile=%s(%d); varlistclean=%s with size : %d\n", cmd, - infile, ilen, outfile, olen, varlist, varlistlen); - */ - - /* Split flag only supported if -v is set */ - if (varlistlen==0 && split_flag!=0) { - split_flag = 0; - printf("Warning: split option is forced to disable.\n"); - } - - - lfi2cdfmain_(infile, &ilen, &outname_flag, outfile, &olen, varlist, &varlistlen, &c2c_flag, &l2c_flag, &list_flag, &hdf5_flag, &merge_flag, - &nb_levels, &reduceprecision_flag, &split_flag, &compress_flag, &compress_level); - - exit(EXIT_SUCCESS); -} -- GitLab