New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
m_count.f90 in vendors/XMLF90/current/doc/Examples/sax/count – NEMO

source: vendors/XMLF90/current/doc/Examples/sax/count/m_count.f90 @ 1960

Last change on this file since 1960 was 1960, checked in by flavoni, 14 years ago

importing XMLF90 r_53 vendor

File size: 2.0 KB
Line 
1MODULE m_count
2!
3! Contributed by Jon Wakelin
4!
5
6  USE flib_sax
7
8  IMPLICIT NONE
9
10  private
11  PUBLIC :: begin_element_handler, end_element_handler, pcdata_chunk_handler
12
13  TYPE, public :: hash
14     CHARACTER(len=50) :: elm
15     INTEGER           :: num
16  END TYPE hash
17
18  TYPE(hash), DIMENSION(50), public  :: element_hash
19  INTEGER, public, save              ::  nhash = 0
20
21  INTEGER, private, save             :: n = 0 
22
23!--------------------------------------------------------
24CONTAINS
25
26  SUBROUTINE begin_element_handler(name,attributes)
27    character(len=*), intent(in)   :: name
28    TYPE(dictionary_t), INTENT(in) :: attributes
29
30    LOGICAL :: match 
31    INTEGER :: pmatch
32    INTEGER :: i
33
34    match = .false.
35
36!!! First time through loop element must be unique...
37    IF (n == 0) THEN
38       element_hash(n+1)%elm = name
39       element_hash(n+1)%num = 1
40       nhash=nhash+1
41    ELSE
42
43!!! ...thereafter we will have to check if it is unique
44       DO i=1,nhash
45          IF (name == element_hash(i)%elm) THEN
46             match = .true. ! set .true. if element already exists
47             pmatch = i     ! and record the position at which the match occured
48                            ! NB there can only ever be 1 or 0 matches
49          ENDIF
50       ENDDO
51
52!!! If element already exists increment the counter for THIS element
53       IF (match) THEN
54          element_hash(pmatch)%num = element_hash(pmatch)%num + 1
55       ELSE
56!!! Otherwise make a new entry in the hash
57          element_hash(n+1)%elm = name
58          element_hash(n+1)%num = 1
59          nhash=nhash+1
60       ENDIF
61    ENDIF
62    n=nhash
63
64  END SUBROUTINE begin_element_handler
65
66
67!--------------------------------------------------------------------------
68! End tag handler
69  SUBROUTINE end_element_handler(name)
70    character(len=*), intent(in)     :: name
71  END SUBROUTINE end_element_handler
72 
73  ! PCDATA handler
74  SUBROUTINE pcdata_chunk_handler(chunk)
75    CHARACTER(len=*), INTENT(in) :: chunk
76  END SUBROUTINE pcdata_chunk_handler
77 
78END MODULE m_count
Note: See TracBrowser for help on using the repository browser.