Skip to content
prepare.F90 41.1 KiB
Newer Older
Fabio Roberto Vitello's avatar
Fabio Roberto Vitello committed
!======================================================================
!
!
                             PROGRAM fly_assistant
!
! xlf90  -WF,-DSP3 prepare.F -o assistant_sp3
! f90 -extend_source  -DORIGIN prepare.F -o assistant_ori
! f90 -N 132 -DT3E prepare.F -o ass_t3e
! ifc -o assistant prepare.F90
!======================================================================
!===================
!
!	Local definitions
!
!===================

	CHARACTER(LEN=256) 	:: headline,ibodfile,f32,f32_ql,mestr
	CHARACTER(LEN=256) 	:: parsfile,par1file,fewgrid,fewtab,fewphi,fpar35,ql_tab,fly_exe=""
	CHARACTER(LEN=256) 	:: fly_exe_name="",wd_exe="",wd_st="",wd_st_ori="",fly_name=""
	CHARACTER(LEN=256) 	:: fc_comp="",fc_opt="",cc_comp="",cc_opt="",lib=""
	CHARACTER(LEN=256) 	:: parsfile_d,par1file_d,fewgrid_d,fewtab_d,fewphi_d,fpar35_d,ql_tab_d
	CHARACTER(LEN=132) 	:: FFLAGS,FFLAGS1,FFLAGS2,CFLAGS,LDFLAGS,root_fly,use_fly
	CHARACTER(LEN=256) 	:: str,str_z32
	CHARACTER(LEN=110) 	:: str_mod
	CHARACTER(LEN=1) 	:: usequad,y_n,inasc='',ouasc='',qlf,sta,pw2,dt_var,y_n_s
	INTEGER		  	:: nsteps,npes=0,nbodies=0,nbodies_old,nnodes,nproc,var_ql,i_l_st
	REAL(KIND=8)		:: pstat,dtime,tol,eps,omega_cdm,omega_hdm,omega_l,mass_read,gstat
	REAL(KIND=4)		:: hubble=0.0
	
	
	REAL(KIND=8)		:: znow,rsize=0.0,rmin(3)
	INTEGER(KIND=4)		:: tstep,tst_max,ncrit,nbodcrit,l_end=5
	
	INTEGER			:: i,i_end,i1
	
	REAL(KIND=4), DIMENSION (100) :: z32_ou,z32_old
	
	INTEGER(KIND=8), DIMENSION(262144) :: ql_pos	
	INTEGER(KIND=8)		:: counter,ic,mem_pe,maxnterm,ql_swap,inx2,in_st,max_time=0,tempSort
	
	REAL			:: X_NR
	
	CHARACTER(LEN=64)	:: CMD
	
        INTEGER(KIND=4) :: lrefine_min=3
 	INTEGER(KIND=4) :: lrefine_max=5 	! MUST be <=31
        INTEGER(KIND=4) :: nxb=4,nyb=4,nzb=4 
	INTEGER(KIND=4) :: nguard=2 
        INTEGER         :: nob_global=10000    
	 
!===================
!
!	General section
!
!===================
	write(6,*)""
	write(6,*)""
	write(6,*)""
	write(6,*)""
	write(6,*)"                              Welcome to FLY assistant!                         "
	write(6,*)""
	write(6,*)"Answer all the questions following the instructions  that FLY  assistant will"
	write(6,*)"show."
	write(6,*)""
	write(6,*)""   
	write(6,*)"Some  questions  include  a default  value in   square  brackets. The  available"
	write(6,*)"choices are indicated in brackets."
	write(6,*)""   
	write(6,*)""   
	write(6,*)"FLY setup  will prepare  the  stat_pars  (static parameters used  by  FLY),  the"
	write(6,*)"dyn_pars  (dinamical  parameters  used  by  FLY), the  table  of  the programmed"
	write(6,*)"output files (out32.tab), the table for the quick look file generation (ql.dat)," 
	write(6,*)"the Ewald  grid (ew_grid)  and the Ewald  table  (ew_table) for  the  periodical"
	write(6,*)"boundary conditions. The FLY assistant will prepare the makefile_FLY to generate"
	write(6,*)"the executable (FLY) and the makefile_FLY_sort to generate the FLY_sort utility."
	write(6,*)""   
	write(6,*)""  
	write(6,*)"The FLY assistant will prepare the executables FLY and FLY_sort, and will generate"
	write(6,*)"the job scripts to run a simulation. The job scripts must  be modified by the user"
	write(6,*)"considering the specific  implementation of the  machine he will use."
	write(6,*)""   
	write(6,*)""  
!===================
!
!	working direct section
!
!===================
	

	wd_st_ori='../bin/'
	wd_st='../bin/'
	write(6,*)""
	write(6,*)"                GENERAL SETTING                       "
	write(6,*)""
	write(6,*)""
5	write(6,FMT=100)"Please set the working directory. The default value is ../bin : "  
	write(6,*)""
	write(6,ADVANCE='NO',FMT=105)"Working Direct [",TRIM(wd_st),"] : "  
	read(5,FMT='(A256)') wd_st
	wd_st=TRIM(wd_st)
	IF(wd_st.eq."") wd_st=wd_st_ori
	IF(wd_st(1:1).NE."." .AND. wd_st(1:1).NE."/") THEN
	write(6,*)""
	write(6,FMT=100)"WARNING. Please Check the data input "  
	write(6,*)""
	wd_st='../bin/'
	wd_st_ori='../bin/'
	goto 5
	
	ENDIF
	IF(wd_st(LEN_TRIM(wd_st):LEN_TRIM(wd_st)) .NE. "/") wd_st=TRIM(wd_st)//'/'	

7	write(6,*)""
	write(6,FMT='(3A)',ADVANCE='NO')"Confirm this ", TRIM(wd_st)," Working Directory (Y/N)  : "  
	read(5,FMT='(A1)') y_n
	y_n=TRIM(y_n)
	IF(y_n.eq.'n') y_n='N' 
	IF(y_n.eq.'y') y_n='Y' 
	write(6,*)""   
	IF(y_n.ne.'Y'.and. Y_n.ne.'N') GOTO 7
	IF(y_n.eq.'N') THEN
	 wd_st_ori=wd_st
	 GOTO 5
	ENDIF
	write(6,*)""
	write(6,*)"Working direct:  ",TRIM(wd_st)  
	write(6,*)""
	write(6,*)""
	CMD='mkdir '//TRIM(wd_st)
	CALL SYSTEM(CMD)
	
	
!===================
!
!	fly_fnames section
!
!===================

	fly_name=TRIM(wd_st)//'fly_fnames'

200	write(6,*)""
	write(6,*)"                Starting generation of ",TRIM(fly_name)," file...                    "
	write(6,*)""

	parsfile='stat_pars'
	par1file='dyn_pars'
	fewgrid='ew_grid'
	fewtab='ew_tab'
	fpar35='out32.tab'
	ql_tab='ql.tab'

	OPEN(UNIT=10, FILE=fly_name,STATUS='UNKNOWN')
  	read(10,133,END=205)  parsfile
    	read(10,133,END=205)  par1file
    	read(10,133,END=205)  fewgrid
  	read(10,133,END=205)  fewtab
    	read(10,133,END=205)  fpar35
    	read(10,133,END=205)  ql_tab        
205	CLOSE(UNIT=10)

	parsfile=TRIM(parsfile)
	par1file=TRIM(par1file)
	fewgrid=TRIM(fewgrid)
	fewtab=TRIM(fewtab)
	fpar35=TRIM(fpar35)
	ql_tab=TRIM(ql_tab)

	IF(parsfile.eq."") parsfile='stat_pars'
	IF(par1file.eq."") par1file='dyn_pars'
	IF(fewgrid.eq."") fewgrid='ew_grid'
	IF(fewtab.eq."") fewtab='ew_tab'
	IF(fpar35.eq."") fpar35='out32.tab'
	IF(ql_tab.eq."") ql_tab='ql.tab'

	parsfile_d=TRIM(parsfile)
	par1file_d=TRIM(par1file)
	fewgrid_d=TRIM(fewgrid)
	fewtab_d=TRIM(fewtab)
	fpar35_d=TRIM(fpar35)
	ql_tab_d=TRIM(ql_tab)
	
	
	
210	write(6,100,ADVANCE='NO')"Do you want to create this file (Y/N) : "  
	read(5,FMT='(A1)') y_n
	y_n=TRIM(y_n)
	IF(y_n.eq.'n') y_n='N' 
    	IF(y_n.eq.'y') y_n='Y' 
	write(6,*)""   
	IF(y_n.ne.'Y'.and. y_n.ne.'N') GOTO 210
	IF(y_n.eq.'N') THEN
          write(6,FMT='(3A)',ADVANCE='NO') "WARNING: The",TRIM(fly_name),"  will contain the default names (Y/N) [Y] : "  
	  read(5,FMT='(A1)') y_n
          IF(y_n.eq.'n') y_n='N' 
	  IF(y_n.eq.'N') STOP
	  write(6,*)"Please accept the default input data."   
          GOTO 213
	ENDIF
	write(6,*)""
	write(6,FMT='(3A)')"All NOT-ABSOLUTE filename paths will be ",TRIM(wd_st)," : "  
Loading full blame...