!===================================================================================================================== ! ! Module to read prior file and calculate prior cloud probability ! ! ! !===================================================================================================================== module READ_PRIOR_MOD use NB_CLOUD_MASK_NETCDF_READ_MODULE, only: & OPEN_NETCDF & , CLOSE_NETCDF & , READ_NETCDF_GLOBAL_ATTRIBUTE_R4 & , READ_NETCDF_4D_REAL implicit none public COMPUTE_PRIOR contains subroutine COMPUTE_PRIOR(Prior_File_Name, Lon, Lat, Month, Prior_Probability) character(len=*), intent(in) :: Prior_File_Name real, dimension(:,:), intent(in) :: Lon real, dimension(:,:), intent(in) :: Lat integer, intent(in) :: Month real, dimension(:,:), allocatable, intent(out) :: Prior_Probability real :: Nlon_Prior, Nlat_Prior, Nmonths_Prior, Ndiurnal_Prior real :: Dlon_Prior, Dlat_Prior real :: Lon_Min_Prior, Lon_Max_Prior real :: Lat_Min_Prior, Lat_Max_Prior real, dimension(:,:,:,:), allocatable :: Prior_Table integer :: Ncid integer :: Nx, Ny integer, parameter:: Idiurnal = 1 !1 = daily averaged integer :: i,j,ilon,ilat integer, dimension(4) :: Dims !--- open file call OPEN_NETCDF(trim(Prior_File_Name), Ncid) !--- read attributes call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "number_longitudes", Nlon_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "number_latitudes", Nlat_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "number_months", Nmonths_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "number_times", Ndiurnal_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "longitude_spacing", Dlon_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "latitude_spacing", Dlat_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "longitude_min", Lon_Min_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "longitude_max", Lon_Max_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "latitude_min", Lat_Min_Prior) call READ_NETCDF_GLOBAL_ATTRIBUTE_R4(Ncid, "latitude_max", Lat_Max_Prior) ! --- allocate prior table Dims = (/int(Nlon_Prior),int(Nlat_Prior),int(Nmonths_Prior), int(Ndiurnal_Prior)/) allocate(Prior_Table(Dims(1),Dims(2),Dims(3),Dims(4))) ! --- read table call READ_NETCDF_4D_REAL(Ncid, (/1,1,1,1/), (/1,1,1,1/), Dims, & "cloud_fraction_table_smoothed", Prior_Table) ! --- close file call CLOSE_NETCDF(Ncid) ! --- get dimensions Nx = size(Lon,1) Ny = size(Lon,2) ! --- allocate Prior_Probability allocate(Prior_Probability(Nx, Ny)) ! --- calculate prior do i = 1, Nx do j = 1, Ny ilon = min(int(Nlon_Prior),max(1,int((Lon(i,j) - Lon_Min_Prior) / (Dlon_Prior))+1)) ilat = min(int(Nlat_Prior),max(1,int((Lat(i,j) - Lat_Min_Prior) / (Dlat_Prior))+1)) Prior_Probability(i,j) = Prior_Table(Ilon, Ilat, Month, Idiurnal) enddo enddo ! --- deallocate prior table if (allocated(Prior_Table)) deallocate(Prior_Table) end subroutine COMPUTE_PRIOR end module READ_PRIOR_MOD