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.
agrif_create_data.f90 in branches/UKMO/r5936_hadgem3_cplfld/NEMOGCM/TOOLS/NESTING/src – NEMO

source: branches/UKMO/r5936_hadgem3_cplfld/NEMOGCM/TOOLS/NESTING/src/agrif_create_data.f90 @ 7138

Last change on this file since 7138 was 7138, checked in by jcastill, 7 years ago

Remove svn keywords

File size: 1.8 KB
Line 
1PROGRAM create_data
2  !
3  USE io_netcdf
4  USE bilinear_interp
5  USE agrif_readwrite
6  USE agrif_interpolation     
7  !
8  IMPLICIT NONE
9  !
10  !************************************************************************
11  !                           *
12  ! PROGRAM  CREATE_DATA                     *
13  !                           *
14  ! program to implement data interpolation to generate        *
15  ! child grid forcing files                 *
16  !                           *                          *
17  !Interpolation is carried out using bilinear interpolation      *
18  !routine from SCRIP package                *     
19  !                           *
20  !http://climate.lanl.gov/Software/SCRIP/            *                          *
21  !************************************************************************
22  !
23  INTEGER :: narg,iargc,i
24  CHARACTER(len=80) :: namelistname
25
26  narg = iargc()
27
28  IF (narg == 0) THEN
29     namelistname = 'namelist.input'
30  ELSE
31     CALL getarg(1,namelistname)
32  ENDIF
33
34  ! read input file (namelist.input)
35  !
36  CALL read_namelist(namelistname)
37
38  i = 1
39  !
40  ! Interpolate U grid  data
41  !
42  DO WHILE( TRIM(U_Files(i)) .NE. '/NULL' )
43     PRINT *,'Grid U forcing files = ',u_files(i)
44     !       
45     CALL Interp_Extrap_var(U_FILES(i), 'U') 
46     i = i+1               
47     !             
48  END DO
49
50  i = 1
51  !
52  ! Interpolate V grid  data
53  !
54  DO WHILE( TRIM(V_Files(i)) .NE. '/NULL' )
55     PRINT *,'Grid V forcing files = ',v_files(i)
56     !       
57     CALL Interp_Extrap_var(V_FILES(i), 'V') 
58     i = i+1               
59     !             
60  END DO
61
62  i = 1
63  !
64  ! Interpolate flux data
65  !
66  DO WHILE( TRIM(Flx_Files(i)) .NE. '/NULL' )
67     PRINT *,'flxfiles = ',flx_files(i)
68     !       
69     CALL Interp_Extrap_var(FLX_FILES(i), 'T') 
70     i = i+1               
71     !             
72  END DO
73  !
74  WRITE(*,*) ' '
75  WRITE(*,*) '******* forcing files successfully created *******' 
76  WRITE(*,*) ' ' 
77  !
78  STOP
79END PROGRAM create_data
Note: See TracBrowser for help on using the repository browser.