1UDUNITS(3f)                UNIDATA LIBRARY FUNCTIONS               UDUNITS(3f)
2
3
4

NAME

6       udunits,  utopen,  utmake,  uttime,  utorigin,  utclr,  utcpy,  utorig,
7       utscal, utmult, utinv,  utdiv,  utexp,  utdec,  utcaltime,  uticaltime,
8       utenc, utcvt, utfree, utcls - Unidata units library
9

SYNOPSIS

11       f77 -Iunidata_inc -Lunidata_lib -ludunits ...
12
13       include udunits.inc
14
15       integer function utopen     (character*(*) path)
16
17       PTR function     utmake     ()
18
19       integer function uttime     (PTR unit)
20
21       integer function utorigin   (PTR unit)
22
23       subroutine       utclr      (PTR unit)
24
25       subroutine       utcpy      (PTR source, PTR dest)
26
27       subroutine       utorig     (PTR source,
28                                    doubleprecision amount,
29                                    PTR result)
30
31       subroutine       utscal     (PTR source,
32                                    doubleprecision factor,
33                                    PTR result)
34
35       subroutine       utmult     (PTR term1, PTR term2,
36                                    PTR result)
37
38       subroutine       utinv      (PTR source, PTR result)
39
40       subroutine       utdiv      (PTR numer, PTR denom,
41                                    PTR result)
42
43       subroutine       utexp      (PTR source, integer power,
44                                    PTR result)
45
46       integer function utdec      (character*(*) spec, PTR unit)
47
48       integer function utcaltime  (doubleprecision value,
49                                    PTR unit,
50                                    integer year,
51                                    integer month,
52                                    integer day,
53                                    integer hour,
54                                    integer minute,
55                                    real second)
56
57       integer function uticaltime (integer year,
58                                    integer month,
59                                    integer day,
60                                    integer hour,
61                                    integer minute,
62                                    real second
63                                    PTR unit,
64                                    doubleprecision value)
65
66       integer function utenc      (PTR unit, character*(*) spec)
67
68       integer function utcvt      (PTR from, PTR to,
69                                    doubleprecision slope,
70                                    doubleprecision intercept)
71
72       subroutine       utfree     (PTR unit)
73
74       subroutine       utcls      ()
75

DESCRIPTION

