Wednesday, April 30, 2014
Makefile example
FC=/usr/local/intel/composerxe-2011.2.137/bin/intel64/ifort
CFLAGS = -O3 -shared-intel
LD=$(FC)
LDFLAGS = -O3 -shared-intel -Wl,
RM = rm
EXE = debufr
FSRC = main_read_ssmis.f90
## FOBJ depending on $(FSRC) , convert FSRC from .f90 to .o
FOBJ = ${FSRC:.f90=.o}
# Clear out all suffixes
.SUFFIXES:
# List only those we use
.SUFFIXES: .o .f90
# Define a suffix rule for .f90 -> .o (Suffix rule / implicit rule )
# How to convert .f90 -> .o
.f90.o:
$(FC) $(CFLAGS) -c $<
all : $(EXE)
$(EXE): $(FOBJ) ../libbufr.a
$(LD) $(LDFLAGS) -o $@ $(FOBJ) -L../ -lbufr
clean:
$(RM) -f $(FOBJ)
cleaner:
$(RM) -f $(EXE) $(FOBJ)
F90 module
The functionality of the module unit is similar to that of the C header file.
Also it's like C++ header file defining namespace, therefore, other components, who USE it, can access its content.
A form of a module is as follows
MODULE name
specifications
END MODULE name
See example below:
To make use of the module in the main program, we employ the USE statement. We use a special form of the USE statement that specifies that we are only interested in variable radius in the main program, namely, USE Circle, ONLY : radius. Similarly, we make use of only the parameter Pi in the function subprogram Area_Circle by way of the USE statement appearing in that routine.
eg 1:
eg 2:
MODULE Dyn_Array
INTEGER :: n
REAL, DIMENSION(:), ALLOCATABLE :: A
END MODULE Dyn_Array
PROGRAM Play_with_Array
USE Dyn_Array
IMPLICIT NONE
INTERFACE ! checking subroutine signature
SUBROUTINE Get_Data
END SUBROUTINE Get_Data
END INTERFACE
INTERFACE ! checking subroutine signature
SUBROUTINE Dealloc_Array
END SUBROUTINE Dealloc_Array
END INTERFACE
REAL :: Prod_A, Sum_A
CALL Get_Data ! load data into A
Prod_A = PRODUCT(A) ! use A
write(*,100) "The product of the elements of array A area", &
Prod_A
Sum_A = SUM(A) ! use A
write(*,100) "The sum of the elements of array A are", &
Sum_A
CALL Dealloc_Array ! unload A
100 format (A, 2x, F11.2)
END PROGRAM Play_with_Array
SUBROUTINE Get_Data
USE Dyn_Array ! include everything from module (header file in c)
IMPLICIT NONE
INTEGER :: AllocateStatus
write(*,'(A)', ADVANCE = "NO") "Input the number of elements desired: "
read(*,*) n
ALLOCATE( A(n), STAT = AllocateStatus) ! load A
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
write(*, '(A)', ADVANCE = "NO") "Input array values: "
read(*,*) A
END SUBROUTINE Get_Data
SUBROUTINE Dealloc_Array
USE Dyn_Array
IMPLICIT NONE
INTEGER :: DeAllocateStatus
DEALLOCATE( A, STAT = DeAllocateStatus) ! unload A
IF (DeAllocateStatus /= 0) STOP "*** Trouble deallocating ***"
END SUBROUTINE Dealloc_Array
Also it's like C++ header file defining namespace, therefore, other components, who USE it, can access its content.
A form of a module is as follows
MODULE name
specifications
END MODULE name
See example below:
To make use of the module in the main program, we employ the USE statement. We use a special form of the USE statement that specifies that we are only interested in variable radius in the main program, namely, USE Circle, ONLY : radius. Similarly, we make use of only the parameter Pi in the function subprogram Area_Circle by way of the USE statement appearing in that routine.
eg 1:
MODULE Circle REAL, PARAMETER :: Pi = 3.1415927 REAL :: radius END MODULE Circle PROGRAM Area USE Circle, ONLY : radius ! only interested in radius. IMPLICIT NONE INTERFACE ! check function signature FUNCTION Area_Circle (r) REAL, INTENT(IN) :: r END FUNCTION Area_Circle END INTERFACE write(*, '(A)', ADVANCE = "NO") "Enter the radius of the circle: " read(*,*) radius ! radius is NOT defined in main code, included from Module Circle write(*,100) "Area of circle with radius", radius, " is", & Area_Circle(radius) 100 format (A, 2x, F6.2, A, 2x, F11.2) END PROGRAM Area FUNCTION Area_Circle(r) USE Circle, ONLY : Pi ! only interested in constant/parameter Pi. IMPLICIT NONE REAL :: Area_Circle REAL, INTENT(IN) :: r Area_Circle = Pi * r * r ! Pi is NOT defined in function either, included from module. END FUNCTION Area_Circle
eg 2:
MODULE Dyn_Array
INTEGER :: n
REAL, DIMENSION(:), ALLOCATABLE :: A
END MODULE Dyn_Array
PROGRAM Play_with_Array
USE Dyn_Array
IMPLICIT NONE
INTERFACE ! checking subroutine signature
SUBROUTINE Get_Data
END SUBROUTINE Get_Data
END INTERFACE
INTERFACE ! checking subroutine signature
SUBROUTINE Dealloc_Array
END SUBROUTINE Dealloc_Array
END INTERFACE
REAL :: Prod_A, Sum_A
CALL Get_Data ! load data into A
Prod_A = PRODUCT(A) ! use A
write(*,100) "The product of the elements of array A area", &
Prod_A
Sum_A = SUM(A) ! use A
write(*,100) "The sum of the elements of array A are", &
Sum_A
CALL Dealloc_Array ! unload A
100 format (A, 2x, F11.2)
END PROGRAM Play_with_Array
SUBROUTINE Get_Data
USE Dyn_Array ! include everything from module (header file in c)
IMPLICIT NONE
INTEGER :: AllocateStatus
write(*,'(A)', ADVANCE = "NO") "Input the number of elements desired: "
read(*,*) n
ALLOCATE( A(n), STAT = AllocateStatus) ! load A
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
write(*, '(A)', ADVANCE = "NO") "Input array values: "
read(*,*) A
END SUBROUTINE Get_Data
SUBROUTINE Dealloc_Array
USE Dyn_Array
IMPLICIT NONE
INTEGER :: DeAllocateStatus
DEALLOCATE( A, STAT = DeAllocateStatus) ! unload A
IF (DeAllocateStatus /= 0) STOP "*** Trouble deallocating ***"
END SUBROUTINE Dealloc_Array
Tuesday, April 29, 2014
f90 data type
f90 Language elements
The basic components of the Fortran language are its character set. The members are:- the letters A ... Z and a ... z (which are equivalent outside a character context);
- the numerals 0 ... 9;
- the underscore _; and
- the special characters
= : + blank - * / ( ) , . $ ' (old) ! " % & ; < > ? (new)
Label: 123 Constant: 123.456789_long Keyword: ALLOCATABLE Operator: .add. Name: solve_equation (up to 31 characters, including _) Separator: / ( ) (/ /) , = => : :: ; %From the tokens, we can build statements. These can be coded using the new free source form which does not require positioning in a rigid column structure:
FUNCTION string_concat(s1, s2) ! This is a comment TYPE (string), INTENT(IN) :: s1, s2 TYPE (string) string_concat string_concat%string_data = s1%string_data(1:s1%length) // & s2%string_data(1:s2%length) ! This is a continuation string_concat%length = s1%length + s2%length END FUNCTION string_concatNote the trailing comments and the trailing continuation mark. There may be 39 continuation lines, and 132 characters per line. Blanks are significant. Where a token or character constant is split across two lines:
... start_of& &_name ... 'a very long & &string'a leading & on the continued line is also required. Automatic conversion of source form for existing programs can be carried out by convert.f90. Its options are:
- significant blank handling;
- indentation;
- CONTINUE replaced by END DO;
- name added to subprogram END statement; and
- INTEGER*2 etc. syntax converted.
INTEGER
1 0 -999 32767 +10for the default kind;
but we may also define, for instance for a desired range of [-10^4, +10^4], a named constant, say two_bytes:
! I need an integer in range of [-10^4, +10^4],
INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND(4) ! 4 means 10^4
eg:
INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND(4) ! [-10^4, 10^4]
INTEGER (KIND = two_bytes) :: ii ! :: required
INTEGER jj ! nothing before jj
! kind() returns number of bytes to store variable
print *, kind(ii) ! customized integer type , 2 bytes
print *, kind(34_two_bytes) ! 2 bytes , attach kind type to a constant 34 to indicate its type.
print *, kind(jj) ! default integer type , 4 bytes
print *, range(ii) ! customized integer type , 4 [-10^4, 10^4]
print *, range(jj) ! default integer type , 9 [-10^9, 10^9]
! [-0.123*10^40, 0.123*10^40]
INTEGER, PARAMETER :: realType = SELECTED_REAL_KIND(3,40)
real (KIND = realType) :: r1
real r2
print *, kind(r1) ! customized integer type
print *, kind(r2) ! default integer type
print *, range(r1) ! customized integer type
print *, range(r2) ! default integer type
8 ! bytes
4
307 ! range
37
Also, in DATA statements, binary, octal and hexcadecimal constants may be used:
B'01010101' O'01234567' Z'10fa'
REAL
There are at least two real kinds - the default, and one with greater precision (this replaces DOUBLE PRECISION). We might specifyINTEGER, PARAMETER :: long = SELECTED_REAL_KIND(9, 99)for at least 9 decimal digits of precision and a range of 10*(-99) to 10**99, allowing
1.7_long ! use a named constantAlso, we have the intrinsic functions
KIND(1.7_long) PRECISION(1.7_long) RANGE(1.7_long)that give in turn the kind type value, the actual precision (here at least 9), and the actual range (here at least 99).
COMPLEX
This data type is built of two integer or real components:(1, 3.7_long)The forms of literal constants for the two non-numeric data types are:
CHARACTER
'A string' "Another" 'A "quote"' ''(the last being a null string). Other kinds are allowed, especially for support of non-European languages:
2_' 'and again the kind value is given by the KIND function:
KIND('ASCII')
LOGICAL
Here, there may also be different kinds (to allow for packing into bits):.FALSE. .true._one_bitand the KIND function operates as expected:
KIND(.TRUE.)The numeric types are based on model numbers with associated inquiry functions (whose values are independent of the values of their arguments):
DIGITS(X) Number of significant digits EPSILON(X) Almost negligible compared to one (real) HUGE(X) Largest number MAXEXPONENT(X) Maximum model exponent (real) MINEXPONENT(X) Minimum model exponent (real) PRECISION(X) Decimal precision (real, complex) RADIX(X) Base of the model RANGE(X) Decimal exponent range TINY(X) Smallest postive number (real)These functions are important for portable numerical software. We can specify scalar variables corresponding to the five intrinsic types:
INTEGER(KIND=2) i REAL(KIND=long) a COMPLEX current LOGICAL Pravda CHARACTER(LEN=20) word CHARACTER(LEN=2, KIND=Kanji) kanji_wordwhere the optional KIND parameter specifies a non-default kind, and the LEN= specifier replaces the *len form. The explicit KIND and LEN specifiers are optional:
CHARACTER(2, Kanji) kanji_wordworks just as well. For derived-data types we must first define the form of the type:
TYPE person CHARACTER(10) name REAL age END TYPE personand then create structures of that type:
TYPE(person) you, meTo select components of a derived type, we use the % qualifier:
you%ageand the form of a literal constant of a derived type is shown by:
you = person('Smith', 23.5)which is known as a structure constructor. Definitions may refer to a previously defined type:
TYPE point REAL x, y END TYPE point
TYPE triangle TYPE(point) a, b, c !! TYPE(point) together END TYPE triangle
and for a variable of type triangle, as in
TYPE(triangle) t !! TYPE(triangle) togetherwe have components of type point:
t%a t%b t%c !! how to refer to each component
which, in turn, have ultimate components of type real:
t%a%x t%a%y t%b%x etc.
type base
integer, dimension(3) :: aa=(/1,2,3/)
end type base
We note that the
% qualifier was chosen rather than . because of ambiguity difficulties.
Arrays are considered to be variables in their own right. Given
REAL a(10) INTEGER, DIMENSION(0:100, -50:50) :: map(the latter an example of the syntax that allows grouping of attributes to the left of :: and of variables sharing the attributes to the right), we have two arrays whose elements are in array element order (column major), but not necessarily in contiguous storage. Elements are, for example,
a(1) a(i*j)and are scalars. The subscripts may be any scalar integer expression. Sections are
a(i:j) ! rank one map(i:j, k:l:m) ! rank two a(map(i, k:l)) ! vector subscript a(3:2) ! zero lengthWhole arrays and array sections are array-valued objects. Array-valued constants (constructors) are available:
(/ 1, 2, 3, 4, 5 /) (/ (i, i = 1, 9, 2) /) (/ ( (/ 1, 2, 3 /), i = 1, 10) /) (/ (0, i = 1, 100) /) (/ (0.1*i, i = 1, 10) /)making use of the implied-DO loop notation familiar from I/O lists. A derived data type may, of course, contain array components:
TYPE triplet REAL, DIMENSION(3) :: vertex END TYPE triplet TYPE(triplet), DIMENSION(4) :: tso that
t(2) is a scalar (a structure) t(2)%vertex is an array component of a scalarThere are some other interesting character extensions. Just as a substring as in
CHARACTER(80), DIMENSION(60) :: page ... = page(j)(i:i) ! substringwas already possible, so now are the substrings
'0123456789'(i:i) you%name(1:2)Also, zero-length strings are allowed:
page(j)(i:i-1) ! zero-length stringFinally, there are some new intrinsic character functions:
ACHAR IACHAR (for ASCII set) ADJUSTL ADJUSTR LEN_TRIM INDEX(s1, s2, BACK=.TRUE.) REPEAT SCAN (for one of a set) TRIM VERIFY(for all of a set)
Fortran 90: Derived Data Types
The Fortran 90 derived data type is similar to C structures and also has some similarities with C++ classes. The syntax for declaring a derived type, istype mytype integer:: i real*8 :: a(3) end type mytypeTo create a variable of type
mytype
, use
type (mytype) varAn array of
mytype
can also be created.
type (mytype) stuff(3)Elements of derived types are accessed with the "%" operator. For instance,
var%i = 3 var%a(1) = 4.0d0 stuff(1)%a(2) = 8.0d0The real power of derived types comes with the ability to choose bewteen functions (or subroutines) based on the type of their arguments. Different functions can be called by the same name, depending on whether the argument type is real, integer,or even a derived type. Intrinsic Fortran routines have always had this ability, the simplest example being choosing between single and double precision versions of the function. Now it can be extended to user's routines and defined data types as well. See the example in the section on intefaces for subroutines . The compiler is free to store the constitutients of a derived type how it chooses. To force the derived type to be stored contiguously, use the
sequence
keyword. For example,
type mytype
sequence
integer:: i
real*8 :: a(3)
end type mytype
The IBM compiler seems to require this keyword if a derived type is the argument
of a subroutine or function.Pointer type :
eg 1:
integer , pointer :: ip !! ip is a pointer to a single data
integer, allocatable, dimension(:), target :: iarr
allocate(iarr(20))
do i = 1, 20
iarr (i) = i
enddo
ip => iarr(1) !! pointer can only points to a single value, ip is same as iarr(1)
!! not to a chunk of memory seen in c/c++
print *, ip
iarr(1) = 999
print *, ip
1
999
eg2 :
integer , parameter :: size = 3
integer , pointer :: ip(:) !! pointer to a chunk of memory
integer, allocatable,target :: iarr(:,:)
allocate(iarr(10,10))
do i = 1, size
do j = 1, size
iarr (i,j) = i+j*10
enddo
enddo
ip => iarr(1:size, 1) !! to a chunk of memory, ip -> 3 ints
print *, ip
iarr(2,1) = 999
print *, ip
ip(2)=888
print *, ip
11 12 13
11 999 13
11 888 13
Monday, April 14, 2014
Thursday, April 10, 2014
create SVN repository locally
1. Create a SVN repository
$ cd
$ svnadmin create SVN_REPOSITORY # create folder SVN_REPOSITORY in $HOME
$ echo `pwd`/SVN_REPOSITORY # /data/home001/dxu/SVN_REPOSITORY
2. Add stuff into the repository
# check out the empty repository
$ svn co file:///data/home001/dxu/SVN_REPOSITORY my_reps
$ cd my_reps
$ mkdir dir1 # create a folder dir1
$ svn add dir1 # add dir1 into svn repository
$ svn commit -m "" dir1 # commit the change into svn
3. How to use svn copy
Note: File bar.txt must NOT exist, otherwise, get error like
svn: Path 'bar.txt' is not a directory
$ svn copy file:///tmp/repos/test/far-away file:///tmp/repos/test/over-there -m "remote copy."
This is the easiest way to “tag” a revision in your repository—just svn copy that revision (usually HEAD) into your tags directory.
$ svn copy -r 11 file:///tmp/repos/test/trunk file:///tmp/repos/test/tags/0.6.32-prerelease -m "Forgot to tag at rev 11"
Committed revision 13.
1) Either way is ok to specify a specific version
2) File abc / def must NOT exist before copy.
[dxu@orbit272l ssmis_bufr]$ svn copy main_read_ssmis.f90@146 abc
A abc
[dxu@orbit272l ssmis_bufr]$ svn copy -r146 main_read_ssmis.f90 def
A def
[dxu@orbit272l ssmis_bufr]$ diff abc def
[dxu@orbit272l ssmis_bufr]$
$ cd
$ svnadmin create SVN_REPOSITORY # create folder SVN_REPOSITORY in $HOME
$ echo `pwd`/SVN_REPOSITORY # /data/home001/dxu/SVN_REPOSITORY
2. Add stuff into the repository
# check out the empty repository
$ svn co file:///data/home001/dxu/SVN_REPOSITORY my_reps
$ cd my_reps
$ mkdir dir1 # create a folder dir1
$ svn add dir1 # add dir1 into svn repository
$ svn commit -m "" dir1 # commit the change into svn
3. How to use svn copy
Note: File bar.txt must NOT exist, otherwise, get error like
svn: Path 'bar.txt' is not a directory
$ svn copy foo.txt bar.txt
A bar.txt
$ svn status
A + bar.txt
OR
$ svn copy file:///tmp/repos/test/foo.txt bar.txt
$ svn copy near.txt file:///tmp/repos/test/far-away.txt -m "Remote copy."
$ svn copy file:///tmp/repos/test/far-away near-here A near-here
And finally, copying between two URLs:
$ svn copy file:///tmp/repos/test/far-away file:///tmp/repos/test/over-there -m "remote copy."
This is the easiest way to “tag” a revision in your repository—just svn copy that revision (usually HEAD) into your tags directory.
$ svn copy file:///tmp/repos/test/trunk file:///tmp/repos/test/tags/0.6.32-prerelease -m "tag tree" Committed revision 12.
And don't worry if you forgot to tag—you can always specify an older revision and tag anytime:
$ svn copy -r 11 file:///tmp/repos/test/trunk file:///tmp/repos/test/tags/0.6.32-prerelease -m "Forgot to tag at rev 11"
Committed revision 13.
Copy a file with specific version
1) Either way is ok to specify a specific version
2) File abc / def must NOT exist before copy.
[dxu@orbit272l ssmis_bufr]$ svn copy main_read_ssmis.f90@146 abc
A abc
[dxu@orbit272l ssmis_bufr]$ svn copy -r146 main_read_ssmis.f90 def
A def
[dxu@orbit272l ssmis_bufr]$ diff abc def
[dxu@orbit272l ssmis_bufr]$
Compare different versions of a file
$ slog main_read_ssmis.f90 ## find all versions
$ svn diff -r 145 main_read_ssmis.f90 ## comp local v.s. r145
$ svn diff -r 146:145 main_read_ssmis.f90 ## comp r146 v.s. r145
View different versions of a file
$ scat main_read_ssmis.f90 ## find all versions
$ svn cat -r145 main_read_ssmis.f90 |less ## view r145
$ svn cat main_read_ssmis.f90@145 |less ## view r145
Wednesday, April 9, 2014
Learn f90 in a day
1. Main Features of Fortran 90
Fortran 90 is a new programming language intended for use in scientific and engineering applications. It is a language that has developed by the introduction of features that are new to Fortran, but are based on experience of other languages (like C and Matlab for instance). Fortran 90 is very different from earlier versions of Fortran, yet it is completely backwards compatible with Fortran 77.
The features of Fortran 90 are far too numerous to mention in entirety here, but some of the key features are outlined below:
a) Free format on source code.
In Fortran 90, you can use either the Fortran 77 input format or free format. If you use free format, the file extension .f90 should be used for the file name.
b) Dynamic allocation and pointers.
It is now possible to allocate storage dynamically. This enables us to finally get rid of all the "work" arrays!
c) User defined data types. (data structure)
You can now define your own composite data types, similar to struct in C or record in Pascal.
d) Modules. ( oo programming)
Modules enables you to program in an object oriented style, similar to C++. Modules can also be used to hide global variables, thereby making the Fortran 77 common construct outdated.
e) Recursive functions.
Now a part of the language.
f) Built-in array operations. (similar to IDL)
Statements like A=0 and C=A+B are now valid when A and B are arrays. There are also built-in functions for matrix operations, e.g., matmul for performing matrix multiplication.
g) Operator overloading.
You can define your own meaning of operators like + and = for your own data types (objects).
2. Compile f90
f90 main.f90 -L/usr/class/me390/lib -lmy_lib90 ! link library
3. Basic program structure
Key features
Free-form source code is allowed. Statements may begin in any column.
Lines may extend to 132 characters.
More than one statement may be placed on a line ( ; )
In-line comments are allowed ( ! )
Continuation ( & )
Variable names may consist of up to 31 characters (letters, digits, and _ )
The first character of a variable name must be a letter.
Declarations
a) The command IMPLICIT NONE is allowed. This feature cancels the default naming
convention.
b) The separator :: is required in a type specification statement whenever it is used to
initialize a variable or to declare a special attribute (such as PARAMETER).
REAL :: Area = 0.
INTEGER :: Num_Months = 12 !
REAL, PARAMETER :: Pi = 3.1415927 ! define a parameter
REAL Area_circle = REAL :: Area_circle ! same
c) The precision of a real, integer, complex, or logical variable may be specified using a kind type
parameter.
Eg: to declare a variable A to be a real number with at least 10 decimal places of precision with a range of at least -10^34 to 10^34, do the following:
REAL(KIND = SELECTED_REAL_KIND(10,34)) :: A ! KIND is used specify precision
If the processor you are using is unable to support a variable with this type specification, a compile-time error will result.
d) To declare a real variable to have the equivalent of Fortran 77 accuracy DOUBLE PRECISION, simply do this:
INTEGER, PARAMETER :: DP = SELECTED_REAL_KIND(14) ! Define a parameter DP
REAL(KIND = DP) :: A ! Use the parameter DP
This declares the variable A to be of type real and have at least 14 decimal places of accuracy.
Program composition
The basic form of a Fortran 90 program is as follows:
PROGRAM name
declarations
executable statements
END PROGRAM
4. Logical expressions
Symbolic forms of the relational operators are allowed:
Old Operator New Symbol
------------ ------
.LT. <
.GT. >
.EQ. ==
.LE. <=
.GE. >=
.NE. /=
IF-ELSE constructs may be named by attaching a label at the beginning of the block:
name: IF (logical argument) THEN
statements
ELSE IF (logical argument) THEN name ! name is optional
statements
.
.
ENDIF name
if ( jj> 10 ) exit ! simple version
if ( jj> 10 ) then
exit
endif
The CASE construct may be used to execute a set of multi-alternative selection criteria:
SELECT CASE (selector) ! selector may be an integer, character, or logical expression.
CASE (list #1) ! a list of one or more possible values of the selector index
statements
CASE (list #2) statements
.
.
.
CASE DEFAULT ! may be omitted
statements
END SELECT
5. Loops
a) DO loops may have either of the two forms:
DO index_variable = start, end, step statements
ENDDO ( or END DO)
or,
DO nnn index_variable = start, end, step statements
nnn CONTINUE
In both cases, the step variable is optional and is assumed to have the value 1 if omitted. As with IF-ELSE and CASE constructs, DO loops may also have names.
b) WHILE loops are allowed. They have the general form:
DO WHILE (logical argument)
statements
END DO
c) An "infinite" loop may be performed as follows:
DO
conditional statement EXIT
END DO
6. Array
1) One-dimensional Arrays
REAL, DIMENSION(10) :: A, B ! 1-based default
INTEGER, DIMENSION(0:9) :: C ! 0-based
Array initialization
A = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 /)
or,
A = (/ (I, I = 1, 10) /)
Array assignment ( must have the same physical dimension )
B = A
Array operation ( must have the same physical dimension )
A = A + B
C = 2*C
For example, if A is assigned the values
A = (/ (I, I = 1,10) /)
WHERE (A > 5)
B = 1.
ELSEWHERE
B = 0.
END WHERE !B has the values 0, 0, 0, 0, 0, 1, 1, 1, 1, 1.
DOT_PRODUCT(A, B): ! returns the dot product of A and B
MAXVAL(A): ! returns the maximum value in array A
MAXLOC(A): ! returns a one-element 1D array whose value is
! the location of the first occurrence of the
! maximum value in A
PRODUCT(A): ! returns the product of the elements of A
SUM(A): ! returns the sum of the elements of A
Dynamic Array allocation
a) To declare a real allocatable array A, do
REAL, DIMENSION(:), ALLOCATABLE :: A ! : represent one dimension
b) To allocate memory at run time
ALLOCATE ( A(N) )
ALLOCATE ( A(N), STAT = AllocateStatus) ! AllocateStatus takes the value 0 if allocation is successful
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
c) To release memory allocatedly
DEALLOCATE (A, STAT = DeAllocateStatus) ! DeAllocateStatus : 0 if the deallocation was successful.
2) Multi-dimensional arrays
Array delcaration:
Multi-dimensional arrays can be dimensioned with statements like
REAL, DIMENSION(2,3) :: A ! 1-based by default
REAL, DIMENSION(0:1,0:2) :: B ! 0-based
INTEGER, DIMENSION(10,20,3) :: I
Array initialization:
The maximum limit on the rank (the number of dimensions) of an array is 7.
For instance, the values 1, 2, 3, 4, 5, 6 may be assigned to the two-dimensional array A by
A = (/ 1, 2, 3, 4, 5, 6 /) ! assign the values to A in column order similar to the rules of Fortran 77.
Array assignment: (both arrays in question have the same physical dimension)
B = A
WHERE (logical argument)
sequence of array assignments
ELSEWHERE
sequence of array assignments
END WHERE
MAXVAL(A, D): ! returns an array of one less dimension than A
! containing the maximum values of A along
! dimension D (if D is omitted, returns the
! maximum value in the entire array)
MAXLOC(A): ! returns a one-element 1D array whose value is
! the location of the first occurrence of the
! maximum value in A
SUM(A, D): ! returns an array of one less dimension than A
! containing the sums of the elements of A along
! dimension D (if D is omitted, returns sum of the
! elements in the entire array)
MATMUL(A, B): ! returns the matrix product of A and B
TRANSPOSE(A): ! returns the transpose of the 2D array A
Dynamic memory allocation:
a) To declare a real allocatable array A, do
REAL, DIMENSION(:, :), ALLOCATABLE :: A ! : represent two dimensions
OR
REAL, ALLOCATABLE :: A(:, :) ! : represent two dimensions
b) To allocate memory at run time
ALLOCATE ( A(N, N), STAT = AllocateStatus)
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
c) To release momory allocated dynamically
DEALLOCATE (A, STAT = DeAllocateStatus)
Internal subroutine / function. (local defined functions)
eg:
Fortran 90 is a new programming language intended for use in scientific and engineering applications. It is a language that has developed by the introduction of features that are new to Fortran, but are based on experience of other languages (like C and Matlab for instance). Fortran 90 is very different from earlier versions of Fortran, yet it is completely backwards compatible with Fortran 77.
The features of Fortran 90 are far too numerous to mention in entirety here, but some of the key features are outlined below:
a) Free format on source code.
In Fortran 90, you can use either the Fortran 77 input format or free format. If you use free format, the file extension .f90 should be used for the file name.
b) Dynamic allocation and pointers.
It is now possible to allocate storage dynamically. This enables us to finally get rid of all the "work" arrays!
c) User defined data types. (data structure)
You can now define your own composite data types, similar to struct in C or record in Pascal.
d) Modules. ( oo programming)
Modules enables you to program in an object oriented style, similar to C++. Modules can also be used to hide global variables, thereby making the Fortran 77 common construct outdated.
e) Recursive functions.
Now a part of the language.
f) Built-in array operations. (similar to IDL)
Statements like A=0 and C=A+B are now valid when A and B are arrays. There are also built-in functions for matrix operations, e.g., matmul for performing matrix multiplication.
g) Operator overloading.
You can define your own meaning of operators like + and = for your own data types (objects).
2. Compile f90
f90 main.f90 ! create an executable file called a.out.
f90 main.f90 -o main.out ! create an executable file called main.out.f90 main.f90 -L/usr/class/me390/lib -lmy_lib90 ! link library
3. Basic program structure
Key features
Free-form source code is allowed. Statements may begin in any column.
Lines may extend to 132 characters.
More than one statement may be placed on a line ( ; )
In-line comments are allowed ( ! )
Continuation ( & )
Variable names may consist of up to 31 characters (letters, digits, and _ )
The first character of a variable name must be a letter.
Declarations
a) The command IMPLICIT NONE is allowed. This feature cancels the default naming
convention.
b) The separator :: is required in a type specification statement whenever it is used to
initialize a variable or to declare a special attribute (such as PARAMETER).
REAL :: Area = 0.
INTEGER :: Num_Months = 12 !
REAL, PARAMETER :: Pi = 3.1415927 ! define a parameter
REAL Area_circle = REAL :: Area_circle ! same
c) The precision of a real, integer, complex, or logical variable may be specified using a kind type
parameter.
Eg: to declare a variable A to be a real number with at least 10 decimal places of precision with a range of at least -10^34 to 10^34, do the following:
REAL(KIND = SELECTED_REAL_KIND(10,34)) :: A ! KIND is used specify precision
If the processor you are using is unable to support a variable with this type specification, a compile-time error will result.
d) To declare a real variable to have the equivalent of Fortran 77 accuracy DOUBLE PRECISION, simply do this:
INTEGER, PARAMETER :: DP = SELECTED_REAL_KIND(14) ! Define a parameter DP
REAL(KIND = DP) :: A ! Use the parameter DP
This declares the variable A to be of type real and have at least 14 decimal places of accuracy.
Program composition
The basic form of a Fortran 90 program is as follows:
PROGRAM name
declarations
executable statements
END PROGRAM
4. Logical expressions
Symbolic forms of the relational operators are allowed:
Old Operator New Symbol
------------ ------
.LT. <
.GT. >
.EQ. ==
.LE. <=
.GE. >=
.NE. /=
IF-ELSE constructs may be named by attaching a label at the beginning of the block:
name: IF (logical argument) THEN
statements
ELSE IF (logical argument) THEN name ! name is optional
statements
.
.
ENDIF name
if ( jj> 10 ) exit ! simple version
if ( jj> 10 ) then
exit
endif
The CASE construct may be used to execute a set of multi-alternative selection criteria:
SELECT CASE (selector) ! selector may be an integer, character, or logical expression.
CASE (list #1) ! a list of one or more possible values of the selector index
statements
CASE (list #2) statements
.
.
.
CASE DEFAULT ! may be omitted
statements
END SELECT
5. Loops
a) DO loops may have either of the two forms:
DO index_variable = start, end, step statements
ENDDO ( or END DO)
or,
DO nnn index_variable = start, end, step statements
nnn CONTINUE
In both cases, the step variable is optional and is assumed to have the value 1 if omitted. As with IF-ELSE and CASE constructs, DO loops may also have names.
b) WHILE loops are allowed. They have the general form:
DO WHILE (logical argument)
statements
END DO
c) An "infinite" loop may be performed as follows:
DO
conditional statement EXIT
END DO
CYCLE : go to next iteration of the loop. EXIT : exit current loopcontinue: The continue statement is an odd statement in FORTRAN. It is an executable statement but it takes no action in the program. It's primarily used as a place holder to span gaps created between branches or loops and the rest of the program.
6. Array
1) One-dimensional Arrays
REAL, DIMENSION(10) :: A, B ! 1-based default
INTEGER, DIMENSION(0:9) :: C ! 0-based
Array initialization
A = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 /)
or,
A = (/ (I, I = 1, 10) /)
Array assignment ( must have the same physical dimension )
B = A
Array operation ( must have the same physical dimension )
A = A + B
C = 2*C
For example, if A is assigned the values
A = (/ (I, I = 1,10) /)
WHERE (A > 5)
B = 1.
ELSEWHERE
B = 0.
END WHERE !B has the values 0, 0, 0, 0, 0, 1, 1, 1, 1, 1.
DOT_PRODUCT(A, B): ! returns the dot product of A and B
MAXVAL(A): ! returns the maximum value in array A
MAXLOC(A): ! returns a one-element 1D array whose value is
! the location of the first occurrence of the
! maximum value in A
PRODUCT(A): ! returns the product of the elements of A
SUM(A): ! returns the sum of the elements of A
Dynamic Array allocation
a) To declare a real allocatable array A, do
REAL, DIMENSION(:), ALLOCATABLE :: A ! : represent one dimension
b) To allocate memory at run time
ALLOCATE ( A(N) )
ALLOCATE ( A(N), STAT = AllocateStatus) ! AllocateStatus takes the value 0 if allocation is successful
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
c) To release memory allocatedly
DEALLOCATE (A, STAT = DeAllocateStatus) ! DeAllocateStatus : 0 if the deallocation was successful.
2) Multi-dimensional arrays
Array delcaration:
Multi-dimensional arrays can be dimensioned with statements like
REAL, DIMENSION(2,3) :: A ! 1-based by default
REAL, DIMENSION(0:1,0:2) :: B ! 0-based
INTEGER, DIMENSION(10,20,3) :: I
Array initialization:
The maximum limit on the rank (the number of dimensions) of an array is 7.
For instance, the values 1, 2, 3, 4, 5, 6 may be assigned to the two-dimensional array A by
A = (/ 1, 2, 3, 4, 5, 6 /) ! assign the values to A in column order similar to the rules of Fortran 77.
Array assignment: (both arrays in question have the same physical dimension)
B = A
WHERE (logical argument)
sequence of array assignments
ELSEWHERE
sequence of array assignments
END WHERE
MAXVAL(A, D): ! returns an array of one less dimension than A
! containing the maximum values of A along
! dimension D (if D is omitted, returns the
! maximum value in the entire array)
MAXLOC(A): ! returns a one-element 1D array whose value is
! the location of the first occurrence of the
! maximum value in A
SUM(A, D): ! returns an array of one less dimension than A
! containing the sums of the elements of A along
! dimension D (if D is omitted, returns sum of the
! elements in the entire array)
MATMUL(A, B): ! returns the matrix product of A and B
TRANSPOSE(A): ! returns the transpose of the 2D array A
Dynamic memory allocation:
a) To declare a real allocatable array A, do
REAL, DIMENSION(:, :), ALLOCATABLE :: A ! : represent two dimensions
OR
REAL, ALLOCATABLE :: A(:, :) ! : represent two dimensions
b) To allocate memory at run time
ALLOCATE ( A(N, N), STAT = AllocateStatus)
IF (AllocateStatus /= 0) STOP "*** Not enough memory ***"
c) To release momory allocated dynamically
DEALLOCATE (A, STAT = DeAllocateStatus)
Internal subroutine / function. (local defined functions)
eg:
PROGRAM COLOR_GUIDE
...
CONTAINS
FUNCTION HUE(BLUE) ! An internal procedure
...
END FUNCTION HUE
END PROGRAM
Tuesday, April 8, 2014
AOSC @ UMD
http://www.atmos.umd.edu/
http://www.gradschool.umd.edu/catalog/programs/aosc.htm
http://www.testudo.umd.edu/ : academic calendar, class description and schedule of classes.
Tamara Hendershot
3409 Computer and Space Science Building
College Park
MD 20742
Telephone: (301) 405-5389
Fax: (301)-314-9482
tammy@atmos.umd.edu
Masters of Professional Studies (M.P.A.O.)
Master of Professional Studies (MPAO) The Master of Professional Studies in Atmospheric and Oceanic Science is designed for meteorologists, oceanographers and environmental scientists who need cutting-edge skills and knowledge in atmospheric and oceanic science, in the computational methods used in our field, and in air quality science. The Director of Professional Studies will advise students in planning his or her course of study, and will provide career advice and The degree is earned by successful completion of ten 3-credit courses. Students must complete two out of the following three Certificate programs, each of which consists of four courses, plus two courses from the remaining Certificate Program.
Certificate #1, in Computational Methods in Atmospheric and Oceanic Science,
develops computer skills needed to understand weather and climate analysis and prediction technologies.
It is earned by successful completion of
AOSC630 : Statistical Methods in Meteorology and Oceanography
AOSC650 : unknown
AOSC684 : Climate System Modeling
AOSC614 : Atmospheric Modeling, Data Assimilation and Predictability
or
AOSC615 : Advanced data assimilation for the Earth Sciences (new)
Certificate #2, in General Atmospheric and Oceanic Science,
provides a broad phenomenological understanding of weather and climate, and the dynamical, thermodynamical
and radiative processes that drive them.
It is earned by successful completion of
AOSC431 : Atmospheric Thermodynamics
AOSC617 : Atmospheric and Oceanic Climate
AOSC632 : unknow
AOSC670 : Physical Oceanography
Finally, Certificate #3, in Air Quality Science and Technology
teaches the physical and chemical principles
that govern air quality and allow for analysis and prediction of extreme weather.
It is earned by successful completion of
AOSC424 : Remote Sensing of the Atmosphere and Ocean
AOSC600 : Synoptic Meteorology I
AOSC637 : Atmospheric chemistry
AOSC624 : Remote Sensing of Surface Climate
or
AOSC625 : Remote sensing of the atmosphere
The MPAO program is designed with the needs of working professionals in mind,
and can be completed on a part-time basis over no more than 5 years,
or on a full-time basis in 1 year and one semester.
class schedule
Graduate Faculty
Chair
Carton, James A.
Director
Busalacchi, Antonio J.
Distinguished University Professor
Kalnay, Eugenia E
Professor
Busalacchi, Antonio J.
Dickerson, Russell R.
Hudson, Robert D.
Li, Zhanqing
Liang, Xin-Zhong
Murtugudde, Raghuram
Nigam, Sumant
Pinker, Rachel
Salawitch, Ross J.
Zhang, Da-Lin
Professor Emeritus
Baer, Ferdinand
Vernekar, Anandu D.
Associate Professor
Zeng, Ning
http://www.gradschool.umd.edu/catalog/programs/aosc.htm
http://www.testudo.umd.edu/ : academic calendar, class description and schedule of classes.
Tamara Hendershot
3409 Computer and Space Science Building
College Park
MD 20742
Telephone: (301) 405-5389
Fax: (301)-314-9482
tammy@atmos.umd.edu
Masters of Professional Studies (M.P.A.O.)
Master of Professional Studies (MPAO) The Master of Professional Studies in Atmospheric and Oceanic Science is designed for meteorologists, oceanographers and environmental scientists who need cutting-edge skills and knowledge in atmospheric and oceanic science, in the computational methods used in our field, and in air quality science. The Director of Professional Studies will advise students in planning his or her course of study, and will provide career advice and The degree is earned by successful completion of ten 3-credit courses. Students must complete two out of the following three Certificate programs, each of which consists of four courses, plus two courses from the remaining Certificate Program.
Certificate #1, in Computational Methods in Atmospheric and Oceanic Science,
develops computer skills needed to understand weather and climate analysis and prediction technologies.
It is earned by successful completion of
AOSC630 : Statistical Methods in Meteorology and Oceanography
AOSC650 : unknown
AOSC684 : Climate System Modeling
AOSC614 : Atmospheric Modeling, Data Assimilation and Predictability
or
AOSC615 : Advanced data assimilation for the Earth Sciences (new)
Certificate #2, in General Atmospheric and Oceanic Science,
provides a broad phenomenological understanding of weather and climate, and the dynamical, thermodynamical
and radiative processes that drive them.
It is earned by successful completion of
AOSC431 : Atmospheric Thermodynamics
AOSC617 : Atmospheric and Oceanic Climate
AOSC632 : unknow
AOSC670 : Physical Oceanography
Finally, Certificate #3, in Air Quality Science and Technology
teaches the physical and chemical principles
that govern air quality and allow for analysis and prediction of extreme weather.
It is earned by successful completion of
AOSC424 : Remote Sensing of the Atmosphere and Ocean
AOSC600 : Synoptic Meteorology I
AOSC637 : Atmospheric chemistry
AOSC624 : Remote Sensing of Surface Climate
or
AOSC625 : Remote sensing of the atmosphere
The MPAO program is designed with the needs of working professionals in mind,
and can be completed on a part-time basis over no more than 5 years,
or on a full-time basis in 1 year and one semester.
class schedule
Graduate Faculty
Chair
Carton, James A.
Director
Busalacchi, Antonio J.
Distinguished University Professor
Kalnay, Eugenia E
Professor
Busalacchi, Antonio J.
Dickerson, Russell R.
Hudson, Robert D.
Li, Zhanqing
Liang, Xin-Zhong
Murtugudde, Raghuram
Nigam, Sumant
Pinker, Rachel
Salawitch, Ross J.
Zhang, Da-Lin
Professor Emeritus
Baer, Ferdinand
Vernekar, Anandu D.
Associate Professor
Zeng, Ning
Monday, April 7, 2014
words
account : a report or description of an event or experience. Consider or regard in a specified way.
ad hoc : formed, arranged, or done for a particular purpose only.
adiabatic : without change in heat
adjective : /a'djective/ a word or phrase naming an attribute, added to or grammatically
related to a noun to modify or describe it.
advection : 平流 the transfer of heat or matter by the flow of a fluid, especially horizontally
in the atmosphere or the sea.
affiliate : associate, partner, colleague, a person or organization officially attached to
a larger body.
analogy : 打个比方a comparison between two things, typically on the basis of their
structure and for the purpose of explanation or clarification.
annotate : gloss, add footnotes to, interpret, explain
archy : 君主国
as-semble : 组合(of people) gather together in one place
for a common purpose.
assimilate : incorporate, take in, absorb
attire : clothes, especially fine or formal ones. be dressed in clothes of a
specified kind.
axes : plural of axis
axis : line around which shape is symmetrical
axle : shaft on which wheel turns
ax : tool for cutting, job loss, termination
baric : 气压
bear : (of a person) carry. 承担
bearer : 负担者 a person or thing that carries or holds something.
Belgium : 比利时bias : prejudice, partiality, unfairness, favoritism
bolt : short screw, bar for fastening door
by a long shot : by a wide margin, indicates a big difference / disparity
caulk : 填缝 seal (a gap or seam) with a waterproof filler and sealant.
coil : loop, curl, spiral, twirl, helix, whirl
collaboration : teamwork, partnership, group effort, alliance
collocate : place side by side
compare to : is to suggest resemblances between things having essentially
DIFFERENT natures
compare with : is to suggest resemblances between things having essentially
SIMILAR natures
conjugate : coupled, connected, or related, in particular.
continent : land mass, land above sea level, able to control urination and bowels
(intestine, the deepest or innermost part of something)
consensus : general agreement
contagious : 传染性 (of a disease) spread from one person or organism to another
by direct or indirect contact.
correlate : associate, compare, show a relationship, link
côté d'ivoire : /'ka:t^di'va:/科特迪瓦
denote : 记be a sign of; indicate.
determinant : a factor that decisively affects the nature of outcome of something
diagnose : identify cause of something, identify illness in patient
diagnosis : analysis, judgement, finding, verdict
difference : dissimilarity, disparity, distinction, divergence
diffusion : the spreading of something more widely.
disassemble : 拆卸 take (something) apart.
discretize : 近似化 represent or approximate (a quantity or series) using
a discrete quantity or quantities.
dissemination : the act of spreading something, especially
information, widely; circulation.
dissertation : 论文 a long essay on a particular subject, esp. one written as a requirement
for the Doctor of Philosophy degree.
electrical : operating by or producing electricity. 电动
electronic : (of a device) having or operating with the aid of many small components, esp.
microchips and transistors, that control and direct an electric current. 电子
en-semble : 合奏 group, collection, together
epidemic : 疫情 a widespread occurrence of an infectious disease in a community at
a particular time.
essay : 作文 a short piece of writing on a particular subject.
et al. : abbr. Latin et alii (and others)
evolution : 进化 the gradual development of something, esp. from a simple to a more
complex form.
exert : put forth, use, apply
extrude : push substance out through small hole
facilitate : make easy, ease, help, aid, assist 方便
flange : 轮缘 a projecting flat rim, collar, or rib on an object,
serving to strengthen or attach or (on a wheel) to maintain
position on a rail.
foe: enemy or opponent
framework : an essential supporting structure of a building,
vehicle, or object.
fringe: edge, periphery, brink, rim, side, margin.
gasket : 垫片 a shaped piece or ring of rubber or other material sealing the junction
between two surfaces in an engine or other device.
genre : 流派 a category of artistic composition, as in music
or literature, characterized by similarities in form,
style, or subject matter.
geography : topography, natural features, characteristics, layout
grace period : 宽限期 is a time past the deadline for an obligation during which
a late penalty that would have been imposed is waived.
graph : chart, diagram, grid, table
graphic : explicit, lifelike, realistic, vivid
graupel : small soft white ice particles that fall as hail or snow
guts : fortitude, resilience, backbone, courage
harness : tie together, strap up, bind, attach, connect
havoc: lay waste to, devastate, widespread destruction.
heterogeneous : varied, mixed, assorted, diverse
hire : 聘请
hirarchy : 等级制度 a system or organization in which people or groups are
ranked one above the other according to status or authority.
homogeneous : uniform, all the same, harmonized, consistent
hub : center, core, heart, focal point, focus, nucleus ( important element )
hydrometeor : any water or ice particles that have formed in atmosphere or at the Earth's
surface as a result of condensation or sublimation.
hydrometeor : water in atmosphere
hydro : water 流体
hydrodynamics: 流体力学
hydrostatics : 流体静力学
hygrometer : an instrument to measure humidity
hydrometeor : 水凝 an atmospheric phenomenon or entity involving water or water
vapor, such as rain or a cloud.
hyper : behaving in an excited and nervous way
hy'pothesis: suppose, guess, assumption
infectious : 传染病 (of a disease or disease-causing organism) likely to be
transmitted to people, organisms, etc., through the environment.
inflict: cause to be suffered by someone or something
influenza : 流感 a highly contagious viral infection of the respiratory passages
causing fever, severe aching, and catarrh, and often
occurring in epidemics.
infrastructure : the basic physical and organizational structures
and facilities (e.g., buildings, roads, and power supplies)
needed for the operation of a society or enterprise.
innovation : 1.something new or different introduced: numerous innovations in the
high-school curriculum. 2.the act of innovating; introduction of new
things or methods.
instant : a precise moment of time.(noun)
intrude : break in, infringe (break a law, rule, or agreement)
isle : island
iso : 异
isobaric : 等压 equal or constant pressure, with respect to either space or time.
isotherm : 等温线 equal temperature
isotropic : 各向同性
justifiable : 正当 able to be shown to be right or reasonable; defensible.
lapse : an accidental or temporary decline or deviation from an expected or accepted
condition or state; a temporary falling or slipping from a previous standard:
a lapse of justice.
latent : dormant, hidden, inactive, sleeping
lateral : side, on the side, cross, sideway
levy : tax, charge, impose, exact, cause
lodge : cabin, hotel, stay, accomodate
manifesto : 宣言 a public declaration of policy and aims, especially one issued
before an election by a political party or candidate.
mason : a builder and worker in stone.
masonry : stonework.
module : element, component, part, unit
mortar : 1. used as a bond in masonry or for covering a wall. 2. a cup-shaped receptacle
made of hard material, in which ingredients are crushed or ground, used
especially in cooking or pharmacy. 3. a short, smoothbore gun for firing
shells (technically called bombs) at high angles
normalize : multiply (a series, function, or item of data) by a factor that makes the
norm or some associated quantity such as an integral equal to a desired
value (usually 1).
notate : 符号表示 write (something, typically music) in notation.
oakum : 麻絮 loose fiber obtained by untwisting old rope, used especially in
caulking wooden ships.
occlude : stop, close up, or obstruct (an opening, orifice, or passage).堵塞
optimal : best, most favorable, best possible
orography : the branch of physical geography dealing with mountains.
the study or mapping of relief, esp of mountains
orthogonal : pertaining to or involving right angles or perpendiculars: an orthogonal
projection. (of a linear transformation) defined so that the length of
a vector/point under the transformation equals the length of the original
vector. (dxu: a point moving from a place to another place with distance
to origin unchanged.)
outreach : help and advice provided without people asking
overlay : palce on top, overlie, spared over the surface
pane : 窗格 a single sheet of glass in a window or door.
panel : 面板 a flat or curved component, typically rectangular, that forms or is set into
the surface of a door, wall, or ceiling.
per'diem : for each day. Used after an amount of money to mean "for each day"
perplex : bewilder, confuse, puzzle, baffle, confound, mystify
perturbation : to disturb or disquiet greatly in mind; agitate. to throw into great
disorder; derange.
pin : hold, fasten, attach, badge, brooch
polarization : cause division of opinion, restrict vibration of light, cause light to
vibrate within a particular plane
procure : obtain, acquire, secure, buy, gain
procurement : the action of obtaining or procuring something
prone to : likely to, given to, inclined to, tend to
propagate : breed specimens of (a plant, animal, etc.) by natural processes from the
parent stock spread and promote (an idea, theory, etc.) widely.
psychrometer : an instrument consisting of two thermomenters
purge : wash out, cleanse, flush out
qualitative : relating to, measuring, or measured by the quality of something rather
than its quantity.
quantitative : relating to, measuring, or measured by the quantity of something rather
than its quality.
radio : the use of electromagnetic waves to transmit and receive information
recap : (noun)a summary of what has been said; a recapitulation.
(verb) state again as a summary; recapitulate.
regression : weakening, failure, decay, falling off
revolution : complete circular turn, overthrow of government, major change
RH : relative humidity
rim : 轮圈 the upper or outer edge of an object, typically something circular or
approximately circular.
RPM : revolutions per minute
savvy : know-how, confidence, knowledge
scale : level, weighing machine, size, range, extent, dimension
scrum : ( restart a play ) an ordered formation of players, used to
restart play, in which the forwards of a team form up with
arms interlocked and heads down, and push forward against
a similar group from the opposing side.
seminar : class, tutorial, discussion group, round table
simulate : replicate, reproduce, copy, imitate, mimic
skirmish : 前哨战 an episode of irregular or unpremeditated fighting, especially
between small or outlying parts of armies or fleets.
sling : throw away
snap : break, crack, sudden
socket : shaped hole for connection, outlet
solute : 溶质 the minor component in a solution, dissolved in the solvent.
solvent weld : 溶剂 the liquid in which a solute is dissolved to form a solution.
spectroscopy : study of the interaction between matter and radiated energy. the
science and practice of using spectrometers and spectroscopes and of
analysing spectra, the methods employed depending on the radiation
being examined.
stochastic : /sto'kastic/ 随机 randomly determined; having a random probability
distribution or pattern that may be analyzed statistically but may not be
predicted precisely.
swath : the width cut by a single passage of a scythe or mowing machinestratify :
form into layers, form into status groups
streamline : 简化, design or provide with a form that presents very little
resistance to a flow of air or water, increasing speed and
ease of movement.(of fluid flow) free from turbulence. to make
(something) simpler, more effective, or more productive
(from complicate to SIMPLER)
submerge: cause to be under water
suppress : overpower, conquer, overturn, dominate
surrogate : a substitute, esp. a person deputizing for another in a specific role or office.
synopsis : a brief summary or general survey of something.
synoptic : the analysis and prediction of large-scale weather systems, such as
extratropical cyclones and their associated fronts and jet streams.
spasm : 痉挛 a sudden involuntary muscular contraction or
convulsive movement.
tale : a story or report that is untrue
tailgate : drive too closely behind another vehicle
temporal : relating to time, brief
thermal : 热
topography : scenery, landscape, geography, countryside
transform : change, alter
transpose : to change the relative position, order, sequence of ,
(of a matrix) to interchange rows and columns
trajectory : the path followed by a projectile flying or an object moving under the
action of given forces.
turbulent : characterized by conflict, disorder, or confusion; not controlled or calm.
underlie/underlying : The obvious meaning of underlying refers to something beneath
something else. But the word carries a more subtle meaning,
that of something hidden but important, something that shapes
the meaning or effect of something else, without being explicit
itself.
usher : 招待员 a person who shows people to their seats,
especially in a theater or at a wedding.
variational : the act, process, or accident of varying in condition, character, or degree.
vorticity : a measure of the circulation of a fluid: a quantity equal to twice the angular
momentum of a particle of the fluid around which there is circulation.
voyage : long journey involving travel by sea or in space
weld : join together (metal pieces or parts) by heating the surfaces to the point of
melting using a blowtorch, electric arc, or other means, and uniting them by
pressing, hammering, etc..
Cardiology 心脏病
Chiropractic Medicine 整脊医学
Dermatology 皮肤科
Ear, Nose and Throat (ENT) 耳,鼻,喉
Family Practice 家庭实践
Gastroenterology 胃肠病
General Practice 一般的做法
Internal Medicine 内科
Obstetrics/Gynecology 产科/妇科
Orthopedics 骨科
Pediatrics 儿科
Podiatry 足部
Surgery 手术
ad hoc : formed, arranged, or done for a particular purpose only.
adiabatic : without change in heat
adjective : /a'djective/ a word or phrase naming an attribute, added to or grammatically
related to a noun to modify or describe it.
advection : 平流 the transfer of heat or matter by the flow of a fluid, especially horizontally
in the atmosphere or the sea.
affiliate : associate, partner, colleague, a person or organization officially attached to
a larger body.
analogy : 打个比方a comparison between two things, typically on the basis of their
structure and for the purpose of explanation or clarification.
annotate : gloss, add footnotes to, interpret, explain
archy : 君主国
as-semble : 组合(of people) gather together in one place
for a common purpose.
assimilate : incorporate, take in, absorb
attire : clothes, especially fine or formal ones. be dressed in clothes of a
specified kind.
axes : plural of axis
axis : line around which shape is symmetrical
axle : shaft on which wheel turns
ax : tool for cutting, job loss, termination
baric : 气压
bear : (of a person) carry. 承担
bearer : 负担者 a person or thing that carries or holds something.
Belgium : 比利时bias : prejudice, partiality, unfairness, favoritism
bolt : short screw, bar for fastening door
by a long shot : by a wide margin, indicates a big difference / disparity
caulk : 填缝 seal (a gap or seam) with a waterproof filler and sealant.
coil : loop, curl, spiral, twirl, helix, whirl
collaboration : teamwork, partnership, group effort, alliance
collocate : place side by side
compare to : is to suggest resemblances between things having essentially
DIFFERENT natures
compare with : is to suggest resemblances between things having essentially
SIMILAR natures
conjugate : coupled, connected, or related, in particular.
continent : land mass, land above sea level, able to control urination and bowels
(intestine, the deepest or innermost part of something)
consensus : general agreement
contagious : 传染性 (of a disease) spread from one person or organism to another
by direct or indirect contact.
correlate : associate, compare, show a relationship, link
côté d'ivoire : /'ka:t^di'va:/科特迪瓦
denote : 记be a sign of; indicate.
determinant : a factor that decisively affects the nature of outcome of something
diagnose : identify cause of something, identify illness in patient
diagnosis : analysis, judgement, finding, verdict
difference : dissimilarity, disparity, distinction, divergence
diffusion : the spreading of something more widely.
disassemble : 拆卸 take (something) apart.
discretize : 近似化 represent or approximate (a quantity or series) using
a discrete quantity or quantities.
dissemination : the act of spreading something, especially
information, widely; circulation.
dissertation : 论文 a long essay on a particular subject, esp. one written as a requirement
for the Doctor of Philosophy degree.
electrical : operating by or producing electricity. 电动
electronic : (of a device) having or operating with the aid of many small components, esp.
microchips and transistors, that control and direct an electric current. 电子
en-semble : 合奏 group, collection, together
epidemic : 疫情 a widespread occurrence of an infectious disease in a community at
a particular time.
essay : 作文 a short piece of writing on a particular subject.
et al. : abbr. Latin et alii (and others)
evolution : 进化 the gradual development of something, esp. from a simple to a more
complex form.
exert : put forth, use, apply
extrude : push substance out through small hole
facilitate : make easy, ease, help, aid, assist 方便
flange : 轮缘 a projecting flat rim, collar, or rib on an object,
serving to strengthen or attach or (on a wheel) to maintain
position on a rail.
foe: enemy or opponent
framework : an essential supporting structure of a building,
vehicle, or object.
fringe: edge, periphery, brink, rim, side, margin.
gasket : 垫片 a shaped piece or ring of rubber or other material sealing the junction
between two surfaces in an engine or other device.
genre : 流派 a category of artistic composition, as in music
or literature, characterized by similarities in form,
style, or subject matter.
geography : topography, natural features, characteristics, layout
grace period : 宽限期 is a time past the deadline for an obligation during which
a late penalty that would have been imposed is waived.
graph : chart, diagram, grid, table
graphic : explicit, lifelike, realistic, vivid
graupel : small soft white ice particles that fall as hail or snow
guts : fortitude, resilience, backbone, courage
harness : tie together, strap up, bind, attach, connect
havoc: lay waste to, devastate, widespread destruction.
heterogeneous : varied, mixed, assorted, diverse
hire : 聘请
hirarchy : 等级制度 a system or organization in which people or groups are
ranked one above the other according to status or authority.
homogeneous : uniform, all the same, harmonized, consistent
hub : center, core, heart, focal point, focus, nucleus ( important element )
hydrometeor : any water or ice particles that have formed in atmosphere or at the Earth's
surface as a result of condensation or sublimation.
hydrometeor : water in atmosphere
hydro : water 流体
hydrodynamics: 流体力学
hydrostatics : 流体静力学
hygrometer : an instrument to measure humidity
hydrometeor : 水凝 an atmospheric phenomenon or entity involving water or water
vapor, such as rain or a cloud.
hyper : behaving in an excited and nervous way
hy'pothesis: suppose, guess, assumption
infectious : 传染病 (of a disease or disease-causing organism) likely to be
transmitted to people, organisms, etc., through the environment.
inflict: cause to be suffered by someone or something
influenza : 流感 a highly contagious viral infection of the respiratory passages
causing fever, severe aching, and catarrh, and often
occurring in epidemics.
infrastructure : the basic physical and organizational structures
and facilities (e.g., buildings, roads, and power supplies)
needed for the operation of a society or enterprise.
innovation : 1.something new or different introduced: numerous innovations in the
high-school curriculum. 2.the act of innovating; introduction of new
things or methods.
instant : a precise moment of time.(noun)
intrude : break in, infringe (break a law, rule, or agreement)
isle : island
iso : 异
isobaric : 等压 equal or constant pressure, with respect to either space or time.
isotherm : 等温线 equal temperature
isotropic : 各向同性
justifiable : 正当 able to be shown to be right or reasonable; defensible.
lapse : an accidental or temporary decline or deviation from an expected or accepted
condition or state; a temporary falling or slipping from a previous standard:
a lapse of justice.
latent : dormant, hidden, inactive, sleeping
lateral : side, on the side, cross, sideway
levy : tax, charge, impose, exact, cause
lodge : cabin, hotel, stay, accomodate
manifesto : 宣言 a public declaration of policy and aims, especially one issued
before an election by a political party or candidate.
mason : a builder and worker in stone.
masonry : stonework.
module : element, component, part, unit
mortar : 1. used as a bond in masonry or for covering a wall. 2. a cup-shaped receptacle
made of hard material, in which ingredients are crushed or ground, used
especially in cooking or pharmacy. 3. a short, smoothbore gun for firing
shells (technically called bombs) at high angles
normalize : multiply (a series, function, or item of data) by a factor that makes the
norm or some associated quantity such as an integral equal to a desired
value (usually 1).
notate : 符号表示 write (something, typically music) in notation.
oakum : 麻絮 loose fiber obtained by untwisting old rope, used especially in
caulking wooden ships.
occlude : stop, close up, or obstruct (an opening, orifice, or passage).堵塞
optimal : best, most favorable, best possible
orography : the branch of physical geography dealing with mountains.
the study or mapping of relief, esp of mountains
orthogonal : pertaining to or involving right angles or perpendiculars: an orthogonal
projection. (of a linear transformation) defined so that the length of
a vector/point under the transformation equals the length of the original
vector. (dxu: a point moving from a place to another place with distance
to origin unchanged.)
outreach : help and advice provided without people asking
overlay : palce on top, overlie, spared over the surface
pane : 窗格 a single sheet of glass in a window or door.
panel : 面板 a flat or curved component, typically rectangular, that forms or is set into
the surface of a door, wall, or ceiling.
per'diem : for each day. Used after an amount of money to mean "for each day"
perplex : bewilder, confuse, puzzle, baffle, confound, mystify
perturbation : to disturb or disquiet greatly in mind; agitate. to throw into great
disorder; derange.
pin : hold, fasten, attach, badge, brooch
polarization : cause division of opinion, restrict vibration of light, cause light to
vibrate within a particular plane
procure : obtain, acquire, secure, buy, gain
procurement : the action of obtaining or procuring something
prone to : likely to, given to, inclined to, tend to
propagate : breed specimens of (a plant, animal, etc.) by natural processes from the
parent stock spread and promote (an idea, theory, etc.) widely.
psychrometer : an instrument consisting of two thermomenters
purge : wash out, cleanse, flush out
qualitative : relating to, measuring, or measured by the quality of something rather
than its quantity.
quantitative : relating to, measuring, or measured by the quantity of something rather
than its quality.
radio : the use of electromagnetic waves to transmit and receive information
recap : (noun)a summary of what has been said; a recapitulation.
(verb) state again as a summary; recapitulate.
regression : weakening, failure, decay, falling off
revolution : complete circular turn, overthrow of government, major change
RH : relative humidity
rim : 轮圈 the upper or outer edge of an object, typically something circular or
approximately circular.
RPM : revolutions per minute
savvy : know-how, confidence, knowledge
scale : level, weighing machine, size, range, extent, dimension
scrum : ( restart a play ) an ordered formation of players, used to
restart play, in which the forwards of a team form up with
arms interlocked and heads down, and push forward against
a similar group from the opposing side.
seminar : class, tutorial, discussion group, round table
simulate : replicate, reproduce, copy, imitate, mimic
skirmish : 前哨战 an episode of irregular or unpremeditated fighting, especially
between small or outlying parts of armies or fleets.
sling : throw away
snap : break, crack, sudden
socket : shaped hole for connection, outlet
solute : 溶质 the minor component in a solution, dissolved in the solvent.
solvent weld : 溶剂 the liquid in which a solute is dissolved to form a solution.
spectroscopy : study of the interaction between matter and radiated energy. the
science and practice of using spectrometers and spectroscopes and of
analysing spectra, the methods employed depending on the radiation
being examined.
stochastic : /sto'kastic/ 随机 randomly determined; having a random probability
distribution or pattern that may be analyzed statistically but may not be
predicted precisely.
swath : the width cut by a single passage of a scythe or mowing machinestratify :
form into layers, form into status groups
streamline : 简化, design or provide with a form that presents very little
resistance to a flow of air or water, increasing speed and
ease of movement.(of fluid flow) free from turbulence. to make
(something) simpler, more effective, or more productive
(from complicate to SIMPLER)
submerge: cause to be under water
suppress : overpower, conquer, overturn, dominate
surrogate : a substitute, esp. a person deputizing for another in a specific role or office.
synopsis : a brief summary or general survey of something.
synoptic : the analysis and prediction of large-scale weather systems, such as
extratropical cyclones and their associated fronts and jet streams.
spasm : 痉挛 a sudden involuntary muscular contraction or
convulsive movement.
tale : a story or report that is untrue
tailgate : drive too closely behind another vehicle
temporal : relating to time, brief
thermal : 热
topography : scenery, landscape, geography, countryside
transform : change, alter
transpose : to change the relative position, order, sequence of ,
(of a matrix) to interchange rows and columns
trajectory : the path followed by a projectile flying or an object moving under the
action of given forces.
turbulent : characterized by conflict, disorder, or confusion; not controlled or calm.
underlie/underlying : The obvious meaning of underlying refers to something beneath
something else. But the word carries a more subtle meaning,
that of something hidden but important, something that shapes
the meaning or effect of something else, without being explicit
itself.
usher : 招待员 a person who shows people to their seats,
especially in a theater or at a wedding.
variational : the act, process, or accident of varying in condition, character, or degree.
a different form of something; variant.
verbose: in details vorticity : a measure of the circulation of a fluid: a quantity equal to twice the angular
momentum of a particle of the fluid around which there is circulation.
voyage : long journey involving travel by sea or in space
weld : join together (metal pieces or parts) by heating the surfaces to the point of
melting using a blowtorch, electric arc, or other means, and uniting them by
pressing, hammering, etc..
Cardiology 心脏病
Chiropractic Medicine 整脊医学
Dermatology 皮肤科
Ear, Nose and Throat (ENT) 耳,鼻,喉
Family Practice 家庭实践
Gastroenterology 胃肠病
General Practice 一般的做法
Internal Medicine 内科
Obstetrics/Gynecology 产科/妇科
Orthopedics 骨科
Pediatrics 儿科
Podiatry 足部
Surgery 手术
Wednesday, April 2, 2014
Relative humidiy ( humidity)
Relative humidity
The ratio = the vapor pressure / the saturation vapor
pressure
The ratio = the mixing ratio / the saturation mixing ratio.
These two definitions yield almost identical numerical
values.
Relative humidity is usually expressed in percent and can be
computed from psychrometric data.Unless specified otherwise, relative humidity
is reported with respect to waterrather than ice because most hygrometers are
sensitive to relative humidity with respect to water even at subfreezing
temperatures, and because the air can easily become supersaturated with respect
to ice, which would require three digits in coded messages for relative
humidity with respect to ice.
mixing
ratio
The ratio of the mass of a variable
atmospheric constituent to the mass of dry air.
If not otherwise indicated, the term
normally refers to water vapor. For many
purposes, the mixing ratio may be approximated by the specific humidity.
Either r or w is commonly used to symbolize
water vapor mixing ratio, with r used
for thermodynamic terms in this glossary. In terms of the pressure p and vapor pressure e, the mixing ratio r
is
saturation
mixing ratio
the value of the mixing ratio of saturated air at the given temperature and pressure.
specific
humidity
In a system of moist air, the ratio of the mass of water vapor to the total mass of the system.
The specific humidity q is
related to the mixing ratio rv by
dewpoint
(Or dewpoint temperature.)
The
temperature to which a given air parcel must be cooled at constant pressure and constant water vapor content in
order for saturation to occur.
When this temperature is below 0°C,
it is sometimes called the frost point.
The dewpoint may alternatively be defined as the
temperature at which the saturation vapor
pressure of the parcel is equal to the actual vapor pressure of the contained water vapor.
Isobaric heating or cooling of an
air parcel does not alter the value of that parcel's dewpoint, as long as no
vapor is added or removed.
Therefore, the dewpoint is a conservative property
of air with respect to such processes.
However, the dewpoint is
nonconservative with respect to vertical adiabatic motions of air in the atmosphere.
The dewpoint of ascending moist air decreases at a rate only about
one-fifth as great as the dry-adiabatic lapse
rate.
The Dry Bulb, Wet Bulb and Dew Point temperatures are important to determine the state of humid air. The knowledge of only two of these values is enough to determine the state - including the content of water vapor and the sensible and latent energy (enthalpy).
Dry Bulb Temperature - Tdb
The Dry Bulb temperature, usually referred to as air temperature, is the air property that is most common used. When people refer to the temperature of the air, they are normally referring to its dry bulb temperature.The Dry Bulb Temperature refers basically to the ambient air temperature. It is called "Dry Bulb" because the air temperature is indicated by a thermometer not affected by the moisture of the air.
Dry-bulb temperature - Tdb, can be measured using a normal thermometer freely exposed to the air but shielded from radiation and moisture. The temperature is usually given in degrees Celsius (oC) or degrees Fahrenheit (oF). The SI unit is Kelvin (K). Zero Kelvin equals to -273oC.
The dry-bulb temperature is an indicator of heat content and is shown along the bottom axis of the psychrometric chart. Constant dry bulb temperatures appear as vertical lines in the psychrometric chart.
Wet Bulb Temperature - Twb
The Wet Bulb temperature is the temperature of adiabatic saturation. This is the temperature indicated by a moistened thermometer bulb exposed to the air flow.Wet Bulb temperature can be measured by using a thermometer with the bulb wrapped in wet muslin. The adiabatic evaporation of water from the thermometer and the cooling effect is indicated by a "wet bulb temperature" lower than the "dry bulb temperature" in the air.
The rate of evaporation from the wet bandage on the bulb, and the temperature difference between the dry bulb and wet bulb, depends on the humidity of the air. The evaporation is reduced when the air contains more water vapor.
The wet bulb temperature is always lower than the dry bulb temperature but will be identical with 100% relative humidity (the air is at the saturation line).
Combining the dry bulb and wet bulb temperature in a psychrometric diagram or Mollier chart, gives the state of the humid air. Lines of constant wet bulb temperatures run diagonally from the upper left to the lower right in the Psychrometric Chart.
Dew Point Temperature - Tdp
The Dew Point is the temperature at which water vapor starts to condense out of the air (the temperature at which air becomes completely saturated). Above this temperature(dew point temp) the moisture will stay in the air.- if the dew-point temperature is close to the dry air temperature - the relative humidity is high
- if the dew point is well below the dry air temperature - the relative humidity is low
The Dew Point temperature can be measured by filling a metal can with water and some ice cubes. Stir by a thermometer and watch the outside of the can. When the vapor in the air starts to condensate on the outside of the can, the temperature on the thermometer is pretty close to the dew point of the actual air.
The Dew Point is given by the saturation line in the psychrometric chart.
Dew Point Temperature Charts
Dew point temperatures from dry and wet bulb temperatures are indicated in the charts below.Dew Point Temperature Charts
Dew Point Temperature Chart in degrees Celcius
Dew Point Temperature Chart in degrees Fahrenheit
Subscribe to:
Posts (Atom)