SUBROUTINE get_aph USE CommonInfo_Module USE APH_Module USE Hamilt_Module USE SymGroup_Module IMPLICIT NONE !========================================================================================= ! Written by Jeff Crawford ! ! This routine reads in system data such as its symmetry group and the APH grid ! dimensions and arrays ! ! Variables: ! chi_val = array containing APH chi grid points ! deltachi = spacing between APH chi grid points (uniformly spaced) ! deltarho = spacing between APH rho grid points (uniformly spaced) ! group = symmetry group ! nchi = number of APH chi grid points ! ndim = total number of APH grid points ! nrho = number of APH rho grid points ! ntheta = number of APH theta grid points ! rho_val = array containing APH rho grid points ! system = type of system, AAA, ABB, ABC, where repeated characters indicate ! identical species ! theta_val = array containing APH theta grid points !========================================================================================= ! I N T E R N A L S LOGICAL :: debug !CHARACTER(LEN=3) :: system,group CHARACTER(LEN=100) :: filename !========================================================================================= ! A L L O C A T A B L E !========================================================================================= ! N A M E L I S T S !========================================================================================= ! Choose whether to output debug information debug=.false. !========================================================================================= ! Read in APH information filename='APH_grid.bin' OPEN(UNIT=bin_unit9,FILE=TRIM(BinOutdir)//TRIM(filename),FORM='unformatted',STATUS='unknown') ! READ(bin_unit9) system READ(bin_unit9) group ! READ(bin_unit9) nrho READ(bin_unit9) ntheta READ(bin_unit9) nchi ndim=nrho*ntheta*nchi !ALLOCATE(rho_val(nrho),theta_val(ntheta),chi_val(nchi+1)) READ(bin_unit9) rho_val READ(bin_unit9) theta_val READ(bin_unit9) chi_val READ(bin_unit9) deltarho READ(bin_unit9) deltachi CLOSE(UNIT=bin_unit9,STATUS='keep') !========================================================================================= ! Write APH info to log file ! WRITE(Out_Unit,30) 'System Info:' ! WRITE(Out_Unit,32) 'system',system ! WRITE(Out_Unit,32) 'group ',group ! WRITE(Out_Unit,31) 'APH Grid Info:','au' ! WRITE(Out_Unit,33) 'nrho ', nrho, 'rhomin ',rho_val(1) ! WRITE(Out_Unit,33) 'ntheta', ntheta,'rhomax ',rho_val(nrho) ! WRITE(Out_Unit,33) 'nchi ', nchi, 'deltarho',deltarho ! WRITE(Out_Unit,34) 'ndim ', ndim, 'deltachi',deltachi ! WRITE(*,32) 'system',system ! WRITE(*,32) 'group ',group ! 30 FORMAT(/1X,a,/1x,50('-')) ! 31 FORMAT(/1X,a,T44,a,/1x,50('-')) ! 32 FORMAT(1X,a,9('.'),a) ! 33 FORMAT(1X,a,9('.'),I4,6X,a,7('.'),f6.3) ! 34 FORMAT(1X,a,9('.'),I7,3X,a,7('.'),f6.3) !========================================================================================= ! Output debug information IF (debug) THEN CALL write_array(nrho,rho_val,'grid/rho_val.txt') CALL write_array(ntheta,theta_val,'grid/theta_val.txt') CALL write_array(nchi,chi_val,'grid/chi_val.txt') ENDIF END SUBROUTINE get_aph