MakePermUsingMask

Discussion about coding and new developments
suecook
Posts: 5
Joined: 11 Dec 2012, 14:51
Antispam: Yes

MakePermUsingMask

Post by suecook »

Hello,

We're trying to write a user function, and we would like to use an array for a particular variable only along one boundary. Reading some previous posts it seems like we could use MakePermUsingMask to read in the variable only along a particular boundary, but I can't find any examples of how to use it.

Does anyone know how I should call MakePermUsingMask inside my function? And how do I declare the mask name properly inside the Boundary Condition section of the sif file?

I hope this was clear, thanks for any help you can provide!

Sue
mzenker
Posts: 1999
Joined: 07 Dec 2009, 11:49
Location: Germany

Re: MakePermUsingMask

Post by mzenker »

Hi,

I don't know the answer, but I would do a search on "MakePermUsingMask" over the sources of ElmerSolver including all individual solvers to find out more ... ;)
They reside in trunc/fem/src (including subdirectory modules) in the Elmer source tree.

HTH,

Matthias
gagliar
Posts: 79
Joined: 04 Sep 2009, 16:34
Location: LGGE - Grenoble
Contact:

Re: MakePermUsingMask

Post by gagliar »

Hi Sue,

I don't know also about this MakePermUsingMask function. My understanding of your problem is that the user function is called for nodes belonging on a boundary but you need the variable value on an other boundary. Correct?

In the case these two boundaries are the upper and lower surfaces of your mesh, one possibility is to export in all the domain the variable so that you can access it from everywhere. This can be done using the ExportVertically solver in the Elmer/Ice package (http://elmerice.elmerfem.org/wiki/doku. ... vertically).

Hope it helps
Gag
suecook
Posts: 5
Joined: 11 Dec 2012, 14:51
Antispam: Yes

Re: MakePermUsingMask

Post by suecook »

Hello,

We managed to get what we needed working. For anyone wanting to use it in future here's what we did:

In the relevant boundary condition of the sif file, one line was added:

Code: Select all

MaskBoundary = Logical True
In the User Function we added:

Code: Select all

BoundaryName = "MaskBoundary"
CALL MakePermUsingMask(Model, Model%Solver,Model%Mesh,BoundaryName,.false.,BoundaryPerm,BoundaryNodes)
This produces BoundaryPerm, which gives a mask of all the nodes on the relevant boundary, and BoundaryNodes which is the total number of nodes on the boundary. To create an array containing values of a variable only on this boundary we then used this:

Code: Select all

! Read in all values of relevant variable, in this case depth
DepthVariable => VariableGet( Model % Variables, 'Depth' )
IF ( ASSOCIATED( DepthVariable ) ) THEN
    DepthPerm    => DepthVariable % Perm
    DepthValues  => DepthVariable % Values
ELSE
    CALL FATAL('MyUserFunction', 'Need Depth solver')
END IF

! Allocate space for new arrays
IF (allocated(dpt)) deallocate(dpt); allocate(dpt(BoundaryNodes))
IF (allocated(boundIndex)) deallocate(boundIndex); allocate(boundIndex(BoundaryNodes))

! Get node mapping
DO i=1,size(BoundaryPerm)
        IF (BoundaryPerm(i)/=0) boundIndex(BoundaryPerm(i))=i
END DO

! Create new array using only values on boundary
DO i=1,BoundaryNodes
       dpt(i) = DepthValues(DepthPerm(boundIndex(i)))
END DO
We have tested the method and it seems to work ok, so hope I hope it might be helpful to others too!

Thanks for the other useful advice on the topic :-)

Sue
Takala
Posts: 186
Joined: 23 Aug 2009, 23:59

Re: MakePermUsingMask

Post by Takala »

suecook wrote:Hello,

We managed to get what we needed working. For anyone wanting to use it in future here's what we did:

In the relevant boundary condition of the sif file, one line was added:

Code: Select all

MaskBoundary = Logical True
In the User Function we added:

Code: Select all

