PROGRAM Process_inputs USE Rcm_mod_subs IMPLICIT NONE ! INTEGER (iprec) :: n, nbf REAL (rprec) :: sw_den, sw_vel, sw_p, alpha_ratio INTERFACE FUNCTION Pdynamic_sw (sw_den, sw_vel, ratio_den) ! sw_den is solar wind proton density in cm-3 ! sw_vel is solar wind bulk velocity in km/s ! ratio_den is ratio of alpha particles to proton number density ! Pdynamic_sw is rho*v**2 in nPa ! IF ratio_den is not known, set it to 0 or <0 and the default ! 4% value will be used. IMPLICIT NONE REAL, INTENT (IN) :: sw_den, sw_vel, ratio_den REAL :: Pdynamic_sw END FUNCTION Pdynamic_sw END INTERFACE ! ! ! Read number of input lines: ! OPEN (LUN, FILE = 'inputs.dat', STATUS = 'OLD') READ (LUN,*) READ (LUN,*) nbf = 0 DO READ (LUN,'(A)', END = 20) nbf = nbf + 1 END DO 20 CLOSE (LUN) ! ALLOCATE (ibtime (nbf)) ! OPEN (LUN_2, FILE='rcmpcp_inp', STATUS='REPLACE') OPEN (LUN_3, FILE='rcmkp_inp', STATUS='REPLACE') ! ! OPEN (LUN, FILE = 'inputs.dat', STATUS = 'OLD') READ (LUN,*) READ (LUN,*) ! DO n = 1, nbf READ (LUN,*) ibtime(n), sw_den, sw_vel, alpha_ratio,vdrop, fdst, fmeb, kp, imf_bz fclps=1.0 ftilt=0.0 vdrop_phase = -1.0 ! sw_p = 1.67E-06*(sw_den*(sw_vel)**2) ! sw ram pressure in nPa sw_p = Pdynamic_sw (sw_den, sw_vel, alpha_ratio) ! print*,ibtime(n), imf_bz, sw_p CALL Rcm_inputs_magnetopause (1, imf_bz, sw_p, fstoff) ! WRITE (LUN_2,'(TR2,I9.9,TR5,F7.2,TR5,F5.2)') & ibtime(n), vdrop, vdrop_phase WRITE (LUN_3,'(TR2, I9.9, TR5, F5.2)') ibtime(n), kp ! END DO CLOSE (UNIT = LUN ) CLOSE (UNIT = LUN_2 ) CLOSE (UNIT = LUN_3 ) ! STOP END PROGRAM Process_inputs