Path: blob/devel/misc/netcdf/src/GridDataMapper/MapperUtils.f90
3206 views
!------------------------------------------------------------------------------1! Vili Forsell2! Created: 7.7.20113! Last Modified: 13.7.20114!------------------------------------------------------------------------------5! This module contains general functions for GridDataMapper6! - GetElmerNodeValue() ; Simplified access to Elmer Node's coordinates7! - GetElmerMinMax() ; Returns min, or max, value for given Elmer dimension8! - IntWidth() ; Returns the numeric width for an integer value9! o Mainly used for determining widths for format fields to avoid prefix spaces10! - ListGetStrings() ; Collects an array of strings from SIF defined with names suffixed by running numbers11! o Used to generalize string input12!------------------------------------------------------------------------------13MODULE MapperUtils1415CONTAINS1617!---------------- GetElmerNodeValue() ---------------18!--- Gets the value of the chosen node from the given dimension (1 = x, 2 = y, 3 = z)19FUNCTION GetElmerNodeValue( Solver, node, dimE ) RESULT( node_val )20!----------------------------------------------------21USE DefUtils, ONLY: Solver_t, dp22USE Messages, ONLY: Fatal23IMPLICIT NONE2425TYPE(Solver_t), INTENT(IN) :: Solver26INTEGER, INTENT(IN) :: node, dimE27REAL(KIND=dp) :: node_val ! The output28SELECT CASE (dimE)29CASE (1)30node_val = Solver % Mesh % Nodes % x(node)31CASE (2)32node_val = Solver % Mesh % Nodes % y(node)33CASE (3)34node_val = Solver % Mesh % Nodes % z(node)35CASE DEFAULT36CALL Fatal('GridDataMapper','GetElmerNodeValue(): Elmer dimension not found')37node_val = 038END SELECT3940END FUNCTION GetElmerNodeValue4142!---------------- GetElmerMinMax() ---------------43!--- Gets the minimum/maximum (chosen) value of the given dimension (1 = x, 2 = y, 3 = z)44FUNCTION GetElmerMinMax( Solver, dimE, GET_MIN ) RESULT( node_val )45!----------------------------------------------------46USE DefUtils, ONLY: Solver_t, CoordinateSystemDimension, dp47USE Messages, ONLY: Fatal48IMPLICIT NONE4950TYPE(Solver_t), INTENT(IN) :: Solver51INTEGER, INTENT(IN) :: dimE52LOGICAL, INTENT(IN) :: GET_MIN53REAL(KIND=dp) :: node_val ! The output5455SELECT CASE (dimE)56CASE (1)57IF ( GET_MIN ) THEN58node_val = MINVAL(Solver % Mesh % Nodes % x)59ELSE60node_val = MAXVAL(Solver % Mesh % Nodes % x)61END IF62CASE (2)63IF ( GET_MIN ) THEN64node_val = MINVAL(Solver % Mesh % Nodes % y)65ELSE66node_val = MAXVAL(Solver % Mesh % Nodes % y)67END IF68CASE (3)69IF ( GET_MIN ) THEN70node_val = MINVAL(Solver % Mesh % Nodes % z)71ELSE72node_val = MAXVAL(Solver % Mesh % Nodes % z)73END IF74CASE DEFAULT75CALL Fatal('GridDataMapper','GetAllElmerNodeValues(): Elmer dimension not found')76node_val = 077END SELECT7879END FUNCTION GetElmerMinMax808182!----------------------- IntWidth() --------------83!--- Finds the width of an integer; ignores sign84FUNCTION IntWidth( NR ) RESULT( width )85!-------------------------------------------------86IMPLICIT NONE87INTEGER, INTENT(IN) :: NR88INTEGER :: val89INTEGER :: width90INTEGER :: comp9192width = 193comp = 1094val = ABS(NR) + 1 ! Ignores sign; val >= 19596! Note that:97! 10^0 - 1 = 0 <= 0..9 <= 10 = 10^1 - 1,98! 10^1 - 1 = 0 <= 10..99 <= 10 = 10^2 - 1,99! 10^2 - 1 = 0 <= 100..999 <= 10 = 10^3 - 1,100! and so forth,101! where 10 corresponds to width of the number with 10 based numbers (n == width).102! We get: 10^(n-1) <= NR + 1 <= 10^(n)103104! Width usually small, so logarithmic search is not usually necessary.105106! P: 10^0 = 1 <= val+1 .AND. width = 1 => For every j; 0 <= j <= i: 10^i <= val+1 .AND. i = 0 .AND. width = i + 1 = 0 + 1 = 1107DO WHILE (comp < val)108width = width + 1 ! width = i+1109comp = 10*comp ! 10*10^(i) = 10^(i+1)110! I: For every j; 0 <= j <= i: 10^j <= val+1 .AND. Exists n; i < n: val+1 <= 10^n .AND. width = i+1111END DO112! Q: (For every i; 0 <= i <= n-1: 10^i <= val+1) .AND. val+1 <= 10^n .AND. width = n113! => 10^(n-1) <= val+1 .AND. val+1 <= 10^n .AND. width = n114115END FUNCTION IntWidth116117!----------------- GetNetCDFAccessParameters() ------118!--- Gets all access strings and their associated accessing order119SUBROUTINE GetNetCDFAccessParameters( List,Variables,Constants,Permutation,Found )120!----------------------------------------------------121USE DefUtils122IMPLICIT NONE123124!--- Arguments125TYPE(ValueList_t), INTENT(IN), POINTER :: List ! A pointer to a list of values126LOGICAL, OPTIONAL, INTENT(INOUT) :: Found(2) ! True, if found127CHARACTER(LEN=MAX_NAME_LEN), INTENT(OUT), ALLOCATABLE :: Variables(:),Constants(:) ! For returned array data128INTEGER, INTENT(OUT), ALLOCATABLE :: Permutation(:) ! NetCDF Access permutation; maps variables and constants to their proper locations129! Indexing order: Variables, then Constants130131!--- Variables132TYPE(ValueList_t), POINTER :: ptr133CHARACTER(LEN=MAX_NAME_LEN) :: tmpStr134CHARACTER(LEN=MAX_NAME_LEN) :: Names(2) ! Names of the SIF variables135LOGICAL, ALLOCATABLE :: IsVariable(:) ! Valid until total_size136LOGICAL :: GotIt, PrevGotIt, OtherWasDefined137INTEGER :: TOTAL, var_i, const_i, const_size, coord_size138INTEGER :: loop, loop2, total_size, alloc_stat139CHARACTER(LEN=10) :: tmpFormat140141!--- Initializations142NULLIFY(ptr)143IF ( PRESENT(Found) ) Found = .FALSE.144145TOTAL = GetInteger(List,'NetCDF Max Parameters', GotIt)146IF ( .NOT. GotIt ) THEN147CALL Warn('GridDataMapper',&148'Please specify the maximum amount of NetCDF parameters with &149variable "NetCDF Max Parameters". Assumed to be 10 by default.')150TOTAL = 10 ! Default 10, affects efficiency and halting151ELSE IF ( TOTAL .LT. 1 ) THEN152CALL Warn('GridDataMapper','Minimum of one parameter expected for "NetCDF Max Parameters". It is now set to 1.')153TOTAL = 1154END IF155156ALLOCATE ( IsVariable(TOTAL), STAT = alloc_stat )157IF ( alloc_stat .NE. 0 ) THEN158CALL Fatal('GridDataMapper','Memory ran out')159END IF160IsVariable = .FALSE. ! Defaulted to constant; even when over range161162! The names of the SIF variables163Names(1) = 'Coordinate Name'164Names(2) = 'NetCDF Constant'165166! Count the amount of defined strings for allocation167total_size = 0168coord_size = 0 ! Amount of existing coordinates/variables169const_size = 0 ! Amount of existing constants170PrevGotIt = .TRUE. ! If previous one was false, then the next one must not be true (otherwise omitted numbers)171OtherWasDefined = .FALSE. ! True if both names defined for the same location172DO loop = 1,TOTAL,1173OtherWasDefined = .FALSE. ! (NO DUPLICATES)174DO loop2 = 1,size(Names),1175! Find all Coordinates and Constants176177!--- Checks for existence of the Name (EXISTS CHECK)178! Tries to ensure that the given integer doesn't have extra spaces before it in char format179! Scales until a number with a width of 9 (limited by tmpFormat)180WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop),')'181WRITE(tmpStr,tmpFormat) TRIM(Names(loop2)),' ',loop182ptr => ListFind( List,tmpStr,GotIt ) ! NOTE: This will probably be a slow operation (linear/logarithmic)183184!--- Checks for duplicates and updates the sizes185IF (GotIt) THEN186IF (.NOT. ASSOCIATED(ptr)) THEN187GotIt = .FALSE.188ELSE IF ( OtherWasDefined ) THEN189!--- The other Name was defined for the same index; conflict! (NO DUPLICATES)190WRITE(Message,'(A,I3)') 'Both a Coordinate Name and a NetCDF Constant &191were defined for NetCDF variable access location ', loop192CALL Fatal('GridDataMapper', Message)193ELSE194!--- Found and works (COORD_SIZE RIGHT, CONST_SIZE RIGHT, TOTAL_SIZE CORRECT)195! < Exists "Names 'loop2'" >196total_size = loop ! Chooses the largest that exists197IF ( loop2 .EQ. 1 ) THEN ! "Names" = "Coordinate Name"198coord_size = coord_size + 1199IsVariable(loop) = .TRUE. ! To find correct places later on200ELSE ! "Names" = "NetCDF Constant"201const_size = const_size + 1202! IsVariable defaulted to .FALSE.203END IF204! Postcondition has been updated for all until loop and loop2 (NO DUPLICATES)205OtherWasDefined = .TRUE.206END IF207END IF208209!--- Checks that there are no gaps with the numbering (TOTAL_SIZE CORRECT)210IF ( GotIt .AND. (.NOT. PrevGotIt) ) THEN211WRITE(Message,'(A,I3,A)') 'NetCDF access parameter(s) before parameter ', loop ,' are missing'212CALL Fatal('GridDataMapper',Message)213END IF214END DO215216!--- Both of the Names have been handled, so PrevGotIt can be updated for the next round (TOTAL_SIZE CORRECT)217! o If total_size < loop at the end(!) of loop, then there have been omissions; holds also for first round218! o Then, there must be no subsequent found parameters until the limit TOTAL; else there is a gap, which aborts immediately219! o NOTE: GotIt is not reliable enough for this check! F.ex. first name found, second not, would imply that nothing has been found.220IF ( total_size .EQ. loop ) THEN221PrevGotIt = .TRUE.222ELSE223PrevGotIt = .FALSE.224END IF225END DO226! Postcondition for the loops:227!< COORD_SIZE RIGHT: coord_size = |{ x | Exists "Coordinate Name 'x'" }| >228!< CONST_SIZE RIGHT: const_size = |{ x | Exists "NetCDF Constant 'x'" }| >229!< TOTAL_SIZE CORRECT: ( total_size = t .AND. (t = 0 .OR. (For Every i; 1 =< i <= t: Exists "Names 'i'")) .AND. ( .NOT. Exist i; t < i <= TOTAL: Exists "Names 'i'") >230!< NO DUPLICATES: ( .NOT. Exists i; 1 =< i <= TOTAL: Exists "NetCDF Constant 'i'" .AND. Exists "Coordinate name 'i'" ) >231232IF ( total_size .LE. 0 ) RETURN ! No strings found233234!--- Input checked and sizes counted; now allocation and data retrieval235236! Allocation237ALLOCATE ( Variables(coord_size),Constants(const_size),Permutation(total_size), STAT = alloc_stat )238IF ( alloc_stat .NE. 0 ) THEN239CALL Fatal('GridDataMapper','Memory ran out')240END IF241Permutation = 0242243! Getting the strings and the permutation data244var_i = 0245const_i = 0246DO loop = 1,total_size,1247!--- Pinpoint the correct type (correct until total_size)248IF ( IsVariable(loop) ) THEN249loop2 = 1 ! Variable/Coordinate250ELSE251loop2 = 2 ! Constant252END IF253254WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop) ,')'255WRITE(tmpStr,tmpFormat) TRIM(Names(loop2)),' ',loop256257!--- Puts the data of the Names(loop2) in the right place258IF ( IsVariable(loop) ) THEN259var_i = var_i + 1260Variables(var_i) = GetString( List,tmpStr,GotIt )261Permutation(var_i) = loop262ELSE263const_i = const_i + 1264Constants(const_i) = GetString( List,tmpStr,GotIt )265Permutation(coord_size + const_i) = loop266END IF267268IF ( .NOT. GotIt ) THEN269CALL Fatal('GridDataMapper','Obtained string did not exist after all')270END IF271END DO272!--- Permutation's contents:273! Range 1 <= i <= coord_size: variable i's location during the loop274! Range coord_size + 1 <= j <= total_size: constant j's location during the loop275! In other words, indexing Permutation gives the right NetCDF access location for the access parameter276277IF ( coord_size .GT. 0 ) Found(1) = .TRUE.278IF ( const_size .GT. 0 ) Found(2) = .TRUE.279280END SUBROUTINE GetNetCDFAccessParameters281282!----------------- ListGetStrings() -----------------283!--- Gets all strings defined with prefix "Name" and ending with " NR", where NR is a number in an array284SUBROUTINE ListGetStrings( List,Name,Found,CValues )285!----------------------------------------------------286USE DefUtils287IMPLICIT NONE288289!--- Arguments290TYPE(ValueList_t), INTENT(IN), POINTER :: List ! A pointer to a list of values291CHARACTER(LEN=*), INTENT(IN) :: Name ! Name of the SIF variable292LOGICAL, OPTIONAL, INTENT(INOUT) :: Found ! True, if found293CHARACTER(LEN=MAX_NAME_LEN), ALLOCATABLE :: CValues(:) ! For returned array data294295!--- Variables296TYPE(ValueList_t), POINTER :: ptr297CHARACTER(LEN=MAX_NAME_LEN) :: tmpStr298LOGICAL :: GotIt299INTEGER :: loop, amount, alloc_stat300CHARACTER(LEN=10) :: tmpFormat301302!--- Initializations303NULLIFY(ptr)304Found = .FALSE.305306! Count the amount of defined strings for allocation307amount = 0308loop = 1309GotIt = .TRUE.310DO WHILE (GotIt)311! Tries to ensure that the given integer doesn't have extra spaces before it in char format312! Scales until a number with a width of 9 (limited by tmpFormat)313WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop),')'314WRITE(tmpStr,tmpFormat) TRIM(Name),' ',loop315ptr => ListFind( List,tmpStr,GotIt )316317! WRITE(*,*) 'TEMP: ', tmpStr318319! Continues until first name is not found320IF (GotIt) THEN321IF (.NOT. ASSOCIATED(ptr)) THEN322GotIt = .FALSE.323RETURN324ELSE325amount = amount + 1326loop = loop + 1327END IF328END IF329END DO330331IF ( amount .LE. 0 ) RETURN ! No strings found332333! Allocation334ALLOCATE ( CValues(amount), STAT = alloc_stat )335IF ( alloc_stat .NE. 0 ) THEN336CALL Fatal('GridDataMapper','Memory ran out')337END IF338339! Getting the strings340DO loop = 1,amount,1341WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop) ,')'342WRITE(tmpStr,tmpFormat) TRIM(Name),' ',loop343CValues(loop) = GetString( List,tmpStr,GotIt )344IF (.NOT. GotIt) THEN345CALL Fatal('GridDataMapper','Obtained string did not exist after all')346END IF347END DO348349Found = .TRUE.350351END SUBROUTINE ListGetStrings352353END MODULE MapperUtils354355356