Simulation Core
Nelze vybrat více než 25 témat Téma musí začínat písmenem nebo číslem, může obsahovat pomlčky („-“) a může být dlouhé až 35 znaků.
 
 
 
 
 
 

70 řádky
2.1 KiB

  1. module test_redis
  2. contains
  3. SUBROUTINE test()
  4. use RedisInterface
  5. use SimulationVariables
  6. use json_module
  7. use iso_c_binding, only: c_ptr, c_char, c_f_pointer,c_null_char,c_loc
  8. character(len=:),allocatable::s2
  9. character(len=:),allocatable::redisContent
  10. type(json_value),pointer :: jsonvalue
  11. type(json_core) :: jsoncore
  12. type(json_file) :: jsonfile
  13. type(json_core)::json
  14. type(c_ptr) :: c_string_ptr
  15. character(len=20) :: f_string
  16. character(kind=c_char, len=20),target,allocatable :: c_string
  17. integer :: i,len
  18. character(len=:),allocatable :: password,address,datakey
  19. integer::port,status
  20. integer :: string_shape(1)
  21. logical :: found
  22. address = "78.109.201.86"
  23. port = 6379
  24. password = "1qazxsw2$$"
  25. datakey = "37364875-c9cf-43a3-de45-08dc0c6103c9"
  26. status = 4
  27. call initConnection(address,port,password, datakey,status)
  28. print *,"redis exmaple program. status =",status
  29. allocate(character(len=20) :: c_string)
  30. c_string = 'Hello' // c_null_char
  31. c_string_ptr = c_loc(c_string)
  32. len=19
  33. call getData2_C(c_string_ptr,len)
  34. ! string_shape(1)=20
  35. ! call c_f_pointer(c_string_ptr, f_string, string_shape)
  36. ! f_string(1:len) = c_string(1:len)
  37. ! print *, "Fortran string: ", f_string(1:len)
  38. ! do i = 1, len
  39. ! print *, "Character at position ", i, ": ", f_string(i:i)
  40. ! end do
  41. call jsonfile%initialize()
  42. call jsonfile%deserialize(c_string(1:len))
  43. call jsonfile%get("status",status,found)
  44. print *,"Status = ",status
  45. call jsonfile%destroy()
  46. end SUBROUTINE
  47. end module test_redis
  48. program redis_example
  49. use test_redis
  50. call test()
  51. end program redis_example
  52. ! call jsoncore%create_object(jsonvalue,'')
  53. ! call ConfigurationToJson(jsonvalue)
  54. ! call WarningsToJson(jsonvalue)
  55. ! call ProblemsToJson(jsonvalue)
  56. ! print *,"write starts"
  57. ! call jsoncore%serialize(jsonvalue,redisContent)
  58. ! ! s = "Test redis write!"
  59. ! call setData(redisContent)
  60. ! print *,"write ends len=",len(redisContent)