PROGRAM test_fluxtable ! PURPOSE: Used to test the flux table (flux_table.f90). ! Shows the structure of the main program and calling ! sequence of include files and subroutines. ! - The correct calling sequence greatly ! improves the time efficiency of the flux table. ! This is important when incorporting the flux table ! into a larger model. ! - The steps for using the flux table are labeled ! in sequential order below !(1) Access module ! - MODULE used to store flux table data and associated ! transfer coefficients USE flux IMPLICIT NONE !(2) Declare and define input/output variables for the flux table ! - If no input data file then follow (2a) ! - If reading input data file then follow (2b) ! - Input variables: 'u' wind speed [m/s] ! 'v' wind speed [m/s] ! sea surface temperature [Celsius] ! air temperature [Celsius] ! reference height [m] ! significant wave height [m] ! 'u' orbital velocity [m/s] ! 'v' orbital velocity [m/s] ! specific humidity (surface) [kg/kg] ! specific humidity (ref. height) [kg/kg] ! surface pressure [Pa] ! - Output variables: 'u' component of stress [N/m^2] ! 'v' component of stress [N/m^2] ! sensible heat flux [W/m^2] ! latent heat flux [W/m^2] !(2a) !REAL :: u, v, sst, at, ref_ht, Hsig, u_orb, v_orb, qs, q, press !REAL :: tau_u, tau_v, shf, lhf !u = 15.7 !v = 0.0 !sst = 6.1 !at = 5.2 !ref_height = 10.0 !Hsig = 0.0 !u_orb = 0.0 !v_orb = 0.0 !qs = 0.006 !q = 0.005 !press = 101325.0 !(2b) If input data being read then call your read subroutine ! (e.g. read_your_data.f90) ! - Input variables not being read in must be defined INTEGER i INTEGER, PARAMETER :: dim=51 REAL, DIMENSION(dim) :: u,sst,at,qs,q REAL :: v,ref_height,Hsig,u_orb,v_orb,press REAL tau_u,tau_v,shf,lhf REAL,DIMENSION(dim) :: tauu_out,tauv_out,shf_out,lhf_out ! Variables not read in are defined as follows v = 0.0 ref_height = 10.0 u_orb = 0.0 v_orb = 0.0 Hsig = 0.0 press = 101325.0 ! Read input data CALL read_your_data(u,at,qs,q,sst) !(3) Call subroutine (read_data.f90) to read in flux table data ! and associated transfer coefficients CALL read_data !(4) Call flux table (flux_table.f90) ! - If (2a) then follow (4a) ! - If (2b) then follow (4b) ! - Output variables: 'u' stress [N/m^2] ! 'v' stress [N/m^2] ! sensible heat flux [W/m^2] ! latent heat flux [W/m^2] !(4a) !CALL flux_table(u,v,sst,at,ref_ht,Hsig,u_orb,v_orb,qs,q, & ! press,tau_u,tau_v,shf,lhf) ! Print output (u-stress, v-stress, shf, lhf) !WRITE(*,*) 'tau_u = ', tau_u !WRITE(*,*) 'tau_v = ', tau_v !WRITE(*,*) 'shf = ', shf !WRITE(*,*) 'lhf = ', lhf !(4b) DO i=1,51 CALL flux_table(u(i),v,sst(i),at(i),ref_height, & Hsig,u_orb,v_orb,qs(i),q(i),press, & tau_u,tau_v,shf,lhf) !Output from flux table (e.g. u-stress, v-stress, shf, and lhf) ! - In this example output variables are written to a ! file (output.dat) for comparison purposes tauu_out(i) = tau_u tauv_out(i) = tau_v shf_out(i) = shf lhf_out(i) = lhf END DO OPEN(UNIT=20, file='output90.dat', STATUS='NEW',ACTION='WRITE') DO i=1,14 WRITE(20,*) i,tauu_out(i),shf_out(i),lhf_out(i) END DO CLOSE (UNIT=20) END PROGRAM test_fluxtable