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

Last change on this file since 125 was 125, checked in by dkearney, 19 years ago

1) removed "as" string from c++'s element() function because
the function does not have the capacity to return anything
other than RpLibrary? Instances
2) changed get() functions in library module to return strings.
this change was propagated to matlab, octave, c, fortran, c++
bindings.
3) fixed rpFreeLibrary inside of c interface, now function accepts
a pointer to a pointer to RpLibrary? (lib) and sets *lib equal to
null
4) added doxygen target to makefile. (make docs), to get graphics
you need the program named dot (debian: apt-get install graphviz)
otherwise you will get errors for the portion of the proceedure
where it is trying to create the graphics.

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(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
44
45      SUBROUTINE  test_get_str(lib,path)
46        integer lib
47        character*100 path, retText
48
49        print *,"TESTING GET STRING: path = ",path
50
51        call rp_lib_get_str(lib, path, retText)
52
53        print *,"retText = ",retText
54      END SUBROUTINE  test_get_str
55
56      SUBROUTINE  test_get_dbl(lib,path)
57        integer lib
58        double precision rslt, rp_lib_get_double
59        character*100 path
60
61        print *,"TESTING GET DOUBLE: path = ",path
62
63        rslt = rp_lib_get_double(lib, path)
64
65        print *,"rslt = ",rslt
66      END SUBROUTINE  test_get_dbl
67
68      program rplib_f_tests
69        IMPLICIT NONE
70
71        integer rp_lib
72
73        integer driver
74        CHARACTER*100 inFile, path
75
76        call getarg(1,inFile)
77        driver = rp_lib(inFile)
78        ! print *,"dict key = ",driver
79
80        ! TESTING ELEMENT
81        path = "input.number(min)"
82        call test_element(driver, path)
83
84        ! TESTING GET
85        path = "input.number(min).current"
86        call test_get(driver, path)
87
88        ! TESTING GET STRING
89        path = "input.number(min).current"
90        call test_get_str(driver, path)
91
92        ! TESTING GET DOUBLE
93        path = "input.number(min).current"
94        call test_get_dbl(driver, path)
95
96
97        call rp_result(driver)
98      end program rplib_f_tests
99
100!        call rp_lib_get(driver,
101!     +        "input.number(min).current", strVal)
102!        ok = rp_units_convert_dbl(strVal,"K",T)
103!
104!        call rp_lib_get(driver,
105!     +        "input.number(Ef).current", strVal)
106!        ok = rp_units_convert_dbl(strVal,"K",Ef)
107!
108!        kT = 8.61734e-5 * T
109!        Emin = Ef - 10*kT
110!        Emax = Ef + 10*kT
111!
112!        dE = 0.005*(Emax - Emin)
113!
114!        do 10 E=Emin,Emax,dE
115!          f = 1.0/(1.0+exp((E-Ef)/kT))
116!          write(xy,'(E20.12,F13.9,A)') f, E, char(10)
117!          call rp_lib_put_str(driver,
118!     +        "output.curve(f12).component.xy", xy, 1)
119! 10     continue
120!
121!      end program rplib_f_tests
Note: See TracBrowser for help on using the repository browser.