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.
sla2fb.F90 in utils/tools/OBSTOOLS/src – NEMO

source: utils/tools/OBSTOOLS/src/sla2fb.F90 @ 10841

Last change on this file since 10841 was 3002, checked in by djlea, 13 years ago

Update documentation for obstools and dataplot. Removal of dataplot code not needed. Addition of headers to some dataplot code. Addition of .exe to command example in obstools.

File size: 2.7 KB
Line 
1PROGRAM sla2fb
2   !!---------------------------------------------------------------------
3   !!
4   !!                     ** PROGRAM sla2fb **
5   !!
6   !!  ** Purpose : Convert AVISO SLA format to feedback format
7   !!
8   !!  ** Method  : Use of utilities from obs_fbm.
9   !!
10   !!  ** Action  :
11   !!
12   !!   Usage:
13   !!     sla2fb.exe [-s type] outputfile inputfile1 inputfile2 ...
14   !!   Option:
15   !!     -s            Select altimeter data_source
16   !!
17   !!   History :
18   !!        ! 2010 (K. Mogensen) Initial version
19   !!----------------------------------------------------------------------
20   USE obs_fbm
21   USE obs_sla_io
22   USE convmerge
23   IMPLICIT NONE
24   !
25   ! Command line arguments for output file and input files
26   !
27#ifndef NOIARGCPROTO
28   INTEGER,EXTERNAL :: iargc
29#endif
30   INTEGER :: nargs
31   CHARACTER(len=256) :: cdoutfile
32   CHARACTER(len=256),ALLOCATABLE :: cdinfile(:)
33   CHARACTER(len=256) :: cdtmp
34   CHARACTER(len=5) :: cdsource
35   !
36   ! Input data
37   !
38   TYPE(obfbdata), POINTER :: slaf(:)
39   INTEGER :: ninfiles,ntotobs
40   !
41   ! Output data
42   !
43   TYPE(obfbdata) :: fbdata
44   !
45   ! Loop variables
46   !
47   INTEGER :: ip,ia,ji,jk,noff
48   !
49   ! Get number of command line arguments
50   !
51   nargs=IARGC()
52   IF (nargs < 1) THEN
53      WRITE(*,'(A)')'Usage:'
54      WRITE(*,'(A)')'sla2fb [-s type] outputfile inputfile1 inputfile2 ...'
55      CALL abort()
56   ENDIF
57   cdsource=''
58   !
59   ! Get input data
60   !
61   noff=1
62   IF ( nargs > 1 ) THEN
63      CALL getarg(1,cdtmp)
64      IF (TRIM(cdtmp)=='-s') THEN
65         IF ( nargs < 3 ) THEN
66            WRITE(*,*)'Missing arguments to -s <datasource>'
67            CALL abort
68         ENDIF
69         CALL getarg(2,cdsource)
70         noff=3
71      ENDIF
72   ENDIF
73   CALL getarg(noff,cdoutfile)
74   ninfiles = nargs - noff
75   ALLOCATE( slaf(MAX(nargs-noff,1)) )
76   ALLOCATE( cdinfile(nargs-noff) )
77   ntotobs = 0
78   DO ia=1,ninfiles
79      CALL getarg( ia + noff, cdinfile(ia) )
80      WRITE(*,'(2A)')'File = ',TRIM(cdinfile(ia))
81      CALL read_avisofile( TRIM(cdinfile(ia)), slaf(ia), 6, .TRUE., .FALSE. )
82      WRITE(*,'(A,I9,A)')'has',slaf(ia)%nobs,' observations'
83      IF (LEN_TRIM(cdsource)>0) THEN
84         DO ji=1,slaf(ia)%nobs
85            slaf(ia)%cdwmo(ji)=TRIM(slaf(ia)%cdwmo(ji))//'_'//TRIM(cdsource)
86         ENDDO
87      ENDIF
88      ntotobs = ntotobs + slaf(ia)%nobs
89   ENDDO
90   IF (ninfiles==0) THEN
91      CALL init_obfbdata( slaf(1) )
92      CALL alloc_obfbdata( slaf(1), 1, 0, 1, 0, 0, .FALSE. )
93      slaf(1)%cname(1) = 'SLA'
94      slaf(1)%cdjuldref = '19500101000000'
95   ENDIF
96   WRITE(*,'(A,I8)') 'Total observations : ',ntotobs
97   !
98   ! Merge and output the data.
99   !
100   CALL conv_fbmerge( TRIM(cdoutfile), ninfiles, slaf )
101
102END PROGRAM sla2fb
Note: See TracBrowser for help on using the repository browser.