source: trunk/test/src/RpLibraryF_test.f @ 115

Last change on this file since 115 was 115, checked in by mmc, 18 years ago

Updated all copyright notices.

File size: 3.3 KB
Line 
1c ----------------------------------------------------------------------
2c  TEST: Fortran Rappture Library Test Source.
3c
4c  Simple tests of the Rappture Library Fortran Bindings
5c
6c ======================================================================
7c  AUTHOR:  Derrick S. Kearney, Purdue University
8c  Copyright (c) 2004-2005  Purdue Research Foundation
9c
10c  See the file "license.terms" for information on usage and
11c  redistribution of this file, and for a DISCLAIMER OF ALL WARRANTIES.
12c ======================================================================
13      SUBROUTINE  test_element(lib,path)
14        integer rp_lib_element_obj
15        integer retVal, lib
16        character*100 typ, comp, id, path
17
18        print *,"TESTING ELEMENT: path = ",path
19
20        retVal = rp_lib_element_obj(lib, path)
21
22        print *,"dict key = ",retVal
23
24        ! what happens when you get details for lib?
25        call rp_lib_node_comp(retVal,comp)
26        call rp_lib_node_type(retVal,typ)
27        call rp_lib_node_id(retVal,id)
28
29        print *,"comp = ",comp
30        print *,"type = ",typ
31        print *,"id = ",id
32      END SUBROUTINE  test_element
33
34      SUBROUTINE  test_get_str(lib,path)
35        integer lib
36        character*100 path, retText
37
38        print *,"TESTING GET: path = ",path
39
40        call rp_lib_get(lib, path, retText)
41
42        print *,"retText = ",retText
43      END SUBROUTINE  test_get_str
44
45      SUBROUTINE  test_get_dbl(lib,path)
46        integer lib
47        double precision rslt, rp_lib_get_double
48        character*100 path, retText
49
50        print *,"TESTING GET: path = ",path
51
52        rslt = rp_lib_get_double(lib, path)
53
54        print *,"rslt = ",rslt
55      END SUBROUTINE  test_get_dbl
56
57      program rplib_f_tests
58        IMPLICIT NONE
59
60        integer rp_lib, rp_units_convert_dbl, rp_units_add_presets
61        integer rp_lib_element_obj
62
63        integer driver, ok
64        double precision T, Ef, kT, Emin, Emax, dE, f, E
65        CHARACTER*100 inFile, strVal, path
66        character*40 xy
67
68        call getarg(1,inFile)
69        driver = rp_lib(inFile)
70        ! print *,"dict key = ",driver
71
72        ok = rp_units_add_presets("all")
73
74        ! TESTING ELEMENT
75        !call test_element(driver, "input.number(min)")
76        path = "input.number(min)"
77        call test_element(driver, path)
78        !call rp_lib_get(driver, path, strVal)
79        !print *,"strVal = ",strVal
80
81        ! TESTING GET STRING
82        path = "input.number(min).current"
83        call test_get_str(driver, path)
84
85        ! TESTING GET DOUBLE
86        path = "input.number(min).current"
87        call test_get_dbl(driver, path)
88
89
90        call rp_result(driver)
91      end program rplib_f_tests
92
93!        call rp_lib_get(driver,
94!     +        "input.number(min).current", strVal)
95!        ok = rp_units_convert_dbl(strVal,"K",T)
96!
97!        call rp_lib_get(driver,
98!     +        "input.number(Ef).current", strVal)
99!        ok = rp_units_convert_dbl(strVal,"K",Ef)
100!
101!        kT = 8.61734e-5 * T
102!        Emin = Ef - 10*kT
103!        Emax = Ef + 10*kT
104!
105!        dE = 0.005*(Emax - Emin)
106!
107!        do 10 E=Emin,Emax,dE
108!          f = 1.0/(1.0+exp((E-Ef)/kT))
109!          write(xy,'(E20.12,F13.9,A)') f, E, char(10)
110!          call rp_lib_put_str(driver,
111!     +        "output.curve(f12).component.xy", xy, 1)
112! 10     continue
113!
114!      end program rplib_f_tests
Note: See TracBrowser for help on using the repository browser.