Subversion Repositories lagranto.ecmwf

Rev

Rev 11 | Rev 39 | Go to most recent revision | Show entire file | Ignore whitespace | Details | Blame | Last modification | View Log | RSS feed

Rev 11 Rev 15
Line 59... Line 59...
59
  integer :: ncol                      ! Number of columns (including time, lon, lat, p)
59
  integer :: ncol                      ! Number of columns (including time, lon, lat, p)
60
  integer :: ntim                      ! Number of times per trajectory
60
  integer :: ntim                      ! Number of times per trajectory
61
  integer :: ntrace0                   ! Number of trace variables
61
  integer :: ntrace0                   ! Number of trace variables
62
  character(len=80) :: tvar0(200)      ! Tracing variable (with mode specification)
62
  character(len=80) :: tvar0(200)      ! Tracing variable (with mode specification)
63
  character(len=80) :: tvar(200)       ! Tracing variable name (only the variable)
63
  character(len=80) :: tvar(200)       ! Tracing variable name (only the variable)
64
  character(len=1)  :: tfil(200)       ! Filename prefix
64
  character(len=80) :: tfil(200)       ! Filename prefix
65
  real :: fac(200)                     ! Scaling factor
65
  real :: fac(200)                     ! Scaling factor
66
  real :: shift_val(200)               ! Shift in space and time relative to trajectory position
66
  real :: shift_val(200)               ! Shift in space and time relative to trajectory position
67
  character(len=80) :: shift_dir(200)  ! Direction of shift
67
  character(len=80) :: shift_dir(200)  ! Direction of shift
68
  integer :: compfl(200)               ! Computation flag (1=compute)
68
  integer :: compfl(200)               ! Computation flag (1=compute)
69
  integer :: numdat                    ! Number of input files
69
  integer :: numdat                    ! Number of input files
Line 802... Line 802...
802
     if ( ( shift_dir(i).ne.'nil'     ).and. &
802
     if ( ( shift_dir(i).ne.'nil'     ).and. &
803
          ( shift_dir(i).ne.'DLON'    ).and. &
803
          ( shift_dir(i).ne.'DLON'    ).and. &
804
          ( shift_dir(i).ne.'DLAT'    ).and. &
804
          ( shift_dir(i).ne.'DLAT'    ).and. &
805
          ( shift_dir(i).ne.'DP'      ).and. &
805
          ( shift_dir(i).ne.'DP'      ).and. &
806
          ( shift_dir(i).ne.'HPA'     ).and. &
806
          ( shift_dir(i).ne.'HPA'     ).and. &
-
 
807
          ( shift_dir(i).ne.'HPA(ABS)').and. &
807
          ( shift_dir(i).ne.'KM(LON)' ).and. &
808
          ( shift_dir(i).ne.'KM(LON)' ).and. &
808
          ( shift_dir(i).ne.'KM(LAT)' ).and. &
809
          ( shift_dir(i).ne.'KM(LAT)' ).and. &
809
          ( shift_dir(i).ne.'H'       ).and. &
810
          ( shift_dir(i).ne.'H'       ).and. &
810
          ( shift_dir(i).ne.'MIN'     ).and. &
811
          ( shift_dir(i).ne.'MIN'     ).and. &
811
          ( shift_dir(i).ne.'INDP'    ) ) then
812
          ( shift_dir(i).ne.'INDP'    ) ) then
Line 818... Line 819...
818
  print*
819
  print*
819
  print*,'---- COMPLETE TABLE FOR TRACING -------------------------'
820
  print*,'---- COMPLETE TABLE FOR TRACING -------------------------'
820
  print*
821
  print*
821
  do i=1,ntrace1
822
  do i=1,ntrace1
822
     if ( ( shift_dir(i).ne.'nil' ) ) then
823
     if ( ( shift_dir(i).ne.'nil' ) ) then
823
        write(*,'(i4,a4,a8,f10.2,a8,3x,a1,i5)') i,' : ',trim(tvar(i)), &
824
        write(*,'(i4,a4,a8,f10.2,a8,3x,a4,i5)') i,' : ',trim(tvar(i)), &
824
             shift_val(i),trim(shift_dir(i)),tfil(i),compfl(i)
825
             shift_val(i),trim(shift_dir(i)),tfil(i),compfl(i)
825
     else
826
     else
826
        write(*,'(i4,a4,a8,10x,8x,3x,a1,i5)') &
827
        write(*,'(i4,a4,a8,10x,8x,3x,a4,i5)') &
827
             i,' : ',trim(tvar(i)),tfil(i),compfl(i)
828
             i,' : ',trim(tvar(i)),tfil(i),compfl(i)
828
     endif
829
     endif
829
  enddo
830
  enddo
830
 
831
 
831
  ! --------------------------------------------------------------------
832
  ! --------------------------------------------------------------------
Line 923... Line 924...
923
         endif
924
         endif
924
 
925
 
925
         ! Load manager:  Load first time (tracing variable and grid)
926
         ! Load manager:  Load first time (tracing variable and grid)
926
         if ( itime0.ne.iloaded0 ) then
927
         if ( itime0.ne.iloaded0 ) then
927
 
928
 
928
            filename = tfil(i)//dat(itime0)
929
            filename = trim(tfil(i))//trim(dat(itime0))
929
            call frac2hhmm(time0,tload)
930
            call frac2hhmm(time0,tload)
930
            varname  = tvar(i)
931
            varname  = tvar(i)
931
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
932
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
932
            call input_open (fid,filename)
933
            call input_open (fid,filename)
933
            call input_wind &
934
            call input_wind &
Line 944... Line 945...
944
         endif
945
         endif
945
 
946
 
946
         ! Load manager: Load second time (tracing variable and grid)
947
         ! Load manager: Load second time (tracing variable and grid)
947
         if ( itime1.ne.iloaded1 ) then
948
         if ( itime1.ne.iloaded1 ) then
948
 
949
 
949
            filename = tfil(i)//dat(itime1)
950
            filename = trim(tfil(i))//trim(dat(itime1))
950
            call frac2hhmm(time1,tload)
951
            call frac2hhmm(time1,tload)
951
            varname  = tvar(i)
952
            varname  = tvar(i)
952
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
953
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
953
            call input_open (fid,filename)
954
            call input_open (fid,filename)
954
            call input_wind &
955
            call input_wind &
Line 1002... Line 1003...
1002
               y0 = y0 + shift_val(i)/deg2km
1003
               y0 = y0 + shift_val(i)/deg2km
1003
 
1004
 
1004
            elseif ( shift_dir(i).eq.'HPA' ) then                      ! HPA
1005
            elseif ( shift_dir(i).eq.'HPA' ) then                      ! HPA
1005
               p0 = p0 + shift_val(i)
1006
               p0 = p0 + shift_val(i)
1006
 
1007
 
-
 
1008
            elseif ( shift_dir(i).eq.'HPA(ABS)' ) then                 ! HPA(ABS)
-
 
1009
               p0 = shift_val(i)
-
 
1010
 
1007
            elseif ( shift_dir(i).eq.'DP' ) then                       ! DP
1011
            elseif ( shift_dir(i).eq.'DP' ) then                       ! DP
1008
               call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0, &
1012
               call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0, &
1009
                    p3t0,p3t1,spt0,spt1,3,nx,ny,nz,xmin,ymin,dx,dy,mdv)
1013
                    p3t0,p3t1,spt0,spt1,3,nx,ny,nz,xmin,ymin,dx,dy,mdv)
1010
               pind = pind - shift_val(i)
1014
               pind = pind - shift_val(i)
1011
               p0   = int_index4(p3t0,p3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
1015
               p0   = int_index4(p3t0,p3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
Line 2103... Line 2107...
2103
  ! Auxiliary variables
2107
  ! Auxiliary variables
2104
  integer :: i,j
2108
  integer :: i,j
2105
  integer :: icolon,inumber
2109
  integer :: icolon,inumber
2106
  character(len=80) :: name
2110
  character(len=80) :: name
2107
  character :: ch
2111
  character :: ch
-
 
2112
  integer      isabsval
2108
 
2113
 
2109
  ! Save variable name
2114
  ! Save variable name
2110
  name = tvar
2115
  name = tvar
2111
 
2116
 
2112
  ! Search for colon
2117
  ! Search for colon
Line 2119... Line 2124...
2119
  ! If there is a colon, split the variable name
2124
  ! If there is a colon, split the variable name
2120
  if ( icolon.ne.0 ) then
2125
  if ( icolon.ne.0 ) then
2121
 
2126
 
2122
     tvar = name(1:(icolon-1))
2127
     tvar = name(1:(icolon-1))
2123
 
2128
 
-
 
2129
     ! Get the index for number
2124
     do i=icolon+1,80
2130
     do i=icolon+1,80
2125
        ch = name(i:i)
2131
        ch = name(i:i)
2126
        if ( ( ch.ne.'0' ).and. ( ch.ne.'1' ).and.( ch.ne.'2' ).and. &
2132
        if ( ( ch.ne.'0' ).and. ( ch.ne.'1' ).and.( ch.ne.'2' ).and. &
2127
             ( ch.ne.'3' ).and. ( ch.ne.'4' ).and.( ch.ne.'5' ).and. &
2133
             ( ch.ne.'3' ).and. ( ch.ne.'4' ).and.( ch.ne.'5' ).and. &
2128
             ( ch.ne.'6' ).and. ( ch.ne.'7' ).and.( ch.ne.'8' ).and. &
2134
             ( ch.ne.'6' ).and. ( ch.ne.'7' ).and.( ch.ne.'8' ).and. &
Line 2131... Line 2137...
2131
           inumber = i
2137
           inumber = i
2132
           exit
2138
           exit
2133
        endif
2139
        endif
2134
     enddo
2140
     enddo
2135
 
2141
 
-
 
2142
     ! Get the number
2136
     read(name( (icolon+1):(inumber-1) ),*) shift_val
2143
     read(name( (icolon+1):(inumber-1) ),*) shift_val
2137
 
2144
 
-
 
2145
     ! Decide whether it is a shift relatiev to trajectory or absolute value
-
 
2146
     ! If the number starts with + or -, it is relative to the trajectory
-
 
2147
     isabsval = 1
-
 
2148
     do i=icolon+1,inumber-1
-
 
2149
       ch = name(i:i)
-
 
2150
       if ( (ch.eq.'+').or.(ch.eq.'-') ) isabsval = 0
-
 
2151
     enddo
-
 
2152
 
-
 
2153
     ! Get the unit/shift axis
2138
     shift_dir = name(inumber:80)
2154
     shift_dir = name(inumber:80)
-
 
2155
     if ( isabsval.eq.1 ) then
-
 
2156
       shift_dir=trim(shift_dir)//'(ABS)'
-
 
2157
     endif
2139
 
2158
 
2140
  else
2159
  else
2141
 
2160
 
2142
     shift_dir = 'nil'
2161
     shift_dir = 'nil'
2143
     shift_val = 0.
2162
     shift_val = 0.