Skip to content
Snippets Groups Projects
Commit 0865bd5a authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann
Browse files

removing unused parameters

parent 2572403b
No related branches found
No related tags found
No related merge requests found
......@@ -16,18 +16,17 @@ MODULE diagnostics_par
! HDF5 file
CHARACTER(len=256), PUBLIC :: resfile0 = "results" ! Head of main result file name
CHARACTER(len=256), PUBLIC :: resfile ! Main result file
CHARACTER(len=256), PUBLIC :: rstfile ! restart result file
INTEGER, PUBLIC :: job2load ! jobnum of the checkpoint to load
INTEGER, PUBLIC :: fidres ! FID for resfile
CHARACTER(len=256), PUBLIC :: rstfile0 = "restart" ! Head of restart file name
CHARACTER(len=256), PUBLIC :: rstfile ! Full restart file
INTEGER, PUBLIC :: fidrst ! FID for restart file
PUBLIC :: output_par_readinputs, output_par_outputinputs
PUBLIC :: diag_par_readinputs, diag_par_outputinputs
CONTAINS
SUBROUTINE output_par_readinputs
SUBROUTINE diag_par_readinputs
! Read the input parameters
USE basic, ONLY : lu_in
......@@ -38,14 +37,14 @@ CONTAINS
NAMELIST /OUTPUT_PAR/ write_doubleprecision, write_gamma, write_hf, write_phi
NAMELIST /OUTPUT_PAR/ write_Na00, write_Napj, write_Sapj
NAMELIST /OUTPUT_PAR/ write_dens, write_temp
NAMELIST /OUTPUT_PAR/ resfile0, rstfile0, job2load
NAMELIST /OUTPUT_PAR/ job2load
READ(lu_in,output_par)
END SUBROUTINE output_par_readinputs
END SUBROUTINE diag_par_readinputs
SUBROUTINE output_par_outputinputs(fidres, str)
SUBROUTINE diag_par_outputinputs(fidres, str)
!
! Write the input parameters to the results_xx.h5 file
!
......@@ -60,9 +59,8 @@ CONTAINS
CALL attach(fidres, TRIM(str), "nsave_1d", nsave_1d)
CALL attach(fidres, TRIM(str), "nsave_2d", nsave_2d)
CALL attach(fidres, TRIM(str), "nsave_5d", nsave_5d)
CALL attach(fidres, TRIM(str), "resfile0", resfile0)
END SUBROUTINE output_par_outputinputs
END SUBROUTINE diag_par_outputinputs
END MODULE diagnostics_par
......@@ -2,7 +2,7 @@ SUBROUTINE readinputs
! Additional data specific for a new run
USE grid, ONLY: grid_readinputs
USE diagnostics_par, ONLY: output_par_readinputs
USE diagnostics_par, ONLY: diag_par_readinputs
USE model, ONLY: model_readinputs
USE initial_par, ONLY: initial_readinputs
USE time_integration, ONLY: time_integration_readinputs
......@@ -18,7 +18,7 @@ SUBROUTINE readinputs
CALL grid_readinputs
! Load diagnostic options from input file
CALL output_par_readinputs
CALL diag_par_readinputs
! Load model parameters from input file
CALL model_readinputs
......
......@@ -166,90 +166,4 @@ CONTAINS
END SUBROUTINE load_output_adapt_pj
!******************************************************************************!
!******************************************************************************!
!!!!!!! Load moments from a previous save
!******************************************************************************!
SUBROUTINE load_cp
IMPLICIT NONE
! Checkpoint filename
WRITE(rstfile,'(a,a1,i2.2,a3)') TRIM(rstfile0),'_',job2load,'.h5'
IF (my_id .EQ. 0) WRITE(*,'(3x,a)') "Resume from previous run"
! Open file
CALL openf(rstfile, fidrst,mpicomm=MPI_COMM_WORLD)
! Get the checkpoint moments degrees to allocate memory
CALL getatt(fidrst,"/Basic/moments_e/" , "pmaxe", pmaxe_cp)
CALL getatt(fidrst,"/Basic/moments_e/" , "jmaxe", jmaxe_cp)
CALL getatt(fidrst,"/Basic/moments_i/" , "pmaxi", pmaxi_cp)
CALL getatt(fidrst,"/Basic/moments_i/" , "jmaxi", jmaxi_cp)
IF (my_id .EQ. 0) WRITE(*,*) "Pe_cp = ", pmaxe_cp
IF (my_id .EQ. 0) WRITE(*,*) "Je_cp = ", jmaxe_cp
! Allocate the required size to load checkpoints moments
CALL allocate_array(moments_e_cp, 1,pmaxe_cp+1, 1,jmaxe_cp+1, ikxs,ikxe, ikys,ikye, izs,ize)
CALL allocate_array(moments_i_cp, 1,pmaxi_cp+1, 1,jmaxi_cp+1, ikxs,ikxe, ikys,ikye, izs,ize)
! Find the last results of the checkpoint file by iteration
n_ = 0
WRITE(dset_name, "(A, '/', i6.6)") "/Basic/moments_e", n_ ! start with moments_e/000000
DO WHILE (isdataset(fidrst, dset_name)) ! If n_ is not a file we stop the loop
n_ = n_ + 1
WRITE(dset_name, "(A, '/', i6.6)") "/Basic/moments_e", n_ ! updtate file number
ENDDO
n_ = n_ - 1 ! n_ is not a file so take the previous one n_-1
! Read state of system from checkpoint file
WRITE(dset_name, "(A, '/', i6.6)") "/Basic/moments_e", n_
CALL getarr(fidrst, dset_name, moments_e_cp(1:pmaxe_cp+1, 1:jmaxe_cp+1, ikxs:ikxe, ikys:ikye, izs:ize),pardim=3)
WRITE(dset_name, "(A, '/', i6.6)") "/Basic/moments_i", n_
CALL getarr(fidrst, dset_name, moments_i_cp(1:pmaxi_cp+1, 1:jmaxi_cp+1, ikxs:ikxe, ikys:ikye, izs:ize),pardim=3)
WRITE(dset_name, "(A, '/', i6.6)") "/Basic/phi", n_
CALL getarr(fidrst, dset_name, phi(ikxs:ikxe,ikys:ikye,izs:ize),pardim=1)
! Initialize simulation moments array with checkpoints ones
! (they may have a larger number of polynomials, set to 0 at the begining)
moments_e = 0._dp; moments_i = 0._dp
DO ip=1,pmaxe_cp+1
DO ij=1,jmaxe_cp+1
DO ikx=ikxs,ikxe
DO iky=ikys,ikye
DO iz = izs,ize
moments_e(ip,ij,ikx,iky,iz,:) = moments_e_cp(ip,ij,ikx,iky,iz)
ENDDO
ENDDO
ENDDO
ENDDO
ENDDO
DO ip=1,pmaxi_cp+1
DO ij=1,jmaxi_cp+1
DO ikx=ikxs,ikxe
DO iky=ikys,ikye
DO iz = izs,ize
moments_i(ip,ij,ikx,iky,iz,:) = moments_i_cp(ip,ij,ikx,iky,iz)
ENDDO
ENDDO
ENDDO
ENDDO
ENDDO
! Deallocate checkpoint arrays
DEALLOCATE(moments_e_cp)
DEALLOCATE(moments_i_cp)
! Read time dependent attributes to continue simulation
CALL getatt(fidrst, dset_name, 'cstep', cstep)
CALL getatt(fidrst, dset_name, 'time', time)
CALL getatt(fidrst, dset_name, 'jobnum', jobnum)
jobnum = jobnum+1
CALL getatt(fidrst, dset_name, 'iframe2d',iframe2d)
CALL getatt(fidrst, dset_name, 'iframe5d',iframe5d)
iframe2d = iframe2d-1; iframe5d = iframe5d-1
CALL closef(fidrst)
IF (my_id .EQ. 0) WRITE(*,'(3x,a)') "Reading from restart file "//TRIM(rstfile)//" completed!"
END SUBROUTINE load_cp
!******************************************************************************!
END MODULE restarts
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment