Skip to content
Snippets Groups Projects
sfx_z0m_all.f90 7.6 KiB
Newer Older
  • Learn to ignore specific revisions
  • module sfx_z0m_all
       
      !< @brief surface thermal roughness parameterizations for all type surface
    
    
        use sfx_z0m_all_surface
    
        
    
        implicit none
        public :: get_dynamic_roughness_all
        public :: get_dynamic_roughness_definition
    
        
        integer, public, parameter :: surface_ocean = 0     !< ocean surface
        integer, public, parameter :: surface_land = 1      !< land surface
        integer, public, parameter :: surface_lake = 2      !< lake surface
        integer, public, parameter :: surface_snow = 3      !< snow covered surface    
        integer, public, parameter :: surface_forest = 4    !< forest csurface  
        integer, public, parameter :: surface_user = 5      !< user surface  
    
        
        integer, public, parameter :: z0m_ch = 0 
        integer, public, parameter :: z0m_fe = 1   
        integer, public, parameter :: z0m_ow = 2  
        integer, public, parameter :: z0m_map = 3      
        integer, public, parameter :: z0m_user = 4     
    
    
    
        character(len = 16), parameter :: surface_ocean_tag = 'ocean'
        character(len = 16), parameter :: surface_land_tag = 'land'
        character(len = 16), parameter :: surface_lake_tag = 'lake'
        character(len = 16), parameter :: surface_snow_tag = 'snow'
        character(len = 16), parameter :: surface_forest_tag = 'forest'
        character(len = 16), parameter :: surface_user_tag = 'user'
    
        character(len = 16), parameter :: z0m_tag_ch = 'charnock'
        character(len = 16), parameter :: z0m_tag_fe = 'fetch'
        character(len = 16), parameter :: z0m_tag_ow = 'owen'
        character(len = 16), parameter :: z0m_tag_map = 'map'
        character(len = 16), parameter :: z0m_tag_user = 'user'
        
    
        integer, public, parameter :: ocean_z0m_id = z0m_ch     !< ocean surface
        integer, public, parameter :: land_z0m_id = z0m_map        !< land surface
        integer, public, parameter :: lake_z0m_id = z0m_fe        !< lake surface
        integer, public, parameter :: snow_z0m_id = z0m_ow        !< snow covered surface    
        integer, public, parameter :: forest_z0m_id = z0m_map     !< forest csurface  
        integer, public, parameter :: usersf_z0m_id = z0m_map       !< user surface  
       
       
        contains
    
    
      ! surface type definition
        ! --------------------------------------------------------------------------------
        function get_surface_id(tag) result(id)
            implicit none
            character(len=*), intent(in) :: tag
            integer :: id
    
            id = - 1
            if (trim(tag) == trim(surface_ocean_tag)) then
                id = surface_ocean
            else if (trim(tag) == trim(surface_land_tag)) then
                id = surface_land
            else if (trim(tag) == trim(surface_lake_tag)) then
                id = surface_lake
            else if (trim(tag) == trim(surface_snow_tag)) then
                id = surface_snow
            end if
    
        end function
    
        function get_surface_tag(id) result(tag)
            implicit none
            integer :: id
            character(len=:), allocatable :: tag
    
            tag = 'undefined'
            if (id == surface_ocean) then
                tag = surface_ocean_tag
            else if (id == surface_land) then
                tag = surface_land_tag
            else if (id == surface_lake) then
                tag = surface_lake_tag
            else if (id == surface_snow) then
                tag = surface_snow_tag
            end if 
    
        end function
    
        
          ! --------------------------------------------------------------------------------
         ! surface type definition
        ! --------------------------------------------------------------------------------
        function get_surface_z0m_id(tag_z0m) result(z0m_id)
            implicit none
            character(len=*), intent(in) :: tag_z0m
            integer :: z0m_id
    
            z0m_id = - 1
            if (trim(tag_z0m) == trim(z0m_tag_ch)) then
                z0m_id = z0m_ch
            else if (trim(tag_z0m) == trim(z0m_tag_fe)) then
                z0m_id = z0m_fe
            else if (trim(tag_z0m) == trim(z0m_tag_ow)) then
                z0m_id = z0m_ow
            else if (trim(tag_z0m) == trim(z0m_tag_map)) then
                z0m_id = z0m_map
            else if (trim(tag_z0m) == trim(z0m_tag_user)) then
                z0m_id = z0m_user
            end if
    
        end function
    
        function get_surface_z0m_tag(z0m_id) result(tag_z0m)
            implicit none
            integer :: z0m_id
            character(len=:), allocatable :: tag_z0m
    
            tag_z0m = 'undefined'
            if (z0m_id == z0m_ch) then
                tag_z0m = z0m_tag_ch
            else if (z0m_id == z0m_fe) then
                tag_z0m =  z0m_tag_fe
            else if (z0m_id == z0m_ow) then
                tag_z0m = z0m_tag_ow
            else if (z0m_id == z0m_map) then
                tag_z0m = z0m_tag_map
            else if (z0m_id == z0m_user) then
                tag_z0m = z0m_tag_user
            end if 
         end function
    
    
    
         ! ----------------------------------------------------------------------------
           subroutine get_dynamic_roughness_all(z0_m, u_dyn0, U, depth, h,&
             maxiters, z0m_map, z0m_id)
         ! ----------------------------------------------------------------------------
                real, intent(out) :: z0_m           !< aerodynamic roughness [m]
                real, intent(out) :: u_dyn0         !< dynamic velocity in neutral conditions [m/s]
        
                real, intent(in) :: U               !< abs(wind speed) [m/s]
                real, intent(in) :: depth           !< depth [m]
                real, intent(in) :: h               !< constant flux layer height [m]
                real, intent(in) :: z0m_map          !< aerodynamic roughness from map [m]
                integer, intent(in) :: maxiters     !< maximum number of iterations
                
                integer, intent(in) :: z0m_id
         ! ---------------------------------------------------------------------------
    
    
           if (z0m_id == z0m_ch) then
               call get_dynamic_roughness_ch(z0_m, u_dyn0, U, h, maxiters)
            else if (z0m_id == z0m_fe) then
                call get_dynamic_roughness_fetch(z0_m, u_dyn0, U, depth, h, maxiters)
            else if (z0m_id == z0m_ow) then
                call get_dynamic_roughness_ow(z0_m, u_dyn0, U, h, maxiters)
            else if (z0m_id == z0m_map) then
                call get_dynamic_roughness_map(z0_m, u_dyn0, U, h, z0m_map)
            else if (z0m_id == z0m_user) then
                write(*, *) 'z0m_user'
         end if 
    
         end subroutine
        ! --------------------------------------------------------------------------------  
       
       ! ----------------------------------------------------------------------------
    
           subroutine get_dynamic_roughness_definition(surface_type, ocean_z0m_id, land_z0m_id, snow_z0m_id, lake_z0m_id, &
            forest_z0m_id, usersf_z0m_id, z0m_id)
    
         ! ----------------------------------------------------------------------------
    
            real, intent(out) :: z0m_id              
        
    
            real, intent(in) :: ocean_z0m_id            
            real, intent(in) :: land_z0m_id              
            real, intent(in) :: snow_z0m_id
            real, intent(in) :: lake_z0m_id
            real, intent(in) :: forest_z0m_id 
            real, intent(in) :: usersf_z0m_id
    
            
         ! ---------------------------------------------------------------------------
    
    
           Write (*,*) 'get_dynamic_roughness_definition'
    
             z0m_id = ocean_z0m_id
    
         else if (surface_type == surface_land) then
    
             z0m_id = land_z0m_id
    
         else if (surface_type == surface_snow) then
    
             z0m_id = snow_z0m_id
    
         else if (surface_type == surface_lake) then
    
            z0m_id = lake_z0m_id
    
         else if (surface_type == surface_forest) then
    
             z0m_id = forest_z0m_id
    
         else if (surface_type == surface_user) then
    
             z0m_id  = usersf_z0m_id