BoundaryName = "MaskBoundary"
CALL MakePermUsingMask(Model, Model%Solver,Model%Mesh,BoundaryName,.false.,BoundaryPerm,BoundaryNodes)
This produces BoundaryPerm, which gives a mask of all the nodes on the relevant boundary, and BoundaryNodes which is the total number of nodes on the boundary. To create an array containing values of a variable only on this boundary we then used this:

Code: Select all

! Read in all values of relevant variable, in this case depth
DepthVariable => VariableGet( Model % Variables, 'Depth' )
IF ( ASSOCIATED( DepthVariable ) ) THEN
    DepthPerm    => DepthVariable % Perm
    DepthValues  => DepthVariable % Values
ELSE
    CALL FATAL('MyUserFunction', 'Need Depth solver')
END IF

! Allocate space for new arrays
IF (allocated(dpt)) deallocate(dpt); allocate(dpt(BoundaryNodes))
IF (allocated(boundIndex)) deallocate(boundIndex); allocate(boundIndex(BoundaryNodes))

! Get node mapping
DO i=1,size(BoundaryPerm)
        IF (BoundaryPerm(i)/=0) boundIndex(BoundaryPerm(i))=i
END DO

! Create new array using only values on boundary
DO i=1,BoundaryNodes
       dpt(i) = DepthValues(DepthPerm(boundIndex(i)))
END DO
We have tested the method and it seems to work ok, so hope I hope it might be helpful to others too!

Thanks for the other useful advice on the topic :-)

Sue
I'm not really sure what you want to do. What I understand from your post is that you want to have an array that contain values of some boundary and you use that array to calculate something when for example dealing with some nodes that are not in that boundary.

If this is the case, then I think you should use a solver (instead of User Function) which gets the boundary values once, goes through all the points you want and do the calculations there and stores the result in the solver variable. Then you could say in sif:
SomeVariable = Equals SolverVariable
The reason is that now you are fetching, allocating and deallocating stuff every time you access the user function. This should be really slow when you increase the number of nodes.

Maybe I didn't get the point of what you are doing?

Cheers,

Eelis
ehooi
Posts: 156
Joined: 20 Aug 2013, 16:02
Antispam: Yes

Re: MakePermUsingMask

Post by ehooi »

suecook wrote:Hello,

We managed to get what we needed working. For anyone wanting to use it in future here's what we did:

In the relevant boundary condition of the sif file, one line was added:

Code: Select all

MaskBoundary = Logical True
In the User Function we added:

Code: Select all

BoundaryName = "MaskBoundary"
CALL MakePermUsingMask(Model, Model%Solver,Model%Mesh,BoundaryName,.false.,BoundaryPerm,BoundaryNodes)
This produces BoundaryPerm, which gives a mask of all the nodes on the relevant boundary, and BoundaryNodes which is the total number of nodes on the boundary. To create an array containing values of a variable only on this boundary we then used this:

Code: Select all

! Read in all values of relevant variable, in this case depth
DepthVariable => VariableGet( Model % Variables, 'Depth' )
IF ( ASSOCIATED( DepthVariable ) ) THEN
    DepthPerm    => DepthVariable % Perm
    DepthValues  => DepthVariable % Values
ELSE
    CALL FATAL('MyUserFunction', 'Need Depth solver')
END IF

! Allocate space for new arrays
IF (allocated(dpt)) deallocate(dpt); allocate(dpt(BoundaryNodes))
IF (allocated(boundIndex)) deallocate(boundIndex); allocate(boundIndex(BoundaryNodes))

! Get node mapping
DO i=1,size(BoundaryPerm)
        IF (BoundaryPerm(i)/=0) boundIndex(BoundaryPerm(i))=i
END DO

! Create new array using only values on boundary
DO i=1,BoundaryNodes
       dpt(i) = DepthValues(DepthPerm(boundIndex(i)))
END DO
We have tested the method and it seems to work ok, so hope I hope it might be helpful to others too!

Thanks for the other useful advice on the topic :-)

Sue
Hi Sue,
Thank you for sharing your codes with us. I am doing something similar where I have to loop over all boundary nodes to determine if the temperature is greater than a threshold to change my BC. I tried implementing your codes into my UDF but I am getting fundamental errors while compiling and this is due to variables like 'TempPerm' and 'TempValues' (your depthperm and depthvalues) not having implicit type. I tried declaring them as REAL but that doesn't work as I obtained error messages saying Pointer assignment to a non-Pointer.

So, I declared them in: TYPE(Variable_t), POINTER :: TempVariable,TempPerm,TempValues but that led to error of 'Different types in pointer assignment'. Do you know how I should declare these variables?

Thank you.


Best wishes,
EH
ehooi
Posts: 156
Joined: 20 Aug 2013, 16:02
Antispam: Yes

Re: MakePermUsingMask

Post by ehooi »

Hi,
I think I figured the problem out from my previous post. One thing I am not sure is when I run my programme, there is a warning that says Unlisted Keyword [maskboundary]. Do I have to include this in my SOLVER.KEYWORDS? If I do, is this the way of doing it:

BC:Logical: 'maskboundary'

Thanks.

Best wishes,
EH
mzenker
Posts: 1999
Joined: 07 Dec 2009, 11:49
Location: Germany

Re: MakePermUsingMask

Post by mzenker »

Yes.

Matthias
ehooi
Posts: 156
Joined: 20 Aug 2013, 16:02
Antispam: Yes

Re: MakePermUsingMask

Post by ehooi »

Hi Eelis,
I tried implementing Sue's code as a UDF and it is consuming a lot of time. In fact, for my first iteration, I get the following message:

Operating system error: Not enough space
Out of memory

I am surprise this happens because this is only the first time step and first iteration step.

Let me just describe what I plan to do:

I am solving a Joule Heating problem where I would like to specify the potential on a boundary that depends on the maximum boundary temperature. For instance, if the temperature at any node on the boundaries of the domain is greater than a value, say To, then the potential is given by V=Vo. Otherwise, it would just be V=0.

So I have in my SIF file:
!***************************************************************************************!
Boundary Condition 2
!***************************************************************************************!
Target Boundaries(12) = 5 6 7 8 9 11 12 13 14 15 16 17
Name = "ZeroFlux"
Heat Flux BC = True
Heat Flux = 0.0
! Potential = pot
MaskBoundary = Logical True
Potential = Variable time
Real Procedure "BCPOT" "BCPOT"
!***************************************************************************************!
End
!***************************************************************************************!

This was after intense search on how to use MakePermUsingMask and I finally successfully compiled it without error. Maybe MakePermUsingMask is not the optimal way of doing what I want but I can't seem to find another option.

You mentioned about writing a solver. I have no experience in that area but I guess I can convert the UDF to a solver quite straightforwardly. If I do that, how do I make the potential that I calculate with this solver visible when I prescribe my boundary condition.

My UDF so far, looks like this, although it may not be the optimum code:

Code: Select all

FUNCTION POT_BC(Model, n ,t) RESULT(pot)

!********************************************************************************!
! MODULE THAT INCLUDES WRAPPERS TO THE BASIC TASKS COMMON TO STANDARD SOLVERS
USE DefUtils

IMPLICIT None

!********************************************************************************!
! DECLARED AND DEFINED IN Types.src AND REFERENCED BY DefUtils 
! CONTAINS MESH AND ALL MODEL DATA SPECIFIED IN SOLVER INPUT FILE
TYPE(Model_t) :: Model
TYPE(Solver_t) :: Solver
TYPE(Mesh_t), POINTER :: Mesh
TYPE(Variable_t), POINTER :: TempVariable
INTEGER, POINTER :: BoundaryPerm(:), TempPerm(:)
REAL(KIND=dp), POINTER :: TempValues(:)
REAL(KIND=dp) :: pot, t, cont
REAL(KIND=dp), ALLOCATABLE :: localTemp(:)
INTEGER, ALLOCATABLE :: boundIndex(:)
INTEGER :: i, N, BoundaryNodes, ss
CHARACTER(LEN=12) :: BoundaryName

!********************************************************************************!
! ACCESS BOUNDARY ONLY ELEMENTS USING MakePermUsingMask
Mesh => Model % Mesh
!if (.FALSE.) then
	N = Mesh % NumberOfNodes
	ALLOCATE(BoundaryPerm(N))
	BoundaryPerm = 0
	BoundaryNodes = 0
	BoundaryName = 'MaskBoundary'
	CALL MakePermUsingMask(Model,Model%Solver,Model%Mesh,BoundaryName,.FALSE.,BoundaryPerm,BoundaryNodes)
!end if

!********************************************************************************!	
! READ IN ALL VALUES OF RELEVANT VARIABLE (TEMPERATURE)
TempVariable => VariableGet( Model % Variables, 'Temperature' )
IF ( ASSOCIATED( TempVariable ) ) THEN
    TempPerm    => TempVariable % Perm
    TempValues  => TempVariable % Values
ELSE
    CALL FATAL('POT_BC', 'Need Temperature solver')
END IF

!********************************************************************************!
! ALLOCATE SPACE FOR NEW ARRAYS Allocate space for new arrays
IF (allocated(localTemp)) deallocate(localTemp); allocate(localTemp(BoundaryNodes))
IF (allocated(boundIndex)) deallocate(boundIndex); allocate(boundIndex(BoundaryNodes))


! GET NODE MAPPING
DO i = 1,size(BoundaryPerm)
    IF (BoundaryPerm(i)/=0) boundIndex(BoundaryPerm(i))=i
END DO


! CREATE NEW ARRAY USING ONLY VALUES ON THE BOUNDARY
DO i = 1,BoundaryNodes
     localTemp(i) = TempValues(TempPerm(boundIndex(i)))
END DO
!pause

!write(*,*) localTemp(BoundaryNodes), BoundaryNodes
!pause

!********************************************************************************!
! RUN DO WHILE LOOP
cont = -10; i = 0; 
DO WHILE  (cont < 0)
	i = i + 1
	if (localTemp(i) > 373) then
		pot = 25
		cont = 10
		GO TO 10
	else
		if (i == BoundaryNodes) then
			cont = 10
			pot = 30
		end if
	end if
END DO

10 CONTINUE

END FUNCTION POT_BC
Can anyone help?

Thanks.

Best wishes,
EH












Takala wrote:
suecook wrote:Hello,

We managed to get what we needed working. For anyone wanting to use it in future here's what we did:

In the relevant boundary condition of the sif file, one line was added:

Code: Select all

MaskBoundary = Logical True
In the User Function we added:

Code: Select all

BoundaryName = "MaskBoundary"
CALL MakePermUsingMask(Model, Model%Solver,Model%Mesh,BoundaryName,.false.,BoundaryPerm,BoundaryNodes)
This produces BoundaryPerm, which gives a mask of all the nodes on the relevant boundary, and BoundaryNodes which is the total number of nodes on the boundary. To create an array containing values of a variable only on this boundary we then used this:

Code: Select all

! Read in all values of relevant variable, in this case depth
DepthVariable => VariableGet( Model % Variables, 'Depth' )
IF ( ASSOCIATED( DepthVariable ) ) THEN
    DepthPerm    => DepthVariable % Perm
    DepthValues  => DepthVariable % Values
ELSE
    CALL FATAL('MyUserFunction', 'Need Depth solver')
END IF

! Allocate space for new arrays
IF (allocated(dpt)) deallocate(dpt); allocate(dpt(BoundaryNodes))
IF (allocated(boundIndex)) deallocate(boundIndex); allocate(boundIndex(BoundaryNodes))

! Get node mapping
DO i=1,size(BoundaryPerm)
        IF (BoundaryPerm(i)/=0) boundIndex(BoundaryPerm(i))=i
END DO

! Create new array using only values on boundary
DO i=1,BoundaryNodes
       dpt(i) = DepthValues(DepthPerm(boundIndex(i)))
END DO
We have tested the method and it seems to work ok, so hope I hope it might be helpful to others too!

Thanks for the other useful advice on the topic :-)

Sue
I'm not really sure what you want to do. What I understand from your post is that you want to have an array that contain values of some boundary and you use that array to calculate something when for example dealing with some nodes that are not in that boundary.

If this is the case, then I think you should use a solver (instead of User Function) which gets the boundary values once, goes through all the points you want and do the calculations there and stores the result in the solver variable. Then you could say in sif:
SomeVariable = Equals SolverVariable
The reason is that now you are fetching, allocating and deallocating stuff every time you access the user function. This should be really slow when you increase the number of nodes.

Maybe I didn't get the point of what you are doing?

Cheers,

Eelis
raback
Site Admin
Posts: 4812
Joined: 22 Aug 2009, 11:57
Antispam: Yes
Location: Espoo, Finland
Contact:

Re: MakePermUsingMask

Post by raback »

Hi

I edited roughly how I might do this. Didn't test or tidy up at all so errors are probable but the basic idea might work.

-Peter

Code: Select all

FUNCTION POT_BC(Model, n ,t) RESULT(pot)

!********************************************************************************!
! MODULE THAT INCLUDES WRAPPERS TO THE BASIC TASKS COMMON TO STANDARD SOLVERS
USE DefUtils

IMPLICIT None

!********************************************************************************!
! DECLARED AND DEFINED IN Types.src AND REFERENCED BY DefUtils 
! CONTAINS MESH AND ALL MODEL DATA SPECIFIED IN SOLVER INPUT FILE
TYPE(Model_t) :: Model
TYPE(Solver_t) :: Solver
TYPE(Mesh_t), POINTER :: Mesh
TYPE(Variable_t), POINTER :: TempVariable
INTEGER, POINTER :: BoundaryPerm(:), TempPerm(:)
REAL(KIND=dp), POINTER :: TempValues(:)
REAL(KIND=dp) :: pot, t, cont, tmax
REAL(KIND=dp), ALLOCATABLE :: localTemp(:)
INTEGER, ALLOCATABLE :: boundIndex(:)
INTEGER :: i, N, BoundaryNodes, ss
CHARACTER(LEN=12) :: BoundaryName
LOGICAL :: AllocationsDone = .FALSE.
INTEGER :: CoupledIter,PrevCoupledIter=-1

SAVE AllocationdDone, BoundaryPerm, BoundaryNodes, TempPerm, TempValues, DoneTime, &
  CoupledIter, PrevCoupledIter, tmax

!********************************************************************************!
! ACCESS BOUNDARY ONLY ELEMENTS USING MakePermUsingMask
IF (.NOT. AllocationsDone) then
   Mesh => Model % Mesh
   N = Mesh % NumberOfNodes
   ALLOCATE(BoundaryPerm(N))
   BoundaryPerm = 0
   BoundaryNodes = 0
   BoundaryName = 'MaskBoundary'
   CALL MakePermUsingMask(Model,Model%Solver,Model%Mesh,BoundaryName,.FALSE.,BoundaryPerm,BoundaryNodes)

  ! READ IN ALL VALUES OF RELEVANT VARIABLE (TEMPERATURE)
  TempVariable => VariableGet( Model % Variables, 'Temperature' )
  IF ( ASSOCIATED( TempVariable ) ) THEN
    TempPerm    => TempVariable % Perm
    TempValues  => TempVariable % Values
  ELSE
    CALL FATAL('POT_BC', 'Need Temperature solver')
  END IF
  AllocationsDone = .TRUE.
END IF

! get max temperature
! Get the max temperature only when going to the next coupled system iteration when the 
! temperature could have changed. This saves some time. 
CoupledIter = GetCoupledIter()
IF( CoupledIter /= PrevCoupledIter ) THEN
  PrevCoupledIter = CoupledIter
  tmax = -HUGE(tmax)
  DO i = 1,size(BoundaryPerm)
      IF (BoundaryPerm(i) /=0 ) THEN
         tmax = MAX(tmax, TempValues(TempPerm(i))
      END IF
  END DO
  print *,'tmax = ',tmax
END IF

! the function depending on tmax
  IF( tmax > 1.23 ) THEN 
    pot = 4.56_dp
  ELSE
    pot = 0.0_dp
  END IF
 
END FUNCTION POT_BC
Post Reply