77       The  Unidata units library, udunits, supports conversion of unit speci‐
78       fications between formatted and binary forms,  arithmetic  manipulation
79       of  unit  specifications,  and  conversion of values between compatible
80       scales of measurement.
81
82       A unit is the amount by which a physical  quantity  is  measured.   For
83       example:
84
85
86
87       A  unit can have an origin associated with it -- in which case the unit
88       and origin together define a scale.  For example, the phrase "the  tem‐
89       perature  is 25 degrees Celsius" specifies a particular point on a mea‐
90       surement scale; whereas the phrase "the temperature  difference  is  25
91       degrees Celsius" specifies a unit with no origin and, hence, no associ‐
92       ated scale.  If not remembered, this subtle distinction can cause prob‐
93       lems when handling units.
94
95       Because  the units library passes pointers to units structures and FOR‐
96       TRAN 77 has no pointer type, the word PTR in the above synopsis  stands
97       for  whatever  FORTRAN type is appropriate for holding a pointer to a C
98       structure on the given platform.  This is  necessarily  platform-depen‐
99       dent  and,  consequently,  IT  IS UP TO THE USER TO DECLARE AND USE THE
100       CORRECT FORTRAN DATA TYPE.
101
102       utopen() initializes the units package.  If path is not empty, then  it
103       specifies a units file containing initializing unit definitions; other‐
104       wise, the environment variable UDUNITS_PATH is checked and, if it exits
105       and  is  not  empty,  then it is assumed to contain the pathname of the
106       units file; otherwise, a compile-time default pathname is used.
107
108       The definitions in the units file are read into memory.  This  function
109       returns  0  on  success,  UT_ENOFILE  if  the units file doesn't exist,
110       UT_ESYNTAX if the units file contains a syntax  error,  UT_EUNKNOWN  if
111       the  units  file  contains  an  unknown specification, UT_EIO if an I/O
112       error occurred while accessing the units file, and UT_EALLOC if a  mem‐
113       ory allocation failure occurred.
114
115       utdec()  decodes  the  formatted  unit specification spec into a binary
116       unit representation and stores the result in unit.  The  binary  repre‐
117       sentation  is used for algebraic manipulation.  This function returns 0
118       on success, UT_ENOINIT if the package hasn't been initialized,  UT_EUN‐
119       KNOWN  if the specification contains an unknown unit, and UT_ESYNTAX if
120       the specification contains a syntax error.
121
122       utcaltime() converts the amount, value, of  the  temporal  unit,  unit,
123       into  a UTC-referenced date and time (see, however, the section on HAN‐
124       DLING TIME).  The reference unit shall be a time unit and have an  ori‐
125       gin.   This  function  returns  0 on success, UT_ENOINIT if the package
126       hasn't been initialized and UT_EINVALID if the unit structure is not  a
127       temporal one.
128
129       uticaltime()  converts  a UTC-referenced date and time into the amount,
130       value, of the temporal unit, unit (see, however, the  section  on  HAN‐
131       DLING  TIME).  The reference unit shall be a time unit and have an ori‐
132       gin.  This function returns 0 on success,  UT_ENOINIT  if  the  package
133       hasn't  been initialized and UT_EINVALID if the unit structure is not a
134       temporal one.
135
136       utcvt() returns the coefficients of the Galilean transformation (i.e. y
137       =  a*x  +  b) necessary to convert the from unit into the to unit.  The
138       units must be compatible (i.e., their quotient must be  dimensionless).
139       On  successful  return, slope and intercept will contain the values for
140       the slope and  intercept  coefficients,  respectively.   This  function
141       returns  0  on  success, UT_ENOINIT if the package hasn't been initial‐
142       ized, UT_EINVALID if one of the unit variables is invalid, and UT_ECON‐
143       VERT if the units are not convertable.
144
145       utenc()  encodes  the  binary  unit variable unit into a formatted unit
146       specification and stores the string in spec.  This function  returns  0
147       on  success, UT_ENOINIT if the package hasn't been initialized, UT_EIN‐
148       VALID if the unit variable is invalid, and UT_ENOROOM if  the  supplied
149       character buffer is too small.
150
151       utclr()  clears  a  unit  variable  by  setting it to the dimensionless
152       scalar 1.
153
154       uttime() returns 1 if the given unit variable refers to a time unit;  0
155       otherwise.   This  function ignores whether or not the unit has an ori‐
156       gin.
157
158       utorigin() returns 1 if the given unit variable  has  an  origin  (i.e.
159       defines a scale) and 0 otherwise.
160
161       utcpy()  copies  the  unit  variable  source to the unit variable dest.
162       This function correctly handles the case where the same  unit  variable
163       is referenced by the source and destination units.
164
165       utscal()  scales  the unit variable source by the multiplicative scalar
166       factor, storing the result in the unit variable result.  This  function
167       correctly  handles  the case where the same unit variable is referenced
168       by the source and result units.
169
170       utinv() inverts the unit variable source, storing the  result  in  unit
171       variable  result.   Multiplying  a  unit  by  its reciprocal yields the
172       dimensionless scalar 1.  This function correctly handles the case where
173       the source and result unit refer to the same variable.
174
175       utdiv()  divides  unit variable numer by unit variable denom and stores
176       the result in unit variable result.  This  function  correctly  handles
177       the  case  where  the  same  unit variable is referenced by two or more
178       arguments.
179
180       utmult() multiplies unit variable term1  by  unit  variable  term2  and
181       stores  the  result  in  unit variable result.  This function correctly
182       handles the case where the same unit variable is referenced by  two  or
183       more arguments.
184
185       utexp() raises the unit variable source by the power power, storing the
186       result in the unit variable result.  This  function  correctly  handles
187       the  case  where the same unit variable is referenced by the source and
188       result units.
189
190       utcls() terminates usage of this package.  In particular, it frees  all
191       allocated  memory.   It  should be called when the library is no longer
192       needed.
193
194       utmake() Creates a new unit variable.  The value returned by this func‐
195       tion  may be used in subsequent calls.  The unit variable is cleared by
196       a call to utclr.
197
198       utfree() Frees the unit variable unit which was returned by a  previous
199       call to utmake().
200

