|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869 |
- module test_redis
-
- contains
- SUBROUTINE test()
- use RedisInterface
- use SimulationVariables
- use json_module
- use iso_c_binding, only: c_ptr, c_char, c_f_pointer,c_null_char,c_loc
- character(len=:),allocatable::s2
- character(len=:),allocatable::redisContent
- type(json_value),pointer :: jsonvalue
- type(json_core) :: jsoncore
- type(json_file) :: jsonfile
- type(json_core)::json
-
- type(c_ptr) :: c_string_ptr
- character(len=20) :: f_string
- character(kind=c_char, len=20),target,allocatable :: c_string
- integer :: i,len
- character(len=:),allocatable :: password,address,datakey
- integer::port,status
- integer :: string_shape(1)
- logical :: found
-
- address = "78.109.201.86"
- port = 6379
- password = "1qazxsw2$$"
- datakey = "37364875-c9cf-43a3-de45-08dc0c6103c9"
- status = 4
-
- call initConnection(address,port,password, datakey,status)
- print *,"redis exmaple program. status =",status
-
- allocate(character(len=20) :: c_string)
- c_string = 'Hello' // c_null_char
- c_string_ptr = c_loc(c_string)
- len=19
- call getData2_C(c_string_ptr,len)
- ! string_shape(1)=20
- ! call c_f_pointer(c_string_ptr, f_string, string_shape)
- ! f_string(1:len) = c_string(1:len)
- ! print *, "Fortran string: ", f_string(1:len)
-
- ! do i = 1, len
- ! print *, "Character at position ", i, ": ", f_string(i:i)
- ! end do
- call jsonfile%initialize()
- call jsonfile%deserialize(c_string(1:len))
- call jsonfile%get("status",status,found)
- print *,"Status = ",status
- call jsonfile%destroy()
- end SUBROUTINE
- end module test_redis
-
- program redis_example
- use test_redis
- call test()
- end program redis_example
-
-
- ! call jsoncore%create_object(jsonvalue,'')
- ! call ConfigurationToJson(jsonvalue)
- ! call WarningsToJson(jsonvalue)
- ! call ProblemsToJson(jsonvalue)
- ! print *,"write starts"
- ! call jsoncore%serialize(jsonvalue,redisContent)
- ! ! s = "Test redis write!"
- ! call setData(redisContent)
- ! print *,"write ends len=",len(redisContent)
|