PROGRAM test_lookup_kara ! PURPOSE: Used to test the lookup table (lookup_kara.f90). Shows ! the structure of the structure of the main program and ! calling sequence of module and subroutines ! ! COMMENTS: (1) The correct calling sequence greatly improves the ! the time ifficiency of the lookup table. This is ! important when incorporating the lookup table ! into a larger model ! ! (2) The steps for using the lookup table are labeled in ! sequential order below !(1) Access module USE lookup_kara_mod !(2) Declare and define input/output variables for the lookup table ! ! - In this test program a file containing the input variables ! is read IMPLICIT NONE INTEGER :: i REAL, DIMENSION(20) :: spd, ustar, ustar_sq, sst, tair, tdif REAL, DIMENSION(20) :: spd_table REAL :: output CHARACTER(60) :: file1 file1='test_input_data.dat' OPEN(UNIT=12,FILE=file1,STATUS='OLD') DO i=1,20 READ(12,*) spd(i), ustar(i), ustar_sq(i), sst(i), tair(i), tdif(i) END DO CLOSE(UNIT=12) !(3) Call subroutine (read_lookup_data.f90) to read in lookup table data ! and associated 10 meter wind speed CALL read_lookup_data !(4) Call lookup table (lookup_kara.f90) DO i=1,20 !ustar^2 = stress/density CALL lookup_kara(ustar_sq(i),sst(i),tair(i),output) spd_table(i) = output WRITE(*,'(A,I2,A,1X,A,1X,F4.1)') 'i =',i,',', 'wind speed =',spd_table(i) END DO !Validation. The above output should match the following: ! !i = 1, wind speed = 1.3 !i = 2, wind speed = 2.2 !i = 3, wind speed = 3.1 !i = 4, wind speed = 3.8 !i = 5, wind speed = 5.0 !i = 6, wind speed = 6.1 !i = 7, wind speed = 7.0 !i = 8, wind speed = 8.0 !i = 9, wind speed = 9.1 !i =10, wind speed = 10.0 !i =11, wind speed = 11.1 !i =12, wind speed = 12.0 !i =13, wind speed = 13.0 !i =14, wind speed = 14.0 !i =15, wind speed = 15.0 !i =16, wind speed = 16.0 !i =17, wind speed = 17.1 !i =18, wind speed = 18.0 !i =19, wind speed = 19.0 !i =20, wind speed = 20.1 END PROGRAM test_lookup_kara