File: normalize.f90

package info (click to toggle)
libpsml 2.1.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 3,048 kB
  • sloc: f90: 3,888; makefile: 211; pascal: 166; sh: 76
file content (87 lines) | stat: -rw-r--r-- 2,574 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
program normalize

  !
  ! Parses a PSML file and dumps the contents of the resulting
  ! ps_t object in a PSML 1.1 file.
  !
  ! If it detects a 1.0 PSML file, it inserts
  ! a new provenance element, but keeps the original uuid.
  !
  ! It will also add 'record-number' attributes to provenance elements.
  !
use m_psml
use m_getopts

integer, parameter :: dp = selected_real_kind(10,100)

type(ps_t)   :: ps

      character(len=200) :: filename, output_filename
      logical            :: debug
      character(len=200) :: opt_arg, mflnm, ref_line
      character(len=10)  :: opt_name 
      integer :: nargs, iostat, n_opts, nlabels
      
      integer :: i, j, l, n, num, nfun, set, seq
      character(len=20) :: date, version
!
!     Process options
!
      n_opts = 0
      debug = .false.
      output_filename = "PSML_DUMP"
      do
         call getopts('do:',opt_name,opt_arg,n_opts,iostat)
         if (iostat /= 0) exit
         select case(opt_name)
           case ('d')
              debug = .true.
           case ('o')
              read(opt_arg,*) output_filename
           case ('?',':')
             write(0,*) "Invalid option: ", opt_arg(1:1)
             write(0,*) "Usage: test_dump [-o output_file] PSML_FILE"
             STOP
          end select
       enddo

       nargs = command_argument_count()
       nlabels = nargs - n_opts + 1
       if (nlabels /= 1)  then
             write(0,*) "Invalid option: ", opt_arg(1:1)
             write(0,*) "Usage: test_dump [-o output_file] PSML_FILE"
             STOP
       endif

       call get_command_argument(n_opts,value=filename,status=iostat)
       if (iostat /= 0) then
          STOP "Cannot get filename"
       endif
!
if (debug) print "(a)", "Processing: " // trim(filename)
call date_and_time(date)
call psml_reader(filename,ps,debug=debug,stat=iostat)
if (iostat == -1) then
   write(0,*) "Cannot open PSML file " // trim(filename)
   STOP
endif

call ps_RootAttributes_Get(ps,version=version)

call ps_RootAttributes_Set(ps,version="1.1",&
     namespace="http://esl.cecam.org/PSML/ns/1.1")

if (trim(version) == "1.0") then
   if (nitems_annotation(ps%annotation)>0) then
      call ps_Provenance_Add(ps,creator="1.0-to-1.1-conversion",&
           date=trim(date),  annotation=ps%annotation)
   else
      call ps_Provenance_Add(ps,creator="1.0-to-1.1-conversion",&
           date=trim(date), annotation=EMPTY_ANNOTATION)
   endif
endif

call ps_DumpToPSMLFile(ps,trim(output_filename))
write(0,"(a)") "Written PSML 1.1 file: " // trim(output_filename)
end program normalize