source: CPL/oasis3/trunk/src/mod/oasis3/src/skip.f90 @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 1.3 KB
Line 
1SUBROUTINE skip (cd_one, id_len)
2!
3!**** SKIP
4!
5!     Purpose:
6!       Skip line if it is a comment
7!
8!     Interface:
9!       Call skip (cl_one)
10!
11!     Method:
12!       Read the first caracter of the line and skip line if
13!       it is a comment
14!
15!     External:
16!       none
17!
18!     Files:
19!       none
20!   
21!     References:
22!
23!     History:
24!     --------
25!       Version   Programmer     Date        Description
26!       ------------------------------------------------
27!       2.5       A.Caubel       2002/04/04  created
28!
29!*-----------------------------------------------------------------------
30!
31!** + DECLARATIONS
32!
33!
34!** ++ Include files
35!
36  USE mod_kinds_oasis
37  USE mod_unit
38!
39!** ++ Local declarations
40!
41  INTEGER (kind=ip_intwp_p) :: ib,id_len
42  CHARACTER(len=80) :: cl_line
43  CHARACTER(len=1), DIMENSION(id_len) :: cd_one
44  CHARACTER(len=1) :: cl_two
45!
46!*-----------------------------------------------------------------------
47!
48  cl_two='#'
49100 IF (cd_one(1) .NE. cl_two) GO TO 120
50  READ (UNIT = nulin, FMT = 1001) cl_line
51  DO ib = 1,id_len
52    cd_one(ib) = cl_line(ib:ib)
53  END DO
54  GO TO 100
55120 CONTINUE
561001 FORMAT(A80)
57!
58!*-----------------------------------------------------------------------
59!
60END SUBROUTINE skip
61!
62!*========================================================================
Note: See TracBrowser for help on using the repository browser.