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.
dom_doc.f90 in utils/tools/DOMAINcfg/src – NEMO

source: utils/tools/DOMAINcfg/src/dom_doc.f90 @ 14623

Last change on this file since 14623 was 13390, checked in by mathiot, 4 years ago

ticket #2502: merge ticket branch into trunk. DOMAIN_cfg namelist contains now fields to specify input files names (bathy meter and level files, coord file, isf draft meter and level files), save it into the netcdf (dom_doc.exe) and re-generate the namelist if needed (xtrac_namelist.bash). The usage is documented in the DOMAIN_cfg README.rst.

File size: 4.4 KB
Line 
1PROGRAM dom_doc
2   !!======================================================================
3   !!                     ***  PROGRAM  dom_doc  ***
4   !!=====================================================================
5   !!  ** Purpose : Add documentation to domain_cfg.nc files created for
6   !!               NEMO4.
7   !!
8   !!  ** Method  : Define a namelist_cfg variable and add source_bathy,
9   !!               source_coord as global attributes.
10   !!
11   !! History :  1.0  : 05/2019  : J.M. Molines (MEOM/IGE/DRAKKAR)   : original DRAKKAR file
12   !!                   07/2020  : P.   Mathiot (CryoDyn/IGE/DRAKKAR): added in NEMO repo
13   !!----------------------------------------------------------------------
14   USE netcdf
15   IMPLICIT NONE
16 
17   INTEGER :: narg, ijarg, iargc
18   INTEGER :: inum=10, n, ji
19   INTEGER :: ncid, id , ierr, idl, idlen, ilen
20   INTEGER :: iformat
21 
22   CHARACTER(LEN=300), DIMENSION(:), ALLOCATABLE :: cv_namlist
23   CHARACTER(LEN=300)                            :: cldum
24   CHARACTER(LEN=80)                             :: cf_namlist
25   CHARACTER(LEN=255)                            :: cf_domcfg
26   !!----------------------------------------------------------------------
27   !! DCM4, MEOM 2019
28   !! Copyright (c) 2019, J.-M. Molines
29   !! Software governed by the CeCILL licence
30   !!----------------------------------------------------------------------
31   narg = iargc()
32   
33   ! default initialisation
34   cf_namlist='namelist_cfg'
35   cf_domcfg ='domain_cfg.nc'
36
37   ijarg = 1 
38   DO WHILE ( ijarg <= narg )
39      CALL getarg(ijarg, cldum ) ; ijarg=ijarg+1
40      SELECT CASE ( cldum )
41      CASE ( '-n'   ) ; CALL getarg(ijarg, cf_namlist ) ; ijarg=ijarg+1
42      CASE ( '-d'   ) ; CALL getarg(ijarg, cf_domcfg  ) ; ijarg=ijarg+1
43      CASE ( '-h'   ) ; CALL usage
44      CASE DEFAULT    ; PRINT *, ' ERROR : ', TRIM(cldum),' : unknown option.'; STOP 1
45      END SELECT
46   ENDDO
47   
48   ! Open namelist and count the number of lines before redifining namelist variable in domcfg file.
49   OPEN(inum, file=cf_namlist)
50 
51   ! count the number of lines
52   n=0 ; ilen=0
53   DO
54      READ(inum,'(a)',END=999) cldum   ! loop till the end of file
55      ilen=MAX(ilen,LEN(TRIM(cldum)))
56      n=n+1
57   ENDDO
58 
59 999 PRINT *,' Number of lines in ',TRIM(cf_namlist),' is : ', n
60 
61   ! allocate variable array
62   ALLOCATE (cv_namlist(n) )
63 
64   REWIND (inum)
65   DO ji = 1, n
66      READ(inum,'(a)',END=999) cv_namlist(ji)
67   ENDDO
68   CLOSE(inum)
69   
70   ! Open domain_cfg file
71   ierr = NF90_OPEN(cf_domcfg,NF90_WRITE,ncid)
72   ierr = NF90_REDEF(ncid)
73 
74   ierr=NF90_DEF_DIM(ncid,'nlines',n, idl)
75   ierr=NF90_DEF_DIM(ncid,'nlen',ilen, idlen)
76 
77   ! note that namelist is a character 2D variables in the sense of netcdf
78   ! the program variable is thus an array of character with ilen char per line and n lines.
79   ! If domain_cfg is netcdf4, then deflate the namelist
80   ierr = NF90_INQUIRE(ncid,formatNum=iformat)
81   IF ( iformat == NF90_FORMAT_NETCDF4 .OR. iformat == NF90_FORMAT_NETCDF4_CLASSIC ) THEN
82      ierr=NF90_DEF_VAR(ncid,'namelist_cfg',NF90_CHAR,(/idlen,idl/), id, chunksizes=(/ilen,n/), deflate_level=9 )
83   ELSE
84      ierr=NF90_DEF_VAR(ncid,'namelist_cfg',NF90_CHAR,(/idlen,idl/), id)
85   ENDIF
86   IF (ierr /= 0 ) THEN
87      PRINT *,NF90_STRERROR(ierr); STOP 1; 
88   END IF
89 
90   ierr=NF90_ENDDEF(ncid)
91   DO ji=1,n
92      ierr=NF90_PUT_VAR(ncid,id,cv_namlist(ji)(1:ilen) ,start=(/1,ji/), count=(/ilen,1/) )
93      IF (ierr /= 0 ) THEN
94         PRINT *,NF90_STRERROR(ierr); STOP 1;
95      END IF
96   ENDDO
97   ierr=NF90_CLOSE(ncid)
98
99CONTAINS
100
101   SUBROUTINE usage
102
103      PRINT *,' usage : dom_doc -n NAMELIST-file '
104      PRINT *,'                       -d DOMAIN_CFG-file'
105      PRINT *,'      '
106      PRINT *,'     PURPOSE :'
107      PRINT *,'        Add information in the domain_cfg.nc file after its creation for'
108      PRINT *,'        NEMO4. The additional information consists in a new netcdf variable'
109      PRINT *,'        called namelist_cfg, holding the content of the used namelist_cfg.'
110      PRINT *,'      '
111      PRINT *,'     ARGUMENTS :'
112      PRINT *,'        -n NAMELIST-file : name of the namelist_cfg. file required'
113      PRINT *,'        -d DOMAIN_CFG-file : name of the domain_cfg file to document. file required'
114      PRINT *,'      '
115      PRINT *,'     OUTPUT : '
116      PRINT *,'         input DOMAIN_CFG-file is modified on output.'
117      PRINT *,'      '
118      STOP
119
120   END SUBROUTINE usage
121 
122END PROGRAM dom_doc
123 
Note: See TracBrowser for help on using the repository browser.