Building Controls Virtual Test Bed
f90client.f90
Go to the documentation of this file.
1 program first
2 ! Note: This program uses fixed array size.
3 ! Variable array size (using ALLOCATE) do not work: The c
4 ! function only gets a value of 0 for all elements.
5 ! This is also the case if a fortran pointer is passed as an argument
6 ! instead of the array itself.
7 
8  IMPLICIT NONE
9 
10  ! These parameters are also declared in an interface below.
11  ! Change all together.
12  INTEGER, PARAMETER :: ndblmax = 2 ! Maximum number of doubles
13 
14  interface
15  function establishclientsocket(fileName)
16  CHARACTER(len=*) :: filename ! file from which socket port number will be read
17  INTEGER establishclientsocket ! socket file descriptor
18  end function establishclientsocket
19  end interface
20 
21  interface
22  function exchangedoubleswithsocket( socketFD, &
23  flawri, flarea, &
24  ndblwri, ndblrea, &
25  simtimwri, dblvalwri, &
26  simtimrea, dblvalrea)
27  ! These parameters are also declared in an interface below.
28  ! Change all together.
29  INTEGER, PARAMETER :: ndblmax = 2 ! Maximum number of doubles
30 
31  INTEGER socketfd ! socket file descriptor
32 
33  INTEGER flawri ! flag to write to the socket
34  INTEGER flarea ! flag read from the socket
35 
36  INTEGER ndblwri ! number of doubles to write to socket
37  INTEGER ndblrea ! number of doubles to read from socket
38 
39  DOUBLE PRECISION simtimwri ! simulation time to write to socket
40  ! if ':' instead of '2' is specified, then 1.7042624463E-313 is exchanged.
41  DOUBLE PRECISION, DIMENSION(nDblMax) :: dblvalwri
42 
43  DOUBLE PRECISION simtimrea ! simulation time to read from socket
44  DOUBLE PRECISION, DIMENSION(nDblMax) :: dblvalrea
46  end function exchangedoubleswithsocket
47  end interface
48 
49  interface
50  function closesocket(socketFD)
51  INTEGER socketfd ! socket file descriptor
52  INTEGER closesocket
53  end function closesocket
54  end interface
55 
56 
57 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
58 ! Declarations for room model
59  INTEGER, PARAMETER :: nroo = 2 ! Number of rooms
60  DOUBLE PRECISION :: tini ! Initial room temperature
61  DOUBLE PRECISION :: tau ! Room time constant
62  DOUBLE PRECISION :: q0hea ! Nominal heating power
63  DOUBLE PRECISION :: deltim ! Time step
64  DOUBLE PRECISION :: ua ! UA value
65  DOUBLE PRECISION :: tout ! current outside temperature
66  DOUBLE PRECISION :: simtimrea ! simulation time read from the socket
67  DOUBLE PRECISION :: simtim ! current simulation time
68 
69 
70  DOUBLE PRECISION, DIMENSION(nRoo) :: c ! Room heat capacity
71  DOUBLE PRECISION, DIMENSION(nRoo) :: u ! control signal
72  DOUBLE PRECISION, DIMENSION(nRoo) :: troo ! current room temperature
73 
74 
75 
76 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
77 ! Declarations for IPC
78  CHARACTER(len=*), PARAMETER :: simcfgfilnam="socket.cfg"
79  INTEGER portno
80  INTEGER i
81  INTEGER retval
82  INTEGER socketfd
83  INTEGER flawri, flarea
84  INTEGER ndblwri
85  INTEGER ndblrea
86  DOUBLE PRECISION, DIMENSION(nDblMax) :: dblvalwri
87  DOUBLE PRECISION, DIMENSION(nDblMax) :: dblvalrea
88 
89 ! Buffer for the command line argument
90  CHARACTER *100 buffer
91 
92 ! Get the command line argument
93  IF ( iargc() .LT. 1 ) THEN
94  WRITE(*,*) "Error: Wrong arguments in client"
95  WRITE(*,*) "Usage: programName simulationTimeStepInSeconds"
96  stop
97  ENDIF
98 
99  CALL getarg(1,buffer)
100  READ(buffer,*) deltim
101  WRITE(*,'(A, G10.3)') "Simulator set time step to ", deltim
102 
103 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
104 ! Initializations
105  OPEN (unit=11,file='client.log', status='replace', action='write')
106 
107 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
108 ! Declare how many variables are written and read
109  ndblwri= nroo
110  ndblrea= nroo
111  flawri = 0
112  flarea = 0
113 
114 ! Initialize room variables
115  tini = 10
116  tau = 2*3600
117  q0hea = 100
118  ua = q0hea / 20
119  c(1) = tau * ua
120  c(2) = 2*tau * ua
121 
122  troo = tini
123  tout = 5
124 
125  simtim = 0
126 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
127 ! Do time stepping
128  write(11,*) "*** Starting simulation"
129 ! Open socket
130  socketfd = establishclientsocket(simcfgfilnam)
131 !!stop 'manual exit'
132  write(11, *) "Socket file descriptor = ", socketfd
133  IF (socketfd .LT. 0) THEN
134  write(*, *) "Error: Could not open socket."
135  write(11, *) "Error: Could not open socket."
136  close(11)
137  stop
138  END IF
139 
140  simulate: DO
141 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
142 ! Fill arrays for IPC
143 
144  DO i=1,nroo
145  dblvalwri(i)=troo(i)
146  END DO
147  ! Exchange data
148  retval = exchangedoubleswithsocket(socketfd, &
149  flawri, flarea, &
150  ndblwri, ndblrea, &
151  simtim, dblvalwri, &
152  simtimrea, dblvalrea)
153  ! Check for errors, in which case we terminate the simulation loop
154  IF (retval .NE. 0) THEN
155  write(*, *) "Error: Received retVal = ", retval
156  write(11,*) "Error: Received retVal = ", retval
157  EXIT simulate
158  END IF
159  ! Check communication flag
160  IF (flarea .NE. 0) THEN
161  write(*, *) "Received end of simulation flag = ", flarea
162  write(*, *) "Exit simulation."
163  write(11,*) "Received end of simulation flag = ", flarea
164  write(11,*) "Exit simulation."
165  EXIT simulate
166  END IF
167 
168  ! No errors found. Assign exchanged variables
169  DO i=1,nroo
170  u(i) = dblvalrea(i)
171  END DO
172 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
173 ! Having obtained y_k, we compute the new state x_k+1 = f(u_k)
174 ! This is the actual simulation time step of the client
175  DO i=1,nroo
176  troo(i) = troo(i) + &
177  deltim/c(i) * ( ua * (tout-troo(i) ) + q0hea * u(i) )
178  END DO
179  simtim = simtim + deltim
180  END DO simulate
181 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
182  write(11,*) "*** Ending simulation"
183  close(11)
184  close(socketfd)
185 end program
int exchangedoubleswithsocket(const int *sockfd, const int *flaWri, int *flaRea, const int *nDblWri, int *nDblRea, double *simTimWri, double dblValWri[], double *simTimRea, double dblValRea[])
Exchanges data with the socket.
for i
Definition: compile.m:69
int establishclientsocket(const char *const docname)
Establishes a connection to the socket.
program first
Definition: f90client.f90:1
FSCHANGE is a Mathworks internal function that is used for troubleshooting purposes It takes the name of a directory as an input and forces the MATLAB path manager to recheck the contents of the directory to check for windows have Windows c
Definition: compile.m:89