Changeset 83 for trunk


Ignore:
Timestamp:
Oct 5, 2005 8:17:26 AM (18 years ago)
Author:
dkearney
Message:
  1. More cleaning of RpUnits and RpLibrary? code
  2. added rp_result code to c++/fortran/c code
  3. added rp_children, rp_lib_node[comp,type,id] for fortran code (need to test)
  4. adjusted convert function to recognize statements as follows:

convert("5J","neV")
convert("3.12075e+28neV","J")

  1. made joules a metric unit in RpUnits.cc
  2. tested examples/app-fermi/fortran/fermi.f with new rappture library.

added units conversion.

Location:
trunk
Files:
1 added
21 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/examples/app-fermi/fortran/Makefile

    r73 r83  
    1414
    1515LIB_DIR = $(RAPPTURE_DIR)/lib
    16 LIB_RAPPTURE    = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture
     16LIB_RAPPTURE    = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture_test
    1717
    1818all: $(PROGS)
  • trunk/examples/app-fermi/fortran/fermi.f

    r66 r83  
    1313        IMPLICIT NONE
    1414
    15         integer rp_lib
    16         double precision rp_lib_get_double
     15        integer rp_lib, rp_units_convert_dbl, rp_units_add_presets
    1716
    18         integer driver
     17        integer driver, ok
    1918        double precision T, Ef, kT, Emin, Emax, dE, f, E
    20         CHARACTER*100 inFile
     19        CHARACTER*100 inFile, strVal
    2120        character*40 xy
    2221
     
    2423        driver = rp_lib(inFile)
    2524
    26         T = rp_lib_get_double(driver,
    27      +        "input.number(temperature).current")
    28         Ef = rp_lib_get_double(driver,
    29      +        "input.number(Ef).current")
     25        ok = rp_units_add_presets("all")
     26
     27        call rp_lib_get(driver,
     28     +        "input.number(temperature).current", strVal)
     29        ok = rp_units_convert_dbl(strVal,"K",T)
     30
     31        call rp_lib_get(driver,
     32     +        "input.number(Ef).current", strVal)
     33        ok = rp_units_convert_dbl(strVal,"K",Ef)
    3034
    3135        kT = 8.61734e-5 * T
  • trunk/gui/scripts/units.tcl

    r56 r83  
    476476
    477477Rappture::Units::define eV -type energy -metric yes
     478Rappture::Units::define J->eV {J/1.602177e-19} {eV*1.602177e-19}
    478479
    479480Rappture::Units::define V -type voltage -metric yes
  • trunk/include/cee/RpLibraryCInterface.h

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: C Rappture Library Header
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
    111
    212
     
    7282    const char* nodeId              (RpLibrary* node);
    7383
     84    void        result              (RpLibrary* lib);
     85
    7486#ifdef __cplusplus
    7587}
  • trunk/include/cee/RpUnitsCInterface.h

    r76 r83  
    1 
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: C Rappture Units Header
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
    211
    312#ifdef __cplusplus
     
    2029
    2130    const char* getUnitsName(RpUnits* unit);
    22    
     31
    2332    double getExponent(RpUnits* unit);
    24    
     33
    2534    RpUnits* getBasis(RpUnits* unit);
    2635
     
    3544                            int showUnits,
    3645                            int* result );
    37    
     46
    3847    const char* convert_str (   const char* fromVal,
    3948                                const char* toUnitsName,
    4049                                int showUnits,
    4150                                int* result );
    42    
     51
    4352    const char* convert_obj_str (   RpUnits* fromUnits,
    4453                                    RpUnits* toUnits,
    4554                                    double val,
    4655                                    int showUnits   );
    47    
     56
    4857    const char* convert_obj_str_result( RpUnits* fromUnits,
    4958                                        RpUnits* toUnits,
     
    5564                            const char* toUnitsName,
    5665                            int* result );
    57    
     66
    5867    double convert_obj_double ( RpUnits* fromUnits,
    5968                                RpUnits* toUnits,
  • trunk/include/core/RpLibrary.h

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  Rappture Library Header
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
    111
    212#include "scew.h"
     
    515#include <string>
    616#include <sstream>
     17#include <fstream>
    718#include <stdlib.h>
    819#include <errno.h>
     20#include <time.h>
    921
    1022/* indentation size (in whitespaces) */
     
    1729{
    1830    public:
    19        
     31
    2032        // users member fxns
    2133
    2234        RpLibrary* element (std::string path = "", std::string as = "object");
     35
    2336        // should return RpObject& but for simplicity right now it doesnt
    2437        // RpObject will either be an Array, RpString, RpNumber ...
    25         /*
    26         RpLibrary** children (  std::string path = "",
    27                                 std::string as = "object",
    28                                 std::string type = ""   );
    29         */
    30 
    31         RpLibrary*  children (  std::string path = "",
    32                                 RpLibrary* rpChildNode = NULL,
     38
     39        RpLibrary*  children (  std::string path = "",
     40                                RpLibrary* rpChildNode = NULL,
    3341                                std::string type = "",
    3442                                int* childCount = NULL  );
     
    4250                            std::string id = "",
    4351                            int append = 0  );
    44        
     52
    4553        RpLibrary& put (    std::string path,
    4654                            double value,
     
    5563        std::string nodeId();
    5664        std::string nodeComp();
    57        
     65
     66        void result();
    5867        const char* nodeTypeC();
    5968        const char* nodeIdC();
     
    6776                tree        (NULL),
    6877                root        (NULL)
    69                    
    7078        {
    7179            tree = scew_tree_create();
     
    8189                root        (NULL)
    8290        {
    83            
     91
    8492            if (filePath.length() != 0) {
    8593                // file path should not be null or empty string unless we are
     
    105113                    if (code == scew_error_expat)
    106114                    {
    107                         enum XML_Error expat_code = 
     115                        enum XML_Error expat_code =
    108116                            scew_error_expat_code(parser);
    109                         printf("Expat error #%d (line %d, column %d): %s\n", 
     117                        printf("Expat error #%d (line %d, column %d): %s\n",
    110118                               expat_code,
    111119                               scew_error_expat_line(parser),
     
    115123                    // should probably exit program or something
    116124                    // return EXIT_FAILURE;
    117                    
     125
    118126                }
    119127
     
    127135        }
    128136
    129        
     137
    130138        // copy constructor
    131139        // for some reason making this a const gives me problems when calling xml()
     
    149157            buffer = other.xml();
    150158            buffLen = buffer.length();
    151            
     159
    152160            if (buffLen > 0) {
    153161                if (!scew_parser_load_buffer(parser,buffer.c_str(),buffLen))
     
    161169                    if (code == scew_error_expat)
    162170                    {
    163                         enum XML_Error expat_code = 
     171                        enum XML_Error expat_code =
    164172                            scew_error_expat_code(parser);
    165173                        printf("Expat error #%d (line %d, column %d): %s\n",
     
    172180                    // return an empty RpLibrary?
    173181                    // return EXIT_FAILURE;
    174                    
     182
    175183                    parser = NULL;
    176184                }
     
    214222
    215223                // Loads the XML from other
    216                 // the length cannot be 0 because xml() should not be returning 
     224                // the length cannot be 0 because xml() should not be returning
    217225                // empty strings
    218226                buffer = other.xml();
    219227                buffLen = buffer.length();
    220                
     228
    221229                if (buffLen > 0) {
    222230                    if (!scew_parser_load_buffer(parser,buffer.c_str(),buffLen))
     
    242250                        // or maybe return an empty RpLibrary?
    243251                        // return EXIT_FAILURE;
    244                        
     252
    245253                        // return this object to its previous state.
    246254                        parser = tmp_parser;
     
    256264
    257265                        // free the current RpLibrary's data
    258                         // we do the free so far down so we can see if 
     266                        // we do the free so far down so we can see if
    259267                        // parsing the other object's xml fails.
    260                         // if the parsing fails, we can still return this 
     268                        // if the parsing fails, we can still return this
    261269                        // object to its previous state.
    262270                        if (tmp_tree && tmp_freeTree) {
     
    278286            return *this;
    279287        } // end operator=
    280                
     288
    281289
    282290        // default destructor
     
    304312        scew_tree* tree;
    305313        scew_element* root;
    306        
    307         // flag to tell if we are responsible for calling scew_tree_free
    308         // on the tree structure. if we get our tree by using the scew_tree_create
    309         // fxn, we need to free it. if we get our tree using the scew_parser_tree
     314
     315        // flag to tell if we are responsible for calling scew_tree_free
     316        // on the tree structure. if we get our tree by using the
     317        // scew_tree_create
     318        // fxn, we need to free it. if we get our tree using the
     319        // scew_parser_tree
    310320        // fxn, then it will be free'd when the parser is free'd.
    311321        int freeTree;
     
    316326                tree        (NULL),
    317327                root        (node)
    318                    
     328
    319329        {}
    320330
     
    324334        std::string _node2name (scew_element* node);
    325335        std::string _node2comp (scew_element* node);
    326         int _splitPath (std::string& path, 
    327                         std::string& tagName, 
    328                         int* idx, 
     336        int _splitPath (std::string& path,
     337                        std::string& tagName,
     338                        int* idx,
    329339                        std::string& id );
    330         scew_element* _find (std::string path, int create); 
     340        scew_element* _find (std::string path, int create);
    331341        void print_indent (unsigned int indent, std::stringstream& outString);
    332342        void print_attributes (scew_element* element, std::stringstream& outString);
    333         void print_element( scew_element* element, 
    334                             unsigned int indent, 
     343        void print_element( scew_element* element,
     344                            unsigned int indent,
    335345                            std::stringstream& outString    );
    336346
  • trunk/include/core/RpUnits.h

    r76 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  RpUnits.h - Header file for Rappture Units
     4 *
     5 *   RpUnits Class Declaration / Definition
     6 *
     7 * ======================================================================
     8 *  AUTHOR:  Derrick Kearney, Purdue University
     9 *  Copyright (c) 2004-2005
     10 *  Purdue Research Foundation, West Lafayette, IN
     11 * ======================================================================
     12 */
     13
    114#include <iostream>
    215#include <string>
     
    1124#include "RpUnitsStd.h"
    1225
    13 #ifndef _RpUNITS_H 
     26#ifndef _RpUNITS_H
    1427#define _RpUNITS_H
    1528
    16 class RpUnits; 
     29class RpUnits;
    1730
    1831class unit
     
    3043        const std::string units;
    3144        double exponent;
    32         // RpUnits* basis[4];
    33         RpUnits* basis;
     45        RpUnits* basis;
    3446
    3547        unit* prev;
    3648        unit* next;
    3749
    38         unit (
    39                 const std::string& units,
    40                 double&            exponent,
    41                 // RpUnits**           basis,
    42                 RpUnits*           basis, 
     50        // private constructor
     51        unit (
     52                const std::string& units,
     53                double&            exponent,
     54                RpUnits*           basis,
    4355                unit*              next
    4456             )
    45             :   units    (units), 
    46                 exponent (exponent), 
    47                 basis    (basis), 
     57            :   units    (units),
     58                exponent (exponent),
     59                basis    (basis),
    4860                prev     (NULL),
    4961                next     (next)
    50             { };
    51 
     62            {};
     63
     64        /*
     65        // private copy constructor
     66        unit ( unit& other )
     67            :   units       (other.units),
     68                exponent    (other.exponent),
     69                basis       (other.basis),
     70                prev        (other.prev),
     71                next        (other.next)
     72            {};
     73
     74        // copy assignment operator
     75        unit& operator= (unit& other) {
     76            units       = other.units;
     77            exponent    = other.exponent;
     78            basis       = other.basis;
     79            prev        = other.prev;
     80            next        = other.next;
     81        }
     82
     83        // destructor (its not virtual yet, still testing)
     84        ~unit () {
     85
     86        }
     87        */
    5288
    5389        void newExponent(double newExponent) {exponent = newExponent;};
     
    6197// hold the pointer to a function to do the forward conversion (from->to)
    6298// hold the pointer to a function to do the backward conversion (to->from)
    63 // 
     99//
    64100class conversion
    65101{
     
    68104        const RpUnits* getFrom()    { return (const RpUnits*) fromPtr; };
    69105        const RpUnits* getTo()      { return (const RpUnits*) toPtr; };
    70        
     106
    71107        friend class RpUnits;
    72108
     
    86122
    87123        // constructor
    88         // private because i only want RpUnits to be able to 
     124        // private because i only want RpUnits to be able to
    89125        // create a conversion
    90         conversion ( 
    91                 RpUnits* fromPtr, 
    92                 RpUnits* toPtr, 
     126        conversion (
     127                RpUnits* fromPtr,
     128                RpUnits* toPtr,
    93129                double (*convForwFxnPtr)(double),
    94130                double (*convBackFxnPtr)(double),
     
    97133             )
    98134            :   fromPtr             (fromPtr),
    99                 toPtr               (toPtr), 
     135                toPtr               (toPtr),
    100136                convForwFxnPtr      (convForwFxnPtr),
    101137                convBackFxnPtr      (convBackFxnPtr),
     
    106142                prev                (prev),
    107143                next                (next)
    108             {
    109             };
    110 
    111         conversion (
     144            {};
     145
     146        conversion (
    112147                RpUnits* fromPtr,
    113148                RpUnits* toPtr,
     
    120155             )
    121156            :   fromPtr             (fromPtr),
    122                 toPtr               (toPtr), 
     157                toPtr               (toPtr),
    123158                convForwFxnPtr      (NULL),
    124159                convBackFxnPtr      (NULL),
     
    129164                prev                (prev),
    130165                next                (next)
    131             {
    132             };
     166            {};
    133167
    134168        // copy constructor
     
    139173// used by the RpUnits class to create a linked list of the conversions
    140174// associated with the specific unit.
    141 // 
     175//
    142176// we could templitize this and make a generic linked list
    143177// or could use generic linked list class from book programming with objects
     
    156190        convEntry*  next;
    157191
    158         convEntry ( 
    159                 conversion* conv, 
     192        convEntry (
     193                conversion* conv,
    160194                convEntry*  prev,
    161195                convEntry*  next
    162196             )
    163             :   conv    (conv), 
     197            :   conv    (conv),
    164198                prev    (prev),
    165199                next    (next)
    166             { };
     200            {};
    167201
    168202        /*
     
    176210class RpUnits
    177211{
    178     /* 
     212    /*
    179213     * helpful units site
    180214     * http://aurora.regenstrief.org/~gunther/units.html
     
    182216
    183217    public:
    184        
     218
    185219        // users member fxns
    186220        std::string getUnits();
     
    190224
    191225        // convert from one RpUnits to another if the conversion is defined
    192         double convert(RpUnits* toUnits, double val, int* result = NULL); 
     226        double convert(RpUnits* toUnits, double val, int* result = NULL);
    193227        // convert from one RpUnits to another if the conversion is defined
    194         void* convert(RpUnits* toUnits, void* val, int* result = NULL); 
     228        void* convert(RpUnits* toUnits, void* val, int* result = NULL);
    195229        // convert from one RpUnits to another if the conversion is defined
    196         double convert(std::string, double val); 
     230        double convert(std::string, double val);
    197231        // convert from one RpUnits to another if the conversion is defined
    198         std::string convert (   RpUnits* toUnits, 
    199                                 double val, 
    200                                 int showUnits = 0, 
    201                                 int* result = NULL  ); 
     232        std::string convert (   RpUnits* toUnits,
     233                                double val,
     234                                int showUnits = 0,
     235                                int* result = NULL  );
    202236
    203237        static std::string convert ( std::string val,
     
    210244
    211245        // turn the current unit to the metric system
    212         // this should only be used for units that are part of the 
     246        // this should only be used for units that are part of the
    213247        // metric system. doesnt deal with exponents, just prefixes
    214248        double makeBasis(double value, int* result = NULL);
    215249        RpUnits & makeBasis(double* value, int* result = NULL);
    216        
     250
    217251        static int makeMetric(RpUnits * basis);
    218252
     
    222256        static RpUnits* find(std::string key)
    223257        {
    224             // dict.find seems to return a (RpUnits* const) so i had to 
     258            // dict.find seems to return a (RpUnits* const) so i had to
    225259            // cast it as a (RpUnits*)
    226260
    227261            // dict pointer
    228              // RpUnits* unitEntry = (RpUnits*) *(dict.find(key).getValue());
    229              RpUnits* unitEntry = (RpUnits*) *(dict->find(key).getValue());
    230 
    231             // RpUnits* unitEntry = (RpUnits*) dEntr.getValue();
     262            RpUnits* unitEntry = (RpUnits*) *(dict->find(key).getValue());
    232263
    233264            // dict pointer
    234             // if (unitEntry == (RpUnits*)dict.getNullEntry().getValue()) {
    235265            if (unitEntry == (RpUnits*)dict->getNullEntry().getValue()) {
    236266                unitEntry = NULL;
     
    246276        static RpUnits * defineCmplx(const std::string units,RpUnits * basis);
    247277        //
    248         // add relation rule 
    249 
    250         static RpUnits * define(RpUnits* from, 
    251                                 RpUnits* to, 
     278        // add relation rule
     279
     280        static RpUnits * define(RpUnits* from,
     281                                RpUnits* to,
    252282                                double (*convForwFxnPtr)(double),
    253283                                double (*convBackFxnPtr)(double));
    254284
    255         static RpUnits * define(RpUnits* from, 
    256                                 RpUnits* to, 
     285        static RpUnits * define(RpUnits* from,
     286                                RpUnits* to,
    257287                                void* (*convForwFxnPtr)(void*, void*),
    258288                                void* convForwData,
     
    271301        static int addPresets (std::string group);
    272302
    273         // undefining a relation rule is probably not needed 
     303        // undefining a relation rule is probably not needed
    274304        // int undefine(); // delete a relation
    275305
     
    279309
    280310        // why are these functions friends...
    281         // probably need to find a better way to let RpUnits 
     311        // probably need to find a better way to let RpUnits
    282312        // use the RpDict and RpDictEntry fxns
    283313        friend class RpDict<std::string,RpUnits*>;
     
    286316        // copy constructor
    287317        RpUnits ( const RpUnits& myRpUnit )
    288         { 
     318        {
    289319
    290320            /*
     
    295325            */
    296326
    297             // copy constructor for unit 
     327            // copy constructor for unit
    298328            unit* tmp = NULL;
    299329            unit* newUnit = NULL;
     
    319349
    320350            head = tmp;
    321                
     351
    322352        };
    323        
     353
    324354        /*
     355        // copy assignment operator
    325356        RpUnits& operator= (const RpUnits& myRpUnit) {
    326357
     
    332363        }
    333364        */
    334        
     365
    335366    private:
    336367
     
    348379        // move through the linked list, only converting the metric elements.
    349380        //
    350        
     381
    351382        // used by the RpUnits when defining units elements
    352383        unit* head;
     
    371402
    372403
    373         RpUnits (
    374                     const std::string& units,
    375                     double& exponent,
    376                     // RpUnits* basis[]
     404        RpUnits (
     405                    const std::string& units,
     406                    double& exponent,
    377407                    RpUnits* basis
    378408                )
     
    386416
    387417
    388        
    389         RpUnits ( 
     418
     419        RpUnits (
    390420                    RpUnits* from,
    391421                    RpUnits* to,
     
    397427            :   head (NULL),
    398428                convList (NULL),
    399                 conv (new conversion 
     429                conv (new conversion
    400430                        (from,to,convForwFxnPtr,convBackFxnPtr,prev,next))
    401         { 
     431        {
    402432            connectConversion(from);
    403433            connectConversion(to);
     
    407437
    408438
    409        
    410         RpUnits ( 
     439
     440        RpUnits (
    411441                    RpUnits* from,
    412442                    RpUnits* to,
     
    426456                                     )
    427457                     )
    428         { 
     458        {
    429459            connectConversion(from);
    430460            connectConversion(to);
     
    457487        // returns 0 on success (object inserted or already exists)
    458488        // returns !0 on failure (object cannot be inserted or dne)
    459         int RpUnits::insert(std::string key);   
     489        int RpUnits::insert(std::string key);
    460490
    461491        // link two RpUnits objects that already exist in RpUnitsTable
  • trunk/include/fortran/RpFortranCommon.h

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Common Functions
     4 *
     5 *    Fortran functions common to all interfaces.
     6 *
     7 * ======================================================================
     8 *  AUTHOR:  Derrick Kearney, Purdue University
     9 *  Copyright (c) 2005
     10 *  Purdue Research Foundation, West Lafayette, IN
     11 * ======================================================================
     12 */
    113
    214#include <stdlib.h>
     
    921
    1022
    11 #ifdef __cplusplus 
     23#ifdef __cplusplus
    1224extern "C" {
    1325#endif
     
    1729void fortranify(const char* inBuff, char* retText, int retTextLen);
    1830
    19 #ifdef __cplusplus 
     31#ifdef __cplusplus
    2032}
    2133#endif
  • trunk/include/fortran/RpLibraryFInterface.h

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Library Header
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
    111
    212#include "RpLibrary.h"
     
    3646#   define rp_lib_write_xml        rp_lib_write_xml_
    3747#   define rp_lib_xml              rp_lib_xml_
     48#   define rp_lib_node_comp        rp_lib_node_comp_
     49#   define rp_lib_node_type        rp_lib_node_type_
     50#   define rp_lib_node_id          rp_lib_node_id_
     51#   define rp_result               rp_result_
    3852#   define rp_quit                 rp_quit_
    3953#elif defined(COMPNAME_ADD2UNDERSCORE)
     
    5973#   define rp_lib_write_xml        rp_lib_write_xml__
    6074#   define rp_lib_xml              rp_lib_xml__
     75#   define rp_lib_node_comp        rp_lib_node_comp__
     76#   define rp_lib_node_type        rp_lib_node_type__
     77#   define rp_lib_node_id          rp_lib_node_id__
     78#   define rp_result               rp_result__
    6179#   define rp_quit                 rp_quit__
    6280#elif defined(COMPNAME_NOCHANGE)
     
    82100#   define rp_lib_write_xml        rp_lib_write_xml
    83101#   define rp_lib_xml              rp_lib_xml
     102#   define rp_lib_node_comp        rp_lib_node_comp
     103#   define rp_lib_node_type        rp_lib_node_type
     104#   define rp_lib_node_id          rp_lib_node_id
     105#   define rp_result               rp_result
    84106#   define rp_quit                 rp_quit
    85107#elif defined(COMPNAME_UPPERCASE)
     
    105127#   define rp_lib_write_xml        RP_LIB_WRITE_XML
    106128#   define rp_lib_xml              RP_LIB_XML
     129#   define rp_lib_node_comp        RP_LIB_NODE_COMP
     130#   define rp_lib_node_type        RP_LIB_NODE_TYPE
     131#   define rp_lib_node_id          RP_LIB_NODE_ID
     132#   define rp_result               RP_RESULT
    107133#   define rp_quit                 RP_QUIT
    108134#endif
     
    111137void rp_init();
    112138
    113 int rp_lib(const char* filePath, int filePath_len);
    114 
    115 void rp_lib_element_comp( int* handle,
    116                             char* path,
    117                             char* retText,
    118                             int path_len,
    119                             int retText_len );
    120 
    121 void rp_lib_element_id(   int* handle,
    122                             char* path,
    123                             char* retText,
    124                             int path_len,
    125                             int retText_len );
    126 
    127 void rp_lib_element_type( int* handle,
    128                             char* path,
    129                             char* retText,
    130                             int path_len,
    131                             int retText_len );
    132 
    133 int rp_lib_element_obj(   int* handle,
     139int rp_lib ( const char* filePath, int filePath_len );
     140
     141void rp_lib_element_comp (  int* handle,
     142                            char* path,
     143                            char* retText,
     144                            int path_len,
     145                            int retText_len );
     146
     147void rp_lib_element_id (    int* handle,
     148                            char* path,
     149                            char* retText,
     150                            int path_len,
     151                            int retText_len );
     152
     153void rp_lib_element_type ( int* handle,
     154                            char* path,
     155                            char* retText,
     156                            int path_len,
     157                            int retText_len );
     158
     159int rp_lib_element_obj (    int* handle,
    134160                            char* path,
    135161                            int path_len );
    136162
    137 int rp_lib_child_num(    int* handle,
    138                             char* path,
     163int rp_lib_child_num (      int* handle,
     164                            char* path,
     165                            int* childHandle,
    139166                            int path_len);
    140167
    141 int rp_lib_child_comp(   int* handle,    /* integer handle of library */
    142                             char* path,     /* DOM path of requested object */
    143                             char* type,     /* specific name of element */
    144                             int* childNum,  /* child number for iteration */
    145                             char* retText,  /* buffer to store return text */
    146                             int path_len,   /* length of path */
    147                             int type_len,   /* length of type */
    148                             int retText_len /* length of return text buffer */
    149                        );
    150 
    151 int rp_lib_child_id(     int* handle,    /* integer handle of library */
    152                             char* path,     /* DOM path of requested object */
    153                             char* type,     /* specific name of element */
    154                             int* childNum,  /* child number for iteration */
    155                             char* retText,  /* buffer to store return text */
    156                             int path_len,   /* length of path */
    157                             int type_len,   /* length of type */
    158                             int retText_len /* length of return text buffer */
    159                        );
    160 
    161 int rp_lib_child_type(   int* handle,    /* integer handle of library */
    162                             char* path,     /* DOM path of requested object */
    163                             char* type,     /* specific name of element */
    164                             int* childNum,  /* child number for iteration */
    165                             char* retText,  /* buffer to store return text */
    166                             int path_len,   /* length of path */
    167                             int type_len,   /* length of type */
    168                             int retText_len /* length of return text buffer */
    169                        );
    170 
    171 int rp_lib_child_obj(    int* handle,
    172                             char* path,
    173                             char* type,
    174                             int path_len,
    175                             int type_len
    176                           );
    177 
    178 void rp_lib_get(          int* handle,
    179                             char* path,
    180                             char* retText,
    181                             int path_len,
    182                             int retText_len );
    183 
    184 double rp_lib_get_double( int* handle,
     168int rp_lib_children (       int* handle, /* integer handle of library */
     169                            char* path, /* search path of the xml */
     170                            int* childHandle, /*int handle of last returned child*/
     171                            int path_len  /*length of the search path buffer*/
     172                    );
     173
     174
     175void rp_lib_get (           int* handle,
     176                            char* path,
     177                            char* retText,
     178                            int path_len,
     179                            int retText_len );
     180
     181double rp_lib_get_double (  int* handle,
    185182                            char* path,
    186183                            int path_len);
    187184
    188 void rp_lib_put_str(     int* handle,
     185void rp_lib_put_str (       int* handle,
    189186                            char* path,
    190187                            char* value,
     
    193190                            int value_len );
    194191
    195 void rp_lib_put_id_str(  int* handle,
     192void rp_lib_put_id_str (    int* handle,
    196193                            char* path,
    197194                            char* value,
     
    202199                            int id_len );
    203200
    204 void rp_lib_put_obj(     int* handle,
     201void rp_lib_put_obj (       int* handle,
    205202                            char* path,
    206203                            int* valHandle,
     
    208205                            int path_len );
    209206
    210 void rp_lib_put_id_obj(  int* handle,
     207void rp_lib_put_id_obj (    int* handle,
    211208                            char* path,
    212209                            int* valHandle,
     
    216213                            int id_len );
    217214
    218 int rp_lib_remove(       int* handle,
    219                             char* path, 
     215int rp_lib_remove (         int* handle,
     216                            char* path,
    220217                            int path_len);
    221218
    222 int rp_lib_xml_len(      int* handle);
    223 
    224 void rp_lib_xml(         int* handle,
    225                             char* retText, 
    226                             int retText_len);
    227 
    228 int rp_lib_write_xml(     int* handle,
    229                             char* outFile, 
     219int rp_lib_xml_len(         int* handle);
     220
     221void rp_lib_xml(            int* handle,
     222                            char* retText,
     223                            int retText_len);
     224
     225int rp_lib_write_xml(       int* handle,
     226                            char* outFile,
    230227                            int outFile_len);
     228
     229void rp_lib_node_comp (     int* handle,
     230                            char* retText,
     231                            int retText_len);
     232
     233void rp_lib_node_type (     int* handle,
     234                            char* retText,
     235                            int retText_len);
     236
     237void rp_lib_node_id (       int* handle,
     238                            char* retText,
     239                            int retText_len);
     240
     241void rp_result(             int* handle );
     242
    231243void rp_quit();
    232244
  • trunk/include/fortran/RpUnitsFInterface.h

    r76 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Units Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
     11
    112#include "RpFortranCommon.h"
    213
  • trunk/src/Makefile

    r77 r83  
    1414LIB_SCEW_INCL   = -I $(SCEW_HEADERS)
    1515LIB_SCEW_FLAG   = -L/opt/rappture/lib -lscew
     16#LIB_SCEW_FLAG  = /opt/rappture/lib/libscew.a
    1617#LIB_SCEW_FLAG  = -static -L/opt/rappture/lib -lscew
    1718
     
    100101
    101102RP_IO_DEPS              = RpLibrary.o RpLibraryCInterface.o RpLibraryFInterface.o scew_extras.o
    102 RP_UNITS_DEPS   =  RpUnitsStd.o RpUnits.o RpUnitsCInterface.o RpUnitsFInterface.o
     103RP_UNITS_DEPS   = RpUnitsStd.o RpUnits.o RpUnitsCInterface.o RpUnitsFInterface.o
    103104RP_OTHER_DEPS   = RpFortranCommon.o
    104105
     
    121122#### libRpObjects ########################################################
    122123libRpObjects: RpVariable.o RpAbout.o RpNumber.o RpString.o RpBoolean.o RpChoice.o RpOption.o RpUnitsStd.o RpUnits.o
    123         $(CXX) $(DEGUG) -shared -Wl,-rpath,$(LIB_DIR)/ \
    124                 -Wl,-soname,$@.so -o $(LIB_DIR)/$@.so.0.0 $^
     124        $(CC) $(DEGUG) -shared -Wl,-rpath,$(LIB_DIR)/ \
     125                -Wl,-soname,$@.so -o $(LIB_DIR)/$@.so.0.0 $^ -lstdc++
     126#       $(CXX) $(DEGUG) -shared -Wl,-rpath,$(LIB_DIR)/ \
     127#               -Wl,-soname,$@.so -o $(LIB_DIR)/$@.so.0.0 $^
    125128       
    126129        /sbin/ldconfig -n $(LIB_DIR)
  • trunk/src/cee/RpLibraryCInterface.cc

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: C Rappture Library Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
     11
    112#include "RpLibrary.h"
    213#include "RpLibraryCInterface.h"
     
    617#endif
    718
    8     RpLibrary* 
     19    RpLibrary*
    920    library (const char* path)
    1021    {
     
    2435        return lib->element(path);
    2536    }
    26    
    27     RpLibrary* 
     37
     38    RpLibrary*
    2839    elementAsObject (RpLibrary* lib, const char* path)
    2940    {
     
    3142    }
    3243
    33     const char* 
     44    const char*
    3445    elementAsType (RpLibrary* lib, const char* path)
    3546    {
     
    4455    }
    4556
    46     const char* 
     57    const char*
    4758    elementAsComp (RpLibrary* lib, const char* path)
    4859    {
     
    5768    }
    5869
    59     const char* 
     70    const char*
    6071    elementAsId (RpLibrary* lib, const char* path)
    6172    {
     
    7889
    7990    RpLibrary*
    80     childrenByType( RpLibrary* lib, 
    81                     const char* path, 
    82                     RpLibrary* childEle, 
     91    childrenByType( RpLibrary* lib,
     92                    const char* path,
     93                    RpLibrary* childEle,
    8394                    const char* type    )
    8495    {
     
    8697    }
    8798
    88     /*
    89     RpLibrary**
    90     childrenAsObject (RpLibrary* lib, const char* path, const char* type)
    91     {
    92         return chilren(lib, path,type);
    93     }
    94 
    95     const char*
    96     childrenAsType (RpLibrary* lib, const char* path, const char* type)
    97     {
    98 
    99     }
    100 
    101     const char*
    102     childrenAsComp (RpLibrary* lib, const char* path, const char* type)
    103     {
    104 
    105     }
    106 
    107     const char*
    108     childrenAsId (RpLibrary* lib, const char* path, const char* type)
    109     {
    110 
    111     }
    112     */
    113 
    114     RpLibrary* 
     99    RpLibrary*
    115100    get (RpLibrary* lib, const char* path)
    116101    {
     
    118103    }
    119104
    120     const char* 
     105    const char*
    121106    getString (RpLibrary* lib, const char* path)
    122107    {
     
    126111    }
    127112
    128     double 
     113    double
    129114    getDouble (RpLibrary* lib, const char* path)
    130115    {
     
    132117    }
    133118
    134     void 
    135     put         (RpLibrary* lib, 
    136                  const char* path, 
     119    void
     120    put         (RpLibrary* lib,
     121                 const char* path,
    137122                 const char* value,
    138123                 const char* id,
     
    142127    }
    143128
    144     void 
    145     putStringId (RpLibrary* lib, 
    146                  const char* path, 
    147                  const char* value, 
     129    void
     130    putStringId (RpLibrary* lib,
     131                 const char* path,
     132                 const char* value,
    148133                 const char* id,
    149134                 int append          )
     
    152137    }
    153138
    154     void 
    155     putString ( RpLibrary* lib, 
    156                 const char* path, 
    157                 const char* value, 
     139    void
     140    putString ( RpLibrary* lib,
     141                const char* path,
     142                const char* value,
    158143                int append          )
    159144    {
     
    162147
    163148    void
    164     putDoubleId (RpLibrary* lib, 
    165                  const char* path, 
    166                  double value, 
     149    putDoubleId (RpLibrary* lib,
     150                 const char* path,
     151                 double value,
    167152                 const char* id,
    168153                 int append         )
     
    172157
    173158    void
    174     putDouble   (RpLibrary* lib, 
    175                  const char* path, 
    176                  double value, 
     159    putDouble   (RpLibrary* lib,
     160                 const char* path,
     161                 double value,
    177162                 int append         )
    178163    {
     
    180165    }
    181166
    182     const char* 
     167    const char*
    183168    xml (RpLibrary* lib)
    184169    {
     
    188173    }
    189174
    190     const char* 
     175    const char*
    191176    nodeComp (RpLibrary* node)
    192177    {
     
    196181    }
    197182
    198     const char* 
     183    const char*
    199184    nodeType (RpLibrary* node)
    200185    {
     
    204189    }
    205190
    206     const char* 
     191    const char*
    207192    nodeId (RpLibrary* node)
    208193    {
     
    212197    }
    213198
    214 
     199    void
     200    result (RpLibrary* lib)
     201    {
     202        lib->result();
     203    }
    215204
    216205#ifdef __cplusplus
  • trunk/src/cee/RpUnitsCInterface.cc

    r76 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: C Rappture Units Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
     11
    112#include "RpUnits.h"
    213#include "RpUnitsCInterface.h"
     
    718
    819    RpUnits* defineUnit(const char* unitSymbol, RpUnits* basis) {
    9        
     20
    1021        return RpUnits::define(unitSymbol, basis);
    1122    }
     
    2031
    2132    RpUnits* find(const char* key) {
    22        
     33
    2334        return RpUnits::find(key);
    2435    }
    2536
    2637    const char* getUnits(RpUnits* unit) {
    27        
     38
    2839        static std::string retVal;
    2940        retVal = unit->getUnits();
     
    3243
    3344    const char* getUnitsName(RpUnits* unit) {
    34        
     45
    3546        static std::string retVal;
    3647        retVal = unit->getUnitsName();
     
    4455
    4556    RpUnits* getBasis(RpUnits* unit) {
    46        
     57
    4758        return unit->getBasis();
    4859    }
     
    8091        return convert_obj_str_result(fromUnits,toUnits,val,showUnits,NULL);
    8192    }
    82    
     93
    8394    const char* convert_obj_str_result( RpUnits* fromUnits,
    8495                                        RpUnits* toUnits,
     
    8697                                        int showUnits,
    8798                                        int* result ) {
    88        
     99
    89100        static std::string retVal;
    90101        retVal = fromUnits->convert(toUnits,val,showUnits,result);
     
    119130                                        double val,
    120131                                        int* result ) {
    121        
     132
    122133        return fromUnits->convert(toUnits,val,result);
    123134    }
  • trunk/src/core/RpLibrary.cc

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  Rappture Library Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
    111
    212#include "RpLibrary.h"
     
    1525            while((attribute=scew_attribute_next(element, attribute)) != NULL)
    1626            {
    17                 if (strcmp(scew_attribute_name(attribute),attributeName.c_str()) == 0){
     27                if (    strcmp( scew_attribute_name(attribute),
     28                                attributeName.c_str()) == 0     ){
    1829                    attrVal = scew_attribute_value(attribute);
    1930                }
     
    2839}
    2940
    30 int 
     41int
    3142RpLibrary::_path2list (std::string& path, std::string** list, int listLen)
    3243{
     
    4354        list[index++] = new std::string(path.substr(start,pos-start));
    4455        start = ++pos;
    45     }   
     56    }
    4657
    4758    // add the last path to the list
     
    98109                    retVal << type;
    99110                }
    100                
     111
    101112                /*
    102113                if (retVal == NULL) {
     
    109120
    110121        scew_element_list_free(siblings);
    111        
     122
    112123    }
    113124    else {
    114        
     125
    115126        retVal << name;
    116127    }
    117        
     128
    118129    return (retVal.str());
    119130}
     
    167178        }
    168179        scew_element_list_free(siblings);
    169        
     180
    170181    }
    171182    else {
     
    175186        // retVal = scew_strjoinXX(type,name);
    176187        retVal << type << "(" << name << ")";
    177        
    178     }
    179        
     188
     189    }
     190
    180191    return (retVal.str());
    181192}
    182193
    183 int 
     194int
    184195RpLibrary::_splitPath (std::string& path, std::string& tagName, int* idx, std::string& id )
    185196{
     
    249260    scew_element* node = NULL;
    250261    scew_element** eleList = NULL;
    251    
    252    
     262
     263
    253264    if (path.empty()) {
    254265        //user gave an empty path
     
    256267        return tmpElement;
    257268    }
    258    
     269
    259270    if (!list) {
    260271        // error calloc'ing space for list
     
    275286            # If the name is like "type", then assume the index is 0.
    276287            */
    277            
     288
    278289            // eleList = scew_element_list(tmpElement, tagName->c_str(), &count);
    279290            eleList = scew_element_list(tmpElement, tagName.c_str(), &count);
     
    285296                /* there is no element with the specified index */
    286297                node = NULL;
    287             }               
     298            }
    288299
    289300            scew_element_list_free(eleList);
     
    328339            scew_element_list_free(eleList);
    329340            eleList = NULL;
    330            
    331         }
    332                
     341
     342        }
     343
    333344        if (node == NULL) {
    334345            if (create == 0) {
     
    342353                // create == 1
    343354                // we should create the rest of the path
    344                
     355
    345356                // create the new element
    346357                // need to figure out how to properly number the new element
     
    360371        }
    361372
    362        
     373
    363374        // change this so youre not allocating and deallocating so much.
    364375        // make it static or something.
     
    386397        // list = NULL;
    387398    }
    388    
     399
    389400
    390401    return tmpElement;
     
    403414
    404415    scew_element* retNode = _find(path,0);
    405    
     416
    406417    if (retNode == NULL) {
    407418        // add error information as to why we are returning NULL
     
    410421
    411422    retLib = new RpLibrary( retNode );
    412    
     423
    413424    if (!retLib) {
    414425        // add error information as to why we are returning NULL
     
    440451        parentNode = _find(path,0);
    441452    }
    442    
     453
    443454    if (parentNode == NULL) {
    444455        // node not found
     
    480491    std::cout << "childNum = " << childNum << std::endl;
    481492    retLib[childNum] = NULL;
    482        
     493
    483494    // how do you free this??
    484495    return retLib;
     
    521532        }
    522533    }
    523    
     534
    524535    old_path = path;
    525536
     
    539550
    540551    if ( (childNode = scew_element_next(parentNode,childNode)) ) {
    541        
     552
    542553        if (!type.empty()) {
    543554            childName = scew_element_name(childNode);
     
    578589
    579590    scew_element* retNode = _find(path,0);
    580    
     591
    581592    if (retNode == NULL) {
    582593        // need to raise error
     
    602613
    603614    scew_element* retNode = _find(path,0);
    604    
     615
    605616    if (retNode == NULL) {
    606617        // need to raise error
     
    637648    if (! path.empty()) {
    638649        retNode = _find(path,1);
    639        
     650
    640651        if (retNode) {
    641652
     
    646657                value = tmpVal + value;
    647658            }
    648            
     659
    649660            scew_element_set_contents(retNode,value.c_str());
    650661        }
     
    685696    outString << "<?xml version=\"1.0\"?>\n";
    686697    print_element(this->root, 0, outString);
    687    
     698
    688699    return outString.str();
    689700}
     
    705716{
    706717    return _node2comp(root);
     718}
     719
     720/*
     721 * ----------------------------------------------------------------------
     722 *  FUNCTION: rpResult
     723 *
     724 *  Clients call this function at the end of their simulation, to
     725 *  pass the simulation result back to the Rappture GUI.  It writes
     726 *  out the given XML object to a runXXX.xml file, and then writes
     727 *  out the name of that file to stdout.
     728 * ======================================================================
     729 *  AUTHOR:  Michael McLennan, Purdue University
     730 *  Copyright (c) 2004-2005
     731 *  Purdue Research Foundation, West Lafayette, IN
     732 * ======================================================================
     733 */
     734void
     735RpLibrary::result() {
     736    std::stringstream outputFile;
     737    std::fstream file;
     738    std::string xmlText = "";
     739    time_t t = 0;
     740
     741    outputFile << "run" << (int)time(&t) << ".xml";
     742    file.open(outputFile.str().c_str(),std::ios::out);
     743
     744    if ( file.is_open() ) {
     745        xmlText = xml();
     746        if (!xmlText.empty()) {
     747            file << xmlText;
     748        }
     749    }
     750    std::cout << "=RAPPTURE-RUN=>" << outputFile.str() << std::endl;
    707751}
    708752
     
    745789
    746790void
    747 RpLibrary::print_element(   scew_element* element, 
    748                             unsigned int indent, 
     791RpLibrary::print_element(   scew_element* element,
     792                            unsigned int indent,
    749793                            std::stringstream& outString    )
    750794{
  • trunk/src/core/RpUnits.cc

    r80 r83  
    33 *  RpUnits.cc
    44 *
    5  * Data Members and member functions for the RpUnits class
    6  * 
     5 *   Data Members and member functions for the RpUnits class
     6 *
    77 * ======================================================================
    88 *  AUTHOR:  Derrick Kearney, Purdue University
     
    1818
    1919/************************************************************************
    20  *                                                                     
    21  * add RpUnits Object                                                   
    22  *                                                                     
     20 *
     21 * add RpUnits Object
     22 *
    2323 ************************************************************************/
    2424
    2525RpUnits * RpUnits::define(const std::string units, RpUnits * basis)
    26 { 
     26{
    2727    RpUnits * newRpUnit = NULL;
    2828
     
    5353
    5454        srchIndex--;
    55  
     55
    5656        if (srchIndex < 0) {
    5757            break;
    5858        }
    59  
     59
    6060        if     ( isdigit(srchStr[srchIndex]) && !digiSearch && !alphaSearch) {
    6161            digiSearch = 1;
    6262        }
    6363        else if(!isdigit(srchStr[srchIndex]) &&  digiSearch && !alphaSearch) {
    64  
     64
    6565            // convert our exponent to integer
    66  
     66
    6767            // check to see if there is a + or - sign
    6868            if (  ( srchStr[srchIndex] == '+' )
    6969               || ( srchStr[srchIndex] == '-' ) ) {
    70  
     70
    7171                // evaluate a '+' or '-' sign with the value
    7272                srchIndex--;
    7373            }
    74  
     74
    7575            srchIndex++;
    76  
     76
    7777            exp = atoi(&srchStr[srchIndex]);
    78  
     78
    7979            // we are no longer in a digit search
    8080            digiSearch = 0;
    81  
     81
    8282            // place null character where the number starts
    8383            // so we know what we've already parsed
    84  
     84
    8585            srchStr.erase(srchIndex);
    8686            length = srchStr.length();
    87  
     87
    8888        }
    8989        else if( isalpha(srchStr[srchIndex]) && !digiSearch && !alphaSearch) {
     
    9191        }
    9292        else if(!isalpha(srchStr[srchIndex]) && !digiSearch && alphaSearch) {
    93            
     93
    9494            // adjust the exponent if none was provided
    9595            if (exp == 0) {
    9696                exp = 1;
    9797            }
    98  
     98
    9999            // compare unit string to see if it is a recognized system
    100  
    101  
     100
     101
    102102            std::string cmpStr = srchStr.substr(srchIndex+1,length-srchIndex-1);
    103103            if (newRpUnit) {
     
    110110            // place a null character at the end of the string
    111111            // so we know what we've parsed so far.
    112          
     112
    113113            srchStr.erase(srchIndex);
    114114            length = srchStr.length();
    115  
     115
    116116            // fix our searching flag
    117117            alphaSearch = 0;
     
    121121            // have to go back to all of the objects created and
    122122            // multiply their exponents by -1.
    123  
     123
    124124            if (newRpUnit) {
    125125                unit* p = newRpUnit->head;
     
    134134            // place a null character at the end of the string
    135135            // so we know what we've parsed so far.
    136        
     136
    137137            srchStr.erase(srchIndex);
    138138            length = srchStr.length();
     
    145145
    146146    } // end while loop
    147        
     147
    148148
    149149    // complete the last iteration
     
    154154            // convert whatever is left
    155155            exp = atoi(&srchStr[srchIndex+1]);
    156            
     156
    157157            // if we get here, that means units name starts with a digit
    158158            // normally we wont get here, but if we do, should we place
     
    175175
    176176    // place the new object into the dictionary
    177    
     177
    178178    // return a copy of the new object to user
    179179    return newRpUnit;
     
    182182
    183183/************************************************************************
    184  *                                                                     
    185  * add a complex RpUnits Object                                                   
    186  *                                                                     
     184 *
     185 * add a complex RpUnits Object
     186 *
    187187 ************************************************************************/
    188188
    189 RpUnits * RpUnits::defineCmplx ( const std::string units,
    190                             RpUnits * basis )
    191 {
     189RpUnits * RpUnits::defineCmplx ( const std::string units, RpUnits * basis )
     190{
    192191    RpUnits * newRpUnit = NULL;
    193192
     
    221220
    222221        srchIndex--;
    223  
     222
    224223        if (srchIndex < 0) {
    225224            break;
    226225        }
    227  
     226
    228227        if     ( isdigit(srchStr[srchIndex]) && !digiSearch && !alphaSearch) {
    229228            digiSearch = 1;
    230229        }
    231230        else if(!isdigit(srchStr[srchIndex]) &&  digiSearch && !alphaSearch) {
    232  
     231
    233232            // convert our exponent to integer
    234  
     233
    235234            // check to see if there is a + or - sign
    236235            if (  ( srchStr[srchIndex] == '+' )
    237236               || ( srchStr[srchIndex] == '-' ) ) {
    238  
     237
    239238                // evaluate a '+' or '-' sign with the value
    240239                srchIndex--;
    241240            }
    242  
     241
    243242            srchIndex++;
    244  
     243
    245244            exp = atoi(&srchStr[srchIndex]);
    246  
     245
    247246            // we are no longer in a digit search
    248247            digiSearch = 0;
    249  
     248
    250249            // place null character where the number starts
    251250            // so we know what we've already parsed
    252  
     251
    253252            srchStr.erase(srchIndex);
    254253            length = srchStr.length();
    255  
     254
    256255        }
    257256        else if( isalpha(srchStr[srchIndex]) && !digiSearch && !alphaSearch) {
     
    259258        }
    260259        else if(!isalpha(srchStr[srchIndex]) && !digiSearch && alphaSearch) {
    261            
     260
    262261            // adjust the exponent if none was provided
    263262            if (exp == 0) {
    264263                exp = 1;
    265264            }
    266  
     265
    267266            // compare unit string to see if it is a recognized system
    268  
    269  
     267
     268
    270269            std::string cmpStr = srchStr.substr(srchIndex+1,length-srchIndex-1);
    271270            cmpIndex = 0;
    272  
     271
    273272            if ( (unsigned)(cmpIndex = pre_compare(cmpStr,basis)) ==
    274273                    std::string::npos ) {
    275274                alphaSearch = 0;
    276  
     275
    277276                // there are units we did not recognize,
    278277                // right now we ignore them,
    279278                // we may want to deal with them differntly in the future
    280  
     279
    281280                // erase only the last character and reprocess the string
    282281                // because our precompare doesnt take care of this yet.
     
    284283                length = srchStr.length();
    285284                srchIndex = length;
    286                
    287  
     285
     286
    288287                // continue parsing characters
    289288                continue;
    290289            }
    291  
     290
    292291            // the compare function was successful
    293292            // move the search pointer to one value infront of
     
    299298            srchIndex = cmpIndex;
    300299            std::string newUnitText = srchStr.substr(cmpIndex,length-cmpIndex);
    301  
     300
    302301            // call the function to create the unit object
    303  
     302
    304303            // we need pre-compare to return the basis of what it found.
    305304            if (newRpUnit) {
     
    309308                 newRpUnit= new RpUnits(newUnitText, exp, basis);
    310309            }
    311  
    312  
     310
     311
    313312            // place a null character at the end of the string
    314313            // so we know what we've parsed so far.
    315          
     314
    316315            srchStr.erase(srchIndex);
    317316            length = srchStr.length();
    318  
     317
    319318            // fix our searching flag
    320319            alphaSearch = 0;
     
    324323            // have to go back to all of the objects created and
    325324            // multiply their exponents by -1.
    326  
     325
    327326            if (newRpUnit) {
    328327                unit* p = newRpUnit->head;
     
    337336            // place a null character at the end of the string
    338337            // so we know what we've parsed so far.
    339        
     338
    340339            srchStr.erase(srchIndex);
    341340            length = srchStr.length();
     
    348347
    349348    } // end while loop
    350        
     349
    351350
    352351    // complete the last iteration
     
    357356            // convert whatever is left
    358357            exp = atoi(&srchStr[srchIndex+1]);
    359            
     358
    360359            // if we get here, that means units name starts with a digit
    361360            // normally we wont get here, but if we do, should we place
     
    382381                // fundamental type
    383382                newRpUnit = new RpUnits(cmpStr, exp, basis);
    384                
     383
    385384                // put the unit into the dictionary
    386385                //
    387386                newRpUnit->insert(newRpUnit->getUnitsName());
    388                
     387
    389388
    390389            }
     
    395394                // where the units were found.
    396395                // adjusting the search pointer to point to the units
    397                 std::string newUnitText = srchStr.substr(cmpIndex,length-cmpIndex); 
     396                std::string newUnitText = srchStr.substr(cmpIndex,length-cmpIndex);
    398397
    399398                // call the function to create the unit object
     
    417416
    418417    // place the new object into the dictionary
    419    
     418
    420419    // return a copy of the new object to user
    421420    return newRpUnit;
     
    424423
    425424/************************************************************************
    426  *                                                                     
    427  * add relation rule                                                   
    428  *                                                                     
     425 *
     426 * add relation rule
     427 *
    429428 ************************************************************************/
    430429RpUnits * RpUnits::define(  RpUnits* from,
     
    432431                            double (*convForwFxnPtr)(double),
    433432                            double (*convBackFxnPtr)(double))
    434 {
    435     RpUnits* conv = new RpUnits(from,to,convForwFxnPtr,convBackFxnPtr,NULL,NULL);
    436    
    437     return conv;
     433{
     434    RpUnits* conv = new RpUnits(    from,
     435                                    to,
     436                                    convForwFxnPtr,
     437                                    convBackFxnPtr,
     438                                    NULL,
     439                                    NULL);
     440
     441    return conv;
    438442}
    439443
     
    444448                            void* (*convBackFxnPtr)(void*, void*),
    445449                            void* convBackData)
    446 { 
     450{
    447451    RpUnits* conv = new RpUnits(    from,
    448452                                    to,
     
    453457                                    NULL,
    454458                                    NULL);
    455    
    456     return conv; 
     459
     460    return conv;
    457461}
    458462
    459463/************************************************************************
    460  *                                                                     
    461  * report the units this object represents back to the user             
    462  *                                                                     
     464 *
     465 * report the units this object represents back to the user
     466 *
    463467 * **********************************************************************/
    464 std::string RpUnits::getUnits() 
     468std::string RpUnits::getUnits()
    465469{
    466470    std::stringstream unitText;
    467471    unit* p = head;
    468    
     472
    469473    while (p) {
    470474        unitText << p->getUnits() ;
    471475        p = p->next;
    472476    }
    473    
    474     return (unitText.str()); 
     477
     478    return (unitText.str());
    475479}
    476480
    477481/************************************************************************
    478  *                                                                     
    479  * report the units this object represents back to the user             
    480  *                                                                     
     482 *
     483 * report the units this object represents back to the user
     484 *
    481485 * **********************************************************************/
    482 std::string RpUnits::getUnitsName() 
     486std::string RpUnits::getUnitsName()
    483487{
    484488    std::stringstream unitText;
    485489    unit* p = head;
    486490    double exponent;
    487    
     491
    488492    while (p) {
    489493
     
    499503        p = p->next;
    500504    }
    501    
    502     return (unitText.str()); 
     505
     506    return (unitText.str());
    503507}
    504508
    505509/************************************************************************
    506  *                                                                     
     510 *
    507511 * report the exponent of the units of this object back to the user
    508  *                                                                     
     512 *
    509513 * **********************************************************************/
    510 double RpUnits::getExponent() 
    511 { 
     514double RpUnits::getExponent()
     515{
    512516    return head->getExponent();
    513517}
    514518
    515519/************************************************************************
    516  *                                                                     
    517  *  report the basis of this object to the user                         
    518  *                                                                     
     520 *
     521 *  report the basis of this object to the user
     522 *
    519523 * **********************************************************************/
    520 RpUnits * RpUnits::getBasis() 
    521 { 
    522     // check if head exists? 
     524RpUnits * RpUnits::getBasis()
     525{
     526    // check if head exists?
    523527    return head->getBasis();
    524528}
    525529
    526530/************************************************************************
    527  *                                                                     
     531 *
    528532 *  convert the current unit to its basis units
    529  * 
     533 *
    530534 *  Return Codes
    531535 *      0) no error (could also mean or no prefix was found)
    532536 *          in some cases, this means the value is in its basis format
    533537 *      1) the prefix found does not have a built in factor associated.
    534  *                                                                     
     538 *
    535539 ************************************************************************/
    536540double RpUnits::makeBasis(double value, int* result)
    537 { 
     541{
    538542
    539543    RpUnits* basis = getBasis();
     
    547551        // this unit is a basis
    548552        // do nothing
    549        
     553
    550554        if (result) {
    551555            *result = 1;
     
    568572        // this unit is a basis
    569573        // do nothing
    570        
     574
    571575        if (result) {
    572576            *result = 1;
     
    585589    }
    586590
    587    
     591
    588592
    589593    return *this;
     
    591595
    592596/************************************************************************
    593  *                                                                     
    594  *  static int makeMetric(RpUnits * basis);                     
     597 *
     598 *  static int makeMetric(RpUnits * basis);
    595599 *  create the metric attachments for the given basis.
    596  *  should only be used if this unit is of metric type                 
    597  *                                                                     
     600 *  should only be used if this unit is of metric type
     601 *
    598602 * **********************************************************************/
    599603int RpUnits::makeMetric(RpUnits * basis) {
     
    606610    std::string name;
    607611    std::string forw, back;
    608    
     612
    609613    name = "c" + basisName;
    610614    RpUnits * centi = RpUnits::define(name, basis);
     
    622626    RpUnits * nano  = RpUnits::define(name, basis);
    623627    RpUnits::define(nano, basis, nano2base, base2nano);
    624    
     628
    625629    name = "p" + basisName;
    626630    RpUnits * pico  = RpUnits::define(name, basis);
     
    654658    RpUnits * peta  = RpUnits::define(name, basis);
    655659    RpUnits::define(peta, basis, peta2base, base2peta);
    656    
     660
    657661    return (1);
    658662}
    659663
    660 // convert function so people can just send in two strings and 
    661 // we'll see if the units exists and do a conversion 
     664// convert function so people can just send in two strings and
     665// we'll see if the units exists and do a conversion
    662666// strVal = RpUnits::convert("300K","C",1);
    663 std::string 
    664 RpUnits::convert (  std::string val, 
    665                     std::string toUnitsName, 
     667std::string
     668RpUnits::convert (  std::string val,
     669                    std::string toUnitsName,
    666670                    int showUnits,
    667671                    int* result ) {
     
    682686        *result = 0;
    683687    }
    684    
    685     toUnits = find(toUnitsName);   
     688
     689    toUnits = find(toUnitsName);
    686690
    687691    // did we find the unit in the dictionary?
    688692    if (toUnits == NULL) {
    689693        // toUnitsName was not found in the dictionary
     694        if (result) {
     695            *result = 1;
     696        }
    690697        return val;
    691698    }
    692    
     699
    693700    valLen = val.length();
    694701
    695     // search our string to see where the numeric part stops 
     702    // search our string to see where the numeric part stops
    696703    // and the units part starts
     704    //
     705    // switched from the code that starts at the beginning of the string
     706    // and check to see where the numeric part stops
     707    // to the uncommented code section below that starts at the end of the
     708    // string checks to see where the alpha part starts. This approach
     709    // seems to work better so we can parse and convert strings as follows:
     710    //  convert("5J", "neV") => 3.12075e+28neV
     711    //  convert("3.12075e+28neV", "J") => 4.99999J
     712    // now we can actually get the scientific notation portion of the string.
     713    //
    697714    // make sure not to stop searching if we encounter '.', '-', '+'
     715    /*
    698716    for (idx=0; idx < valLen; idx++) {
    699717        if ( !((val[idx] >= '0') && (val[idx] <= '9')) ) {
     
    703721        }
    704722    }
     723    */
     724
     725    // consider using stdtod because it does error checking
     726    // supposedly according to man page?
     727    for (idx=valLen-1; idx >= 0; idx--) {
     728        if ( !(     ((val[idx] >= 'A') && (val[idx] <= 'Z'))
     729                ||  ((val[idx] >= 'a') && (val[idx] <= 'z'))    ) ) {
     730
     731            if ( (val[idx] != '.')&&(val[idx] != '-')&&(val[idx] != '+') ) {
     732                break;
     733            }
     734        }
     735    }
     736
     737    idx++;
    705738
    706739    if ( (idx < valLen) && (idx > 0) ) {
     
    716749                *result = 1;
    717750            }
     751            // not a big fan of multiple returns, but...
     752            return val;
    718753        }
    719754        fromUnitsName = val.substr(idx, valLen-idx);
     
    724759            *result = 1;
    725760        }
    726     }
    727    
    728     fromUnits = find(fromUnitsName);   
     761        // not a big fan of multiple returns, but...
     762        return val;
     763    }
     764
     765    fromUnits = find(fromUnitsName);
    729766
    730767    // did we find the unit in the dictionary?
    731768    if (fromUnits == NULL) {
    732769        // fromUnitsName was not found in the dictionary
     770        if (result) {
     771            *result = 1;
     772        }
    733773        return val;
    734774    }
    735775
    736776    convVal = fromUnits->convert(toUnits, numVal, showUnits, &convResult);
    737    
     777
    738778    if ( (result) && (*result == 0) ) {
    739779        *result = convResult;
     
    744784}
    745785
    746 std::string RpUnits::convert (   RpUnits* toUnits, 
    747                         double val, 
    748                         int showUnits, 
     786std::string RpUnits::convert (   RpUnits* toUnits,
     787                        double val,
     788                        int showUnits,
    749789                        int* result )
    750790{
    751     double retVal = convert(toUnits,val,result); 
     791    double retVal = convert(toUnits,val,result);
    752792    std::stringstream unitText;
    753    
     793
    754794
    755795    if (showUnits) {
     
    767807// if it exists as a conversion from the basis
    768808// example
    769 //      cm.convert(meter,10) 
     809//      cm.convert(meter,10)
    770810//      cm.convert(angstrum,100)
    771811double RpUnits::convert(RpUnits* toUnit, double val, int* result)
     
    796836        return val;
    797837    }
    798    
     838
    799839    // convert unit to the basis
    800840    // makeBasis(&value);
     
    806846        if (my_result == 0) {
    807847            fromUnit = basis;
    808         }   
     848        }
    809849    }
    810850
     
    843883    // loop through our conversion list looking for the correct conversion
    844884    do {
    845        
     885
    846886        if ( (p->conv->toPtr == dictToUnit) && (p->conv->fromPtr == fromUnit) ) {
    847887            // we found our conversion
     
    849889
    850890            value = p->conv->convForwFxnPtr(value);
    851            
     891
    852892            // check to see if we converted to the actual requested unit
    853893            // or to the requested unit's basis.
     
    864904                }
    865905            }
    866            
     906
    867907            // we can probably remove this
    868908            if (result) {
     
    871911            break;
    872912        }
    873        
     913
    874914        if ( (p->conv->toPtr == fromUnit) && (p->conv->fromPtr == dictToUnit) ) {
    875915            // we found our conversion
     
    877917
    878918            value = p->conv->convBackFxnPtr(value);
    879            
     919
    880920            // check to see if we converted to the actual requested unit
    881921            // or to the requested unit's basis.
     
    892932                }
    893933            }
    894            
     934
    895935            // we can probably remove this
    896936            if (result) {
     
    947987        return val;
    948988    }
    949    
     989
    950990    // convert unit to the basis
    951991    // makeBasis(&value);
    952992    // trying to avoid the recursive way of converting to the basis.
    953993    // need to rethink this.
    954     // 
     994    //
    955995    if ( (basis) && (basis->getUnits() != toUnit->getUnits()) ) {
    956996        value = convert(basis,value,&my_result);
    957997        if (my_result == 0) {
    958998            fromUnit = basis;
    959         }   
     999        }
    9601000    }
    9611001
     
    9941034    // loop through our conversion list looking for the correct conversion
    9951035    do {
    996        
     1036
    9971037        if ( (p->conv->toPtr == dictToUnit) && (p->conv->fromPtr == fromUnit) ) {
    9981038            // we found our conversion
     
    10151055                }
    10161056            }
    1017            
     1057
    10181058            // we can probably remove this
    10191059            if (result) {
     
    10221062            break;
    10231063        }
    1024        
     1064
    10251065        if ( (p->conv->toPtr == fromUnit) && (p->conv->fromPtr == dictToUnit) ) {
    10261066            // we found our conversion
     
    10431083                }
    10441084            }
    1045            
     1085
    10461086            // we can probably remove this
    10471087            if (result) {
     
    11031143{
    11041144
    1105     // compare the incomming units with the previously defined units. 
    1106     // compareStr will hold a copy of the incomming string. 
     1145    // compare the incomming units with the previously defined units.
     1146    // compareStr will hold a copy of the incomming string.
    11071147    // first look for the units as they are listed in the incomming variable
    11081148    // next look move searchStr toward the end of the string,
     
    11221162    std::string searchStr = units;
    11231163    std::string dbText = "";
    1124    
     1164
    11251165    // pass 1: look for exact match of units as they came into the function
    11261166    //          move searchStr pointer through string to find match.
    1127     while ( ! compareSuccess && 
     1167    while ( ! compareSuccess &&
    11281168            (searchStr.length() > 0) ) {
    11291169
     
    11901230                break;
    11911231            }
    1192            
     1232
    11931233        }
    11941234
     
    12331273
    12341274// return codes: 0 success, anything else is error
    1235 int 
     1275int
    12361276RpUnits::addPresets (std::string group) {
    12371277    int retVal = -1;
     
    12511291        retVal = addPresetTime();
    12521292    }
    1253    
     1293
    12541294    return retVal;
    12551295}
    1256    
     1296
    12571297// return codes: 0 success, anything else is error
    1258 int 
     1298int
    12591299RpUnits::addPresetAll () {
    12601300
     
    12701310
    12711311// return codes: 0 success, anything else is error
    1272 int 
     1312int
    12731313RpUnits::addPresetTime () {
    12741314
    12751315    RpUnits* seconds    = RpUnits::define("s", NULL);
    1276    
     1316
    12771317    RpUnits::makeMetric(seconds);
    1278    
     1318
    12791319    // add time definitions
    12801320
     
    12831323
    12841324// return codes: 0 success, anything else is error
    1285 int 
     1325int
    12861326RpUnits::addPresetTemp () {
    12871327
     
    12901330    RpUnits* kelvin     = RpUnits::define("K", NULL);
    12911331    RpUnits* rankine    = RpUnits::define("R", NULL);
    1292    
     1332
    12931333    // add temperature definitions
    12941334    RpUnits::define(fahrenheit, celcius, fahrenheit2centigrade, centigrade2fahrenheit);
     
    13011341
    13021342// return codes: 0 success, anything else is error
    1303 int 
     1343int
    13041344RpUnits::addPresetLength () {
    13051345
     
    13091349    RpUnits* feet       = RpUnits::define("ft", NULL);
    13101350    RpUnits* yard       = RpUnits::define("yd", NULL);
    1311    
     1351
    13121352    RpUnits::makeMetric(meters);
    13131353
     
    13221362
    13231363// return codes: 0 success, anything else is error
    1324 int 
     1364int
    13251365RpUnits::addPresetEnergy () {
    13261366
     
    13281368    RpUnits* eVolt      = RpUnits::define("eV", NULL);
    13291369    RpUnits* joule      = RpUnits::define("J", NULL);
    1330    
     1370
    13311371    RpUnits::makeMetric(volt);
    13321372    RpUnits::makeMetric(eVolt);
     1373    RpUnits::makeMetric(joule);
    13331374
    13341375    // add energy definitions
  • trunk/src/core/RpUnitsStd.cc

    r68 r83  
    77 ****************************************/
    88
    9 double centi2base (double centi) 
    10 {
    11    return centi*1e-2;   
     9double centi2base (double centi)
     10{
     11   return centi*1e-2;
    1212}
    1313
     
    6767}
    6868
    69 double base2centi (double base) 
    70 {
    71     return base*1e2;   
     69double base2centi (double base)
     70{
     71    return base*1e2;
    7272}
    7373
     
    230230double joule2electronVolt (double J)
    231231{
    232         return (J*1.602177e19);
     232        return (J/1.602177e-19);
    233233}
    234234
  • trunk/src/fortran/RpFortranCommon.c

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Common Functions Source
     4 *
     5 *    Fortran functions common to all interfaces.
     6 *
     7 * ======================================================================
     8 *  AUTHOR:  Derrick Kearney, Purdue University
     9 *  Copyright (c) 2005
     10 *  Purdue Research Foundation, West Lafayette, IN
     11 * ======================================================================
     12 */
     13
     14
    115#include "RpFortranCommon.h"
    216
  • trunk/src/fortran/RpLibraryFInterface.cc

    r77 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Library Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
     11
    112#include "RpLibraryFInterface.h"
    213
     
    819
    920    inFilePath = null_terminate_str(filePath, filePath_len);
    10    
     21
    1122    // create a RapptureIO object and store in dictionary
    1223    lib = new RpLibrary(inFilePath);
     
    3748        if (lib) {
    3849            retObj = lib->element(inPath);
    39            
     50
    4051            if (retObj) {
    4152                newObjHandle = storeObject_Lib(retObj);
     
    6879        }
    6980    }
    70    
     81
    7182}
    7283
     
    95106
    96107void rp_lib_element_type( int* handle, /* integer handle of library */
    97                             char* path,      /* null terminated path */
     108                            char* path,      /* search path inside xml */
    98109                            char* retText,   /* return buffer for fortran*/
    99110                            int path_len,
     
    113124        fortranify(retStr.c_str(),retText,retText_len);
    114125    }
     126}
     127
     128int rp_lib_children (   int* handle, /* integer handle of library */
     129                        char* path, /* search path of the xml */
     130                        int* childHandle, /*integer hanlde of last returned child*/
     131                        int path_len  /* length of the search path buffer */
     132                    ) {
     133
     134    std::string inPath = "";
     135    RpLibrary* lib = NULL;
     136    RpLibrary* childNode = NULL;
     137    int newObjHandle = -1;
     138
     139    inPath = null_terminate_str(path,path_len);
     140
     141    if (handle && (*handle >= 0) ) {
     142        lib = getObject_Lib(*handle);
     143        if (lib) {
     144            if (*childHandle < 1) {
     145                // check to see if there were any previously returned children
     146                childNode = getObject_Lib(*childHandle);
     147            }
     148
     149            // call the children base method
     150            childNode = lib->children(path,childNode);
     151
     152            // store the childNode in the dictionary.
     153            //
     154            // because the base method is using static memory to get store the
     155            // children we should be able to chekc and see if the childHandle
     156            // was valud.
     157            // if so, then we can just return the childHandle back to the user
     158            // if not, store the object in the dictionary and return the new
     159            // handle.
     160
     161            if (childNode) {
     162                if (*childHandle < 1) {
     163                    newObjHandle = storeObject_Lib(childNode);
     164                }
     165                else {
     166                    newObjHandle = *childHandle;
     167                }
     168            }
     169        }
     170    }
     171
     172    return newObjHandle;
     173
    115174}
    116175
     
    128187
    129188    inPath = null_terminate(path,path_len);
    130    
     189
    131190    if (rapptureStarted) {
    132191        if ((handle) && (*handle != 0)) {
     
    140199                }
    141200                else {
    142                    
     201
    143202                }
    144203            }
     
    394453
    395454    RpLibrary* lib = NULL;
    396    
     455
    397456    std::string inPath = "";
    398457
     
    401460    if ((handle) && (*handle != 0)) {
    402461        lib = getObject_Lib(*handle);
    403        
     462
    404463        if (lib) {
    405464            xmlText = lib->getString(inPath);
     
    420479
    421480    RpLibrary* lib = NULL;
    422    
     481
    423482    std::string inPath = "";
    424483
     
    427486    if ((handle) && (*handle != 0)) {
    428487        lib = getObject_Lib(*handle);
    429        
     488
    430489        if (lib) {
    431490            retVal = lib->getDouble(inPath);
     
    443502                        int path_len,
    444503                        int value_len
    445                       ) 
     504                      )
    446505{
    447506    std::string inPath = "";
     
    459518        }
    460519    }
    461    
     520
    462521    return;
    463    
     522
    464523}
    465524
     
    476535{
    477536    RpLibrary* lib = NULL;
    478    
     537
    479538    std::string inPath = "";
    480539    std::string inValue = "";
     
    487546    if ((handle) && (*handle != 0)) {
    488547        lib = getObject_Lib(*handle);
    489        
     548
    490549        if (lib) {
    491550            lib->put(inPath,inValue,inId,*append);
     
    586645    PyObject* lib = NULL;
    587646    PyObject* removedObj = NULL;
    588    
     647
    589648    char* inPath = NULL;
    590649
     
    597656            if (lib) {
    598657                removedObj = rpRemove(lib, inPath);
    599                
     658
    600659                if (removedObj) {
    601660                    newObjHandle = storeObject_Lib(removedObj);
     
    606665        }
    607666    }
    608    
     667
    609668    if (inPath) {
    610669        free(inPath);
     
    643702}
    644703*/
    645 
    646 void  rp_lib_xml(int* handle, char* retText, int retText_len)
    647 {
    648     std::string xmlText = "";
    649 
    650     RpLibrary* lib = NULL;
    651    
    652     if ((handle) && (*handle != 0)) {
    653         lib = getObject_Lib(*handle);
    654 
    655         if (lib) {
    656             xmlText = lib->xml();
    657             if (!xmlText.empty()) {
    658                 fortranify(xmlText.c_str(), retText, retText_len);
    659             }
    660         }
    661     }
    662 }
    663704
    664705int rp_lib_write_xml(int* handle, char* outFile, int outFile_len)
     
    695736}
    696737
     738void  rp_lib_xml(int* handle, char* retText, int retText_len)
     739{
     740    std::string xmlText = "";
     741
     742    RpLibrary* lib = NULL;
     743
     744    if ((handle) && (*handle != 0)) {
     745        lib = getObject_Lib(*handle);
     746
     747        if (lib) {
     748            xmlText = lib->xml();
     749            if (!xmlText.empty()) {
     750                fortranify(xmlText.c_str(), retText, retText_len);
     751            }
     752        }
     753    }
     754}
     755
     756void rp_lib_node_comp ( int* handle, char* retText, int retText_len ) {
     757
     758    std::string retStr = "";
     759    RpLibrary* node = NULL;
     760
     761    if ((handle) && (*handle != 0)) {
     762        node = getObject_Lib(*handle);
     763
     764        if (node) {
     765            retStr = node->nodeComp();
     766            if (!retStr.empty()) {
     767                fortranify(retStr.c_str(), retText, retText_len);
     768            }
     769        }
     770    }
     771}
     772
     773void rp_lib_node_type ( int* handle, char* retText, int retText_len ) {
     774
     775    std::string retStr = "";
     776    RpLibrary* node = NULL;
     777
     778    if ((handle) && (*handle != 0)) {
     779        node = getObject_Lib(*handle);
     780
     781        if (node) {
     782            retStr = node->nodeType();
     783            if (!retStr.empty()) {
     784                fortranify(retStr.c_str(), retText, retText_len);
     785            }
     786        }
     787    }
     788}
     789
     790void rp_lib_node_id ( int* handle, char* retText, int retText_len ) {
     791
     792    std::string retStr = "";
     793    RpLibrary* node = NULL;
     794
     795    if ((handle) && (*handle != 0)) {
     796        node = getObject_Lib(*handle);
     797
     798        if (node) {
     799            retStr = node->nodeId();
     800            if (!retStr.empty()) {
     801                fortranify(retStr.c_str(), retText, retText_len);
     802            }
     803        }
     804    }
     805}
     806
    697807void rp_quit()
    698808{
     
    701811
    702812    RpDictEntry DICT_TEMPLATE *hPtr;
    703     // RpDictIterator DICT_TEMPLATE iter((RpDict&)*this);                     
     813    // RpDictIterator DICT_TEMPLATE iter((RpDict&)*this);
    704814    RpDictIterator DICT_TEMPLATE iter(fortObjDict_Lib);
    705    
    706     hPtr = iter.first();                                                     
    707    
     815
     816    hPtr = iter.first();
     817
    708818    while (hPtr) {
    709819        // Py_DECREF(*(hPtr->getValue()));
    710820        hPtr->erase();
    711         hPtr = iter.next();                                                   
     821        hPtr = iter.next();
    712822    }
    713823
     
    717827    }
    718828
     829}
     830
     831void rp_result(int* handle) {
     832    RpLibrary* lib = NULL;
     833
     834    if (handle && *handle != 0) {
     835        lib = getObject_Lib(*handle);
     836        if (lib) {
     837            lib->result();
     838        }
     839    }
    719840}
    720841
     
    756877        fortObjDict_Lib.set(dictKey,objectName, &newEntry);
    757878    }
    758    
     879
    759880    retVal = dictKey;
    760881    return retVal;
  • trunk/src/fortran/RpUnitsFInterface.cc

    r76 r83  
     1/*
     2 * ----------------------------------------------------------------------
     3 *  INTERFACE: Fortran Rappture Units Source
     4 *
     5 * ======================================================================
     6 *  AUTHOR:  Derrick Kearney, Purdue University
     7 *  Copyright (c) 2005
     8 *  Purdue Research Foundation, West Lafayette, IN
     9 * ======================================================================
     10 */
     11
    112#include "RpUnits.h"
    213#include "RpDict.h"
  • trunk/test/Makefile

    r77 r83  
    1212
    1313# define the top of the rappture directory structure
    14 RP_BASE   = $(TOP_DIR)/rappture
     14RP_BASE         = $(TOP_DIR)/rappture
    1515
    1616# define which programs can be made
    17                                        
    18 TEST_PROGS          = RpBoolean_test    \
    19                       RpChoice_test     \
    20                       RpNumber_test     \
    21                       RpString_test     \
    22                       RpUnits_test      \
    23                       RpVariable_test   \
    24                       RpUnitsC_test             \
    25                       RpUnitsF_test             \
    26                                           RpLibrary_test        \
    27                                           RpLibraryCInterface_test
     17
     18TEST_PROGS      = RpBoolean_test    \
     19                  RpChoice_test     \
     20                  RpNumber_test     \
     21                  RpString_test     \
     22                  RpUnits_test      \
     23                  RpVariable_test   \
     24                  RpUnitsC_test     \
     25                  RpUnitsF_test     \
     26                  RpLibrary_test    \
     27                  RpLibraryC_test
    2828
    2929# define our compiling environment
    30 # 
    31 CC                              = gcc
    32 CXX                             = g++
    33 DEBUG                   = -g -Wall
    34 DEBUG_PLUS              = -g -DDEBUG
     30#
     31CC              = gcc
     32CXX             = g++
     33DEBUG           = -g -Wall
     34DEBUG_PLUS      = -g -DDEBUG
    3535
    36 # FORTRAN BINDINGS COMPILER FLAGS 
     36# FORTRAN BINDINGS COMPILER FLAGS
    3737#
    3838# available flags
    3939#
    40 #       COMPNAME_NOCHANGE               -       No change to the Rappture Library function
    41 #                                                               name
    42 #       COMPNAME_UPPERCASE      -       Replace the Rappture Library function name
    43 #                                                               with an all uppercase version of the name
    44 #       COMPNAME_ADD1UNDERSCORE -       add 1 underscore to the end of the Rappture
    45 #                                                               Library function name
    46 #       COMPNAME_ADD2UNDERSCORE -       add 2 underscores to the end of the Rappture
    47 #                                                               Library function name
    48 # 
     40#   COMPNAME_NOCHANGE           No change to the Rappture Library function
     41#                                 name
     42#   COMPNAME_UPPERCASE          Replace the Rappture Library function name
     43#                                 with an all uppercase version of the name
     44#   COMPNAME_ADD1UNDERSCORE     Add 1 underscore to the end of the Rappture
     45#                                 Library function name
     46#   COMPNAME_ADD2UNDERSCORE     Add 2 underscores to the end of the Rappture
     47#                                 Library function name
     48#
    4949# when setting CFLAGS, use the following guide for help
    5050#
    51 # gnu's g77/f77                 COMPNAME_ADD2UNDERSCORE
    52 # absoft's f77                  COMPNAME_ADD1UNDERSCORE
    53 # intel's ifort                 COMPNAME_ADD1UNDERSCORE
    54 # intel's mpif90                COMPNAME_ADD1UNDERSCORE
     51# gnu's g77/f77         COMPNAME_ADD2UNDERSCORE
     52# absoft's f77          COMPNAME_ADD1UNDERSCORE
     53# intel's ifort         COMPNAME_ADD1UNDERSCORE
     54# intel's mpif90        COMPNAME_ADD1UNDERSCORE
    5555#
    5656#
    5757
    58 CFLAGS                  = -DCOMPNAME_ADD2UNDERSCORE
     58CFLAGS          = -DCOMPNAME_ADD2UNDERSCORE
    5959
    60 F77                     = g77
     60F77             = g77
    6161
    6262LN              = ln
     
    6464# define our directories
    6565#
    66 INCLUDES_DIR    = $(RP_BASE)/include
    67 BIN_DIR                 = $(RP_BASE)/bin
    68 LIB_DIR                 = $(RP_BASE)/src
    69 SRC_DIR                 = $(RP_BASE)/src
    70 TEST_DIR                = $(RP_BASE)/test
     66INCLUDES_DIR    = $(RP_BASE)/include
     67BIN_DIR         = $(RP_BASE)/bin
     68LIB_DIR         = $(RP_BASE)/src
     69SRC_DIR         = $(RP_BASE)/src
     70TEST_DIR        = $(RP_BASE)/test
    7171
    72 LIB_INC_PREFIX  = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR)
     72LIB_INC_PREFIX  = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR)
    7373
    74 LIB_RP_OBJECTS  = $(LIB_INC_PREFIX) -lRpObjects
    75 LIB_RAPPTURE    = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture
    76 LIB_RAPPTURE_T  = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture_test
     74LIB_RP_OBJECTS  = $(LIB_INC_PREFIX) -lRpObjects
     75LIB_RAPPTURE    = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture
     76LIB_RAPPTURE_T  = -Wl,-rpath,$(LIB_DIR) -L$(LIB_DIR) -lrappture_test
    7777
    78 INCL_CORE               = -I $(INCLUDES_DIR)/core
    79 INCL_CEE                = -I $(INCLUDES_DIR)/cee
    80 INCL_FORTRAN    = -I $(INCLUDES_DIR)/fortran
    81 INCL_PY                 = -I $(INCLUDES_DIR)/python
     78INCL_CORE       = -I $(INCLUDES_DIR)/core
     79INCL_CEE        = -I $(INCLUDES_DIR)/cee
     80INCL_FORTRAN    = -I $(INCLUDES_DIR)/fortran
     81INCL_PY         = -I $(INCLUDES_DIR)/python
    8282
    83 # default:
    8483
     84default: $(TEST_PROGS)
    8585all: $(TEST_PROGS)
    8686test: $(TEST_PROGS)
     
    115115        $(CXX) $(DEBUG) $(INCL_CEE) $(INCL_CORE) $(LIB_SCEW_INCL) -o $@ $^ $(LIB_RAPPTURE_T)
    116116
    117 RpLibraryCInterface_test: $(SRC_TEST)/RpLibraryCInterface_test.c
     117RpLibraryC_test: $(SRC_TEST)/RpLibraryC_test.c
    118118        $(CC) $(DEBUG) $(INCL_CEE) $(INCL_CORE) $(LIB_SCEW_INCL) -o $@ $^ $(LIB_RAPPTURE_T)
     119
     120RpLibraryF_test: $(SRC_TEST)/RpLibraryF_test.f
     121        $(F77) $(DEBUG) -o $@ $^ $(LIB_RAPPTURE_T)
    119122
    120123RpUnitsF_test: $(SRC_TEST)/RpUnitsF_test.f
  • trunk/test/src/RpLibraryC_test.c

    r77 r83  
    106106        id   = nodeId(childEle);
    107107        type = nodeType(childEle);
    108        
     108
    109109        printf("childEle comp = :%s:\n",comp);
    110110        printf("childEle   id = :%s:\n",id);
     
    132132        id   = nodeId(childEle);
    133133        type = nodeType(childEle);
    134        
     134
    135135        printf("childEle comp = :%s:\n",comp);
    136136        printf("childEle   id = :%s:\n",id);
  • trunk/test/src/RpLibrary_test.cc

    r77 r83  
    187187    std::cout << "//////////////////// LIB 3 ////////////////////" << std::endl;
    188188    std::cout << lib3.xml() << std::endl;
     189
     190    lib2.result();
    189191
    190192    return 0;
Note: See TracChangeset for help on using the changeset viewer.