! $Id$ ! ! module out_mod use config_mod use prd_mod type out_type character (200) :: infile character (200) :: outfile = 'not_set_yet' logical :: is_init = .false. contains procedure :: write_seg procedure , NOPASS :: initial end type out_type contains subroutine write_seg ( self, conf , prd) class ( out_type ) :: self type ( conf_user_opt_type) :: conf type ( prd_main_type) :: prd print*,self % is_init if (self % is_init .eqv. .false.) then call self % initial ( self, conf ) end if print*,' write..', conf % file % infile ( 1) print*,' outpath is ',self % outfile end subroutine write_seg ! ! ! subroutine initial (self , conf ) use hdf5 class ( out_type ) :: self type ( conf_user_opt_type) :: conf integer :: loc_npp integer :: hdferr integer ( HID_T) :: file_h5 , dataspace , dset, memspace,cparms,filespace integer (HSIZE_T) :: dims(1:2),dims1(1:2),dims2(1:2) integer (HSIZE_T) :: count(1:2), offset(1:2), stride(1:2), block(1:2), max_dims(1:2) real :: ref_chdnb_lunar1 ( 100,50) real :: ref_chdnb_lunar2 ( 100,30) integer ( HSIZE_T) :: chunk_dims ( 1:2) integer( HSIZE_T) ::data_dims(7) integer :: rank = 2 chunk_dims =[5,2] block =[1,1] stride=[1,1] dims = [100,80] self % is_init = .true. loc_npp = index ( trim(conf % file % infile(1)) , 'npp') self % outfile = trim(conf % file % out_path)//& &"/CLAVRX_"//trim(conf % file % infile(1)(loc_npp:loc_npp+37) )& &//".h5" dims1 = [100,50] ref_chdnb_lunar1 =33. ref_chdnb_lunar2 =43. call h5open_f(hdferr) call h5fcreate_f(self % outfile , H5F_ACC_TRUNC_F, file_h5, hdferr) call h5fclose_f(file_h5,hdferr) end subroutine initial ! ! ! subroutine add_dataset ( self ) use hdf5 class ( out_type ) :: self type ( conf_user_opt_type) :: conf integer :: loc_npp integer :: hdferr integer ( HID_T) :: file_h5 , dataspace , dset, memspace,cparms,filespace integer (HSIZE_T) :: dims(1:2),dims1(1:2),dims2(1:2) integer (HSIZE_T) :: count(1:2), offset(1:2), stride(1:2), block(1:2), max_dims(1:2) real :: ref_chdnb_lunar1 ( 100,50) real :: ref_chdnb_lunar2 ( 100,30) integer ( HSIZE_T) :: chunk_dims ( 1:2) integer( HSIZE_T) ::data_dims(7) integer :: rank = 2 call h5screate_simple_f ( 2 , dims, dataspace ,hdferr ) call h5dcreate_f(file_h5, "quatsch", H5T_NATIVE_REAL,dataspace,dset,hdferr) data_dims(1) = dims1(1) data_dims(2) = dims1(2) call h5dwrite_f (dset, H5T_NATIVE_REAL, ref_chdnb_lunar1, data_dims, hdferr ) CALL h5sclose_f(dataspace, hdferr) CALL h5dclose_f(dset, hdferr) CALL h5fclose_f(file_h5, hdferr) dims2 = [100,30] CALL h5fopen_f(self % outfile, H5F_ACC_RDWR_F, file_h5, hdferr) CALL h5dopen_f(file_h5, "quatsch", dset, hdferr) CALL h5dget_space_f(dset, dataspace, hdferr) offset = [0,50] count =[100,30] CALL h5sselect_hyperslab_f(dataspace, H5S_SELECT_SET_F, & offset, count, hdferr, stride, BLOCK) CALL h5screate_simple_f(rank, dims2, memspace, hdferr) call h5dwrite_f(dset, H5T_NATIVE_REAL, ref_chdnb_lunar2, dims2, hdferr & & , memspace, dataspace) call h5sclose_f (dataspace, hdferr) ! call h5sclose_f (filespace, hdferr) call h5sclose_f (memspace, hdferr) call h5dclose_f ( dset , hdferr) call h5fclose_f ( file_h5, hdferr) end subroutine add_dataset end module out_mod