PROGRAM main ! ! Skeleton for a time dependent program ! Note: Even in this sequential version, MPI is required ! because of FUTILS (more specifcally because ! of the HASTABLE module)! ! USE basic USE mpi USE bsplines USE mumps_bsplines USE futils IMPLICIT NONE INTEGER:: required, provided ! ! required=MPI_THREAD_FUNNELED CALL mpi_init_thread(required,provided,ierr) CALL MPI_COMM_RANK(MPI_COMM_WORLD, mpirank, ierr) CALL MPI_COMM_SIZE(MPI_COMM_WORLD, mpisize, ierr) !-------------------------------------------------------------------------------- ! 1. Prologue CALL timera(0, 'Prologue') CALL daytim('Start at') ! ! Define data specific to run ! CALL basic_data !Definition of global variables and input paramaters loading step=0 ! IF( .NOT. nlres ) THEN CALL newrun !not implemented yet ELSE CALL restart !not implemented yet END IF ! ! Compute auxilliary values ! CALL auxval !time independent values ! ! Initial conditions ! IF( .NOT. nlres ) THEN CALL inital !plasma initialisation ELSE CALL resume !loads restart.h5 file END IF ! ! Start or restart the run ! CALL start !not implemented yet ! ! Initial diagnostocs ! CALL diagnose(0) CALL timera(1, 'Prologue') !-------------------------------------------------------------------------------- ! 2. Time stepping CALL timera(0, 'Main loop') ! DO step = step+1 cstep = cstep+1 time = time+dt CALL tesend CALL stepon CALL diagnose(step) IF(modulo(step,itrestart) .eq. 0) CALL chkrst(1) IF( nlend ) EXIT END DO CALL timera(1, 'Main loop') !-------------------------------------------------------------------------------- ! 9. Epilogue CALL timera(0, 'Epilogue') ! CALL diagnose(-1) CALL endrun IF(mpirank .eq. 0) THEN CALL timera(1, 'Epilogue') CALL timera(9, '') CALL timera(-1, '') CALL daytim('Done at ') END IF CALL mpi_finalize(ierr) END PROGRAM main