Initialization of spatial average of glaciers variables
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | fileini | |||
character(len=*), | intent(in) | :: | pathout | |||
type(grid_real), | intent(in) | :: | iwe |
ice water equivalent (m) |
||
type(grid_real), | intent(in) | :: | freeWater |
water in ice (m) |
||
type(grid_real), | intent(in) | :: | iceMelt |
ice melt in the time step (m) |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
type(IniList), | public | :: | iniDB |
SUBROUTINE InitSpatialAverageGlaciers & ! (fileini, pathout, iwe, freeWater, iceMelt) IMPLICIT NONE !arguments with intent in: CHARACTER(LEN = *), INTENT(IN) :: fileini CHARACTER(LEN = *), INTENT(IN) :: pathout TYPE (grid_real), INTENT(IN) :: iwe !!ice water equivalent (m) TYPE (grid_real), INTENT(IN) :: freeWater !!water in ice (m) TYPE (grid_real), INTENT(IN) :: iceMelt !! ice melt in the time step (m) !local declarations TYPE(IniList) :: iniDB !-------------------------------end of declaration----------------------------- ! open and read configuration file CALL IniOpen (fileini, iniDB) ! search for active variable for output CALL Catch ('info', 'SpatialAverage', 'checking for glaciers active variables ') countice = 0 !ice water equivalent IF ( IniReadInt ('ice-water-equivalent', iniDB, section = 'glacier') == 1) THEN IF ( .NOT. ALLOCATED (iwe % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'ice water equivalent not allocated, & forced to not export spatial average ') iceout (1) = .FALSE. ELSE iceout (1) = .TRUE. countice = countice + 1 END IF ELSE iceout (1) = .FALSE. END IF !ice covered area IF ( IniReadInt ('ice-covered-area', iniDB, section = 'glacier') == 1) THEN IF ( .NOT. ALLOCATED (iwe % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'ice water equivalent not allocated, & forced to not export ice covered area ') iceout (2) = .FALSE. ELSE iceout (2) = .TRUE. countice = countice + 1 END IF ELSE iceout (2) = .FALSE. END IF !liquid water in ice IF ( IniReadInt ('water-in-ice', iniDB, section = 'glacier') == 1) THEN IF ( .NOT. ALLOCATED (freeWater % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'water-in-ice not allocated, & forced to not export water-in-ice ') iceout (3) = .FALSE. ELSE iceout (3) = .TRUE. countice = countice + 1 END IF ELSE iceout (3) = .FALSE. END IF !ice melt IF ( IniReadInt ('ice-melt', iniDB, section = 'glacier') == 1) THEN IF ( .NOT. ALLOCATED (iceMelt % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'ice-melt not allocated, & forced to not export spatial average ') iceout (4) = .FALSE. ELSE iceout (4) = .TRUE. countice = countice + 1 END IF ELSE iceout (4) = .FALSE. END IF iceInitialized = .TRUE. CALL IniClose (iniDB) CALL ConfigureExtents (fileini, pathout) RETURN END SUBROUTINE InitSpatialAverageGlaciers