HANDLING TIME

202       The  udunits(3)  package uses a mixed Gregorian/Julian calendar system.
203       Dates prior to 1582-10-15 are assumed to use the Julian calendar, which
204       was  introduced  by Julius Caesar in 46 BCE and is based on a year that
205       is exactly 365.25 days long.  Dates on and after 1582-10-15 are assumed
206       to use the Gregorian calendar, which was introduced on that date and is
207       based on a year that is exactly 365.2425 days long.  (A year  is  actu‐
208       ally  approximately 365.242198781 days long.)  Seemingly strange behav‐
209       ior of the udunits(3) package can result if a user-given time  interval
210       includes  the changeover date.  For example, utCalendar() and utInvCal‐
211       endar() can be used to show that 1582-10-15 *preceeded* 1582-10-14 by 9
212       days.
213

EXAMPLES

215       In  the  following,  it  is assumed that a FORTRAN INTEGER data type is
216       appropriate for storing a pointer to a C structure.  This assumption is
217       valid  for  most  32-bit  architectures  but is invalid for most 64-bit
218       architectures that have 32-bit INTEGERs (e.g. a DEC Alpha).
219
220       Convert two data sets to a common unit, subtract one  from  the  other,
221       then save the result in a (different) output unit:
222
223                 INTEGER   UTOPEN
224                 ...
225                 IF (UTOPEN('') .NE. 0) THEN
226           C         Handle initialization error
227                 ELSE
228                     CHARACTER*80        UNITSTRING1, UNITSTRING2
229                     CHARACTER*80        OUTPUTUNITSTRING
230                     INTEGER             UNIT1, UNIT2, OUTPUTUNIT
231                     INTEGER             UTMAKE, UTDEC
232                     ...
233                     UNIT1       = UTMAKE()
234                     UNIT2       = UTMAKE()
235                     OUTPUTUNIT  = UTMAKE()
236                     IF (UTDEC(UNITSTRING1, UNIT1) .NE. 0 .OR.
237                *        UTDEC(UNITSTRING2, UNIT2) .NE. 0 .OR.
238                *        UTDEC(OUTPUTUNITSTRING2, OUTPUTUNIT) .ne. 0) THEN
239           C
240           C             Handle decode error
241           C
242                     ELSE
243                         DOUBLEPRECISION INSLOPE, ININTERCEPT
244                         DOUBLEPRECISION OUTSLOPE, OUTINTERCEPT
245
246                         IF (UTCVT(UNIT2, UNIT1, INSLOPE, ININTERCEPT) .NE. 0
247                *            .OR.  UTCVT(UNIT1, OUTPUTUNIT, OUTSLOPE,
248                *                        OUTINTERCEPT) .NE. 0) THEN
249           C
250           C                 Handle data-incompatibility
251           C
252                         ELSE
253           C                 Process data using:
254           C                     OUTPUTVALUE = OUTSLOPE*(DATA1VALUE
255           C                                   - (INSLOPE*DATA2VALUE
256                *                                 + ININTERCEPT))
257           C                                   + OUTINTERCEPT
258                         ENDIF
259                         CALL UTFREE(UNIT1)
260                         CALL UTFREE(UNIT2)
261                         CALL UTFREE(OUTPUTUNIT)
262                         CALL UTCLS
263                     ENDIF
264                 ENDIF
265
266       the  above example could be made more efficient by testing the returned
267       conversion factors for nearness to 1  and  0  and  using  appropriately
268       streamlined processing expressions.
269
270
271       Compute  a  threshold value corresponding to an input data value plus a
272       user-specified delta (the units of the input data value and  delta  can
273       differ):
274
275                 INTEGER         INPUT_UNIT, DELTA_UNIT
276                 INTEGER         UTOPEN, UTMAKE, UTDEC
277                 CHARACTER*(80)  INPUT_UNIT_STRING, DELTA_UNIT_STRING
278                 ...
279                 INPUT_UNIT      = UTMAKE()
280                 DELTA_UNIT      = UTMAKE()
281
282                 CALL UTOPEN('udunits.dat')
283                 IF (UTDEC(INPUT_UNIT_STRING, INPUT_UNIT) .NE. 0 .OR.
284                     UTDEC(DELTA_UNIT_STRING, DELTA_UNIT) .NE. 0) THEN
285           C
286           C         Handle decode error
287           C
288                 ELSE
289                     DOUBLEPRECISION     SLOPE, INTERCEPT
290                     REAL                DELTA_VALUE
291                     ...
292                     IF (UTCVT(DELTA_UNIT, INPUT_UNIT, SLOPE, INTERCEPT)
293                *        .NE. 0) THEN
294           C
295           C             Handle units incompatibility
296           C
297                     ELSE
298                         REAL    INPUT_VALUE
299                         REAL    THRESHOLD
300                         ...
301                         THRESHOLD = INPUT_VALUE + SLOPE*DELTA_VALUE + INTERCEPT
302                     ENDIF
303                 ENDIF
304                 CALL UTCLS
305
306
307       Compute  the  number of time intervals from a start time to a reference
308       time.  PTR is a placeholder for the FORTRAN data type equivalent  to  a
309       memory address.
310
311                 IMPLICIT          NONE
312                 REAL              REF_SECOND      / 0 /
313                 INTEGER           UTOPEN
314                 INTEGER           UTDEC
315                 INTEGER           UTICALTIME
316                 INTEGER           STATUS
317                 INTEGER           REF_YEAR        / 1990 /
318                 INTEGER           REF_MONTH       / 1 /
319                 INTEGER           REF_DAY         / 1 /
320                 INTEGER           REF_HOUR        / 1 /
321                 INTEGER           REF_MINUTE      / 0 /
322                 INTEGER           UTMAKE
323                 INTEGER           TIMECENTERS_UNIT
324                 DOUBLEPRECISION   REF_VALUE
325
326                 STATUS = UTOPEN('udunits.dat')
327                 IF (STATUS .NE. 0) THEN
328                     PRINT *, 'Couldn''t open database: status =', STATUS
329                     CALL ABORT
330                 ENDIF
331
332                 TIMECENTERS_UNIT = UTMAKE()
333
334                 STATUS = UTDEC('2 minutes since 1990-1-1', TIMECENTERS_UNIT)
335                 IF (STATUS .NE. 0)
336                *THEN
337                     PRINT *, 'UTDEC() =', STATUS
338                 ELSE
339           C
340           C         Reference time is start time plus 1 hour.
341           C
342                     STATUS = UTICALTIME(REF_YEAR, REF_MONTH, REF_DAY, REF_HOUR,
343                *                    REF_MINUTE, REF_SECOND, TIMECENTERS_UNIT,
344                *                    REF_VALUE)
345           C
346           C         Number of time intervals between start and reference times:
347           C
348                     IF (STATUS .NE. 0) THEN
349                         PRINT *, 'UTICALTIME() =', STATUS
350                     ELSE
351                         IF (30 .NE. REF_VALUE) THEN
352                             PRINT *, 'Incorrect result:', REF_VALUE
353                         ELSE
354                             PRINT *, 'Correct result'
355                         ENDIF
356                     ENDIF
357                 ENDIF
358                 END
359
360

FORMATTED UNIT SPECIFICATIONS

362       The following are examples of formatted unit specifications that can be
363       interpreted by the utScan() function:
364
365           10 kilogram.meters/seconds2
366           10 kg-m/sec2
367           10 kg m/s^2
368           (PI radian)2
369           degF
370           100rpm
371           geopotential meters
372           33 feet water
373
374       A unit is specified as an arbitrary product of constants and unit names
375       raised  to arbitrary integral powers.  Division is indicated by a slash
376       `/'.  Multiplication is indicated by whitespace, a  period  `.',  or  a
377       hyphen `-'.  Exponentiation is indicated by an integer suffix or by the
378       exponentiation operators `^' and `**'.  Parentheses  may  be  used  for
379       grouping and disambiguation.
380
381       Arbitrary Galilean transformations (i.e. y = ax + b) are supported.  In
382       particular, temperature and time  conversions  are  correctly  handled.
383       The specification:
384
385              degF @ 32
386
387       indicates  a  Fahrenheit  scale  with  the origin shifted to thirty-two
388       degrees Fahrenheit (i.e. to zero degrees Celsius).  The  Celsius  scale
389       is equivalent to the following unit:
390
391              1.8 degR @ 273.15
392
393       Besides  the  character  `@',  the  words  `after',  `from', `ref', and
394       `since' may also be used.  Note that  multiplication  takes  precedence
395       over  origin-shift.   In order of increasing precedence, the operations
396       are origin-shift, division, multiplication, and exponentiation.
397
398       Units of time are similarly handled.  The specification:
399
400              seconds since 1992-10-8 15:15:42.5 -6:00
401
402       indicates seconds since October 8th, 1992 at 3 hours,  15  minutes  and
403       42.5  seconds  in  the afternoon in the time zone which is six hours to
404       the west of Coordinated Universal Time (i.e. Mountain  Daylight  Time).
405       The  time  zone specification can also be written without a colon using
406       one or two-digits (indicating hours) or three or four digits  (indicat‐
407       ing hours and minutes).
408
409       utScan() understands most conventional prefixes and abbreviations:
410
411
412
413       The function utPrint() always encodes a unit specification one way.  To
414       reduce misunderstandings, it is recommended that this encoding style be
415       used  as  the default.  In general, a unit is printed in terms of basic
416       units, factors, and exponents.  Basic units are  separated  by  spaces;
417       and any exponent directly appends its associated unit.  The above exam‐
418       ples would be printed as follows:
419
420           10 kilogram meter second-2
421           9.8696044 radian2
422           0.555556 kelvin @ 255.372
423           10.471976 radian second-1
424           9.80665 meter2 second-2
425           98636.5 kilogram meter-1 second-2
426
427       Note that the Fahrenheit unit is encoded as a deviation, in  fractional
428       kelvins, from an origin at 255.372 kelvin.
429

UNITS FILE

431       The  units  file is a formatted file containing unit definitions and is
432       used to initialize this package.  It is the first place to look to dis‐
433       cover  the  set  of valid names and symbols (of which there are many --
434       On October 9, 1992, it contained 446 entries).
435
436       The format for the units file is documented internally and the file may
437       be  modified by the user as necessary.  In particular, additional units
438       and constants may be  easily  added  (including  variant  spellings  of
439       existing units or constants).
440

ENVIRONMENT

442       UDUNITS_PATH     If utInit() is called without a pathname argument, and
443                        if this environment variable is  non-empty,  then  its
444                        value  overrides  the  default  pathname for the units
445                        file.
446

DIAGNOSTICS

448       This package  prints  (hopefully)  self-explanatory  error-messages  to
449       standard error.
450

SEE ALSO

452       udunits(1).
453

BUGS AND RESTRICTIONS

455       utScan() is case-sensitive.  If this causes difficulties, you might try
456       making appropriate additional entries to the units file.
457
458       Some unit abbreviations in the default units file might  seem  counter-
459       intuitive.  In particular, note the following:
460
461           For       Use               Not     Which Instead Means
462
463           Celsius   `Celsius'         `C'     coulomb
464           gram      `gram'            `g'     <standard free fall>
465           gallon    `gallon'          `gal'   <acceleration>
466           radian    `radian'          `rad'   <absorbed dose>
467           Newton    `newton' or `N'   `nt'    nit (unit of photometry)
468

REFERENCES

470       NIST  Special  Publication 811, 1995 Edition: "Guide for the Use of the
471       International  System  of  Units  (SI)"  by  Barry  N.   Taylor.    URL
472       <http://physics.nist.gov/Divisions/Div840/SI.html>.
473
474       ANSI/IEEE Std 260-1978: "IEEE Standard Letter Symbols for Units of Mea‐
475       surement".
476
477       ASTM Designation: E 380 - 85: "Standard for METRIC PRACTICE".
478
479       International Standard (ISO) 2955: "Information processing -- Represen‐
480       tation  of  SI and other units in systems with limited character sets",
481       Ref. No. ISO 2955-1983 (E).
482
483
484
485Printed: 119.6.22        $Date: 2003/08/29 18:30:33 $              UDUNITS(3f)
Impressum