Commit 7c2192bb authored by Takhir Fakhrutdinov's avatar Takhir Fakhrutdinov

Инициализация репозитория

parent e05bedd4
*
!.gitignore
!makefile
!readme.md
!Makefile
!include/
!fson/
PLATFORM=$(shell uname -s |awk -F- '{print $$1}')
SRC=src
LIB=../build/$(PLATFORM)/lib
BUILD=../build/$(PLATFORM)/obj/json
TEST=../build/$(PLATFORM)/test
MODDIR=../build/$(PLATFORM)/mod
F95=.f95
OBJ=.o
FC = gfortran
FCFLAGS = -O2 -fbounds-check -O -Wall
FCFLAGS += $(FCEXTRA)
FMFLAGS = -J$(MODDIR)
ifeq ($(PLATFORM),$(filter $(PLATFORM),Darwin Linux))
LDFLAGS=-lsofa -L$(LIB)
else
LDFLAGS = -lfson -L$(LIB) -rpath /usr/local/lib/gcc48
endif
LDFLAGS += $(FCEXTRA)
AR = ar
ARFLAGS= ru
ifeq ($(PLATFORM),MINGW32_NT)
EXE=.exe
LIBTARGET=$(LIB)/libfson.a
else
EXE=
# FCFLAGS += -fPIC
ifeq ($(PLATFORM),Darwin)
LIBTARGET=$(LIB)/libfson.a
else
LIBTARGET=$(LIB)/libfson.a
endif
endif
# "make" builds all
all: dirs lib
dirs:
mkdir -p $(LIB) $(BUILD) $(TEST) $(MODDIR)
# List of example programs
EXAMPLES = basic example1
RMEXAS = $(patsubst %, $(TEST)/%$(EXE), $(EXAMPLES))
RMEXASD = $(patsubst %, $(TEST)/%$(EXE).dSym, $(EXAMPLES))
examples: $(patsubst %, $(TEST)/%$(EXE), $(EXAMPLES)) json
JSON = $(shell find src/test -name '*.json')
RMJ = $(patsubst $(SRC)/test%, $(TEST)%, $(JSON))
json: $(patsubst $(SRC)/test%, $(TEST)%, $(JSON))
FSON = fson_string_m fson_value_m fson_path_m fson
OBJECTS = $(patsubst %, $(BUILD)/%.o, $(FSON))
MODS = $(patsubst %, $(MODDIR)/%.mod, $(FSON))
lib: $(LIBTARGET)
$(LIBTARGET) : $(OBJECTS)
$(AR) $(ARFLAGS) $(LIBTARGET) $(OBJECTS)
$(TEST)%.json : $(SRC)/test%.json
cp -f $< $@
#$(LIB)%$(EXE) : $(BUILD)/%$(OBJ) $(OBJECTS)
# $(FC) $(FCFLAGS) -o $@ $^ $(LDFLAGS)
$(TEST)%$(EXE) : $(SRC)/test%$(F95)
$(FC) $(FCFLAGS) -o $@ $^ $(LDFLAGS) $(FMFLAGS)
$(BUILD)/%$(OBJ): $(SRC)/%$(F95)
$(FC) $(FCFLAGS) $(FMFLAGS) -c $< -o $@
test:
$(info test fson...)
clean:
rm -rf $(OBJECTS) $(LIBTARGET) $(MODS) $(RMEXAS) $(RMEXASD) $(RMJ)
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
! FSON MODULE
!
! File: fson.f95
! Author: Joseph A. Levin
!
! Created on March 6, 2012, 7:48 PM
!
module fson
use fson_value_m, fson_print => fson_value_print, fson_destroy => fson_value_destroy, fson_pretty => fson_value_print_pretty
use fson_string_m
use fson_path_m, fson_get => fson_path_get
implicit none
private
public :: fson_parse, fson_value, fson_get, fson_print, fson_destroy, fson_pretty
! FILE IOSTAT CODES
integer, parameter :: end_of_file = -1
integer, parameter :: end_of_record = -2
! PARSING STATES
integer, parameter :: STATE_LOOKING_FOR_VALUE = 1
integer, parameter :: STATE_IN_OBJECT = 2
integer, parameter :: STATE_IN_PAIR_NAME = 3
integer, parameter :: STATE_IN_PAIR_VALUE = 4
! POP/PUSH CHARACTER
integer :: pushed_index = 0
! fte changed
character (len = 100) :: pushed_char
contains
!
! FSON PARSE
!
function fson_parse(file, unit) result(p)
type(fson_value), pointer :: p
integer, optional, intent(in) :: unit
character(len = *), intent(in) :: file
logical :: unit_available
integer :: u
! init the pointer to null
nullify(p)
! select the file unit to use
if (present(unit)) then
u = unit
else
! find the first available unit
unit_available = .false.
u = 20
do while (.not.unit_available)
inquire(unit = u, exist = unit_available)
u = u + 1
enddo
endif
! fte changed....
if( u.ne.5 ) then
! open the file
open (unit = u, file = file, status = "old", action = "read", form = "formatted", position = "rewind")
endif
! create the value and associate the pointer
p => fson_value_create()
! parse as a value
call parse_value(unit = u, value = p)
! close the file
if( .not. present(unit)) then
! fte changed
if( u.ne.5 ) then
close (u)
endif
endif
end function fson_parse
!
! PARSE_VALUE
!
recursive subroutine parse_value(unit, value)
integer, intent(inout) :: unit
type(fson_value), pointer :: value
logical :: eof
character :: c
! for some unknown reason the next pointer is getting messed with the pop
type(fson_value), pointer :: hack
! start the hack
hack => value % next
! pop the next non whitespace character off the file
c = pop_char(unit, eof = eof, skip_ws = .true.)
! finish the hack; set the next pointer to whatever it was before the pop
value % next => hack
if (eof) then
return
else
select case (c)
case ("{")
! start object
value % value_type = TYPE_OBJECT
call parse_object(unit, value)
case ("[")
! start array
value % value_type = TYPE_ARRAY
call parse_array(unit, value)
case ("]")
call push_char(c)
! end an empty array
nullify(value)
case ('"')
! string
value % value_type = TYPE_STRING
value % value_string => parse_string(unit)
case ("t")
!true
value % value_type = TYPE_LOGICAL
call parse_for_chars(unit, "rue")
value % value_logical = .true.
case ("f")
!false
value % value_type = TYPE_LOGICAL
value % value_logical = .false.
call parse_for_chars(unit, "alse")
case ("n")
value % value_type = TYPE_NULL
call parse_for_chars(unit, "ull")
case("-","+", "0": "9")
call push_char(c)
call parse_number(unit, value)
case default
write(0,*) "ERROR: Unexpected character while parsing value. '", c, "' ASCII=", iachar(c)
call exit (1)
end select
endif
end subroutine parse_value
!
! PARSE OBJECT
!
recursive subroutine parse_object(unit, parent)
integer, intent(inout) :: unit
type(fson_value), pointer :: parent, pair
logical :: eof
character :: c
! pair name
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing start of object."
call exit (1)
else if ("}" == c) then
! end of an empty object
return
else if ('"' == c) then
pair => fson_value_create()
pair % name => parse_string(unit)
else
write(0,*) "ERROR: Expecting string: '", c, "'"
call exit (1)
endif
! pair value
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing object member. 1"
call exit (1)
else if (":" == c) then
! parse the value
call parse_value(unit, pair)
call fson_value_add(parent, pair)
else
write(0,*) "ERROR: Expecting : and then a value. ", c
call exit (1)
endif
! another possible pair
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
return
else if ("," == c) then
! read the next member
call parse_object(unit = unit, parent = parent)
else if ("}" == c) then
return
else
write(0,*) "ERROR: Expecting end of object.", c
call exit (1)
endif
end subroutine parse_object
!
! PARSE ARRAY
!
subroutine parse_array(unit, array)
integer, intent(inout) :: unit
type(fson_value), pointer :: array, element
logical :: eof
character :: c
do
! try to parse an element value
element => fson_value_create()
call parse_value(unit, element)
if(associated(element)) then
call fson_value_add(array, element)
endif
! popped the next character
c = pop_char(unit, eof = eof, skip_ws = .true.)
if(eof) exit
if("," == c) cycle
exit
enddo
end subroutine parse_array
!
! PARSE STRING
!
function parse_string(unit) result(string)
integer, intent(inout) :: unit
type(fson_string), pointer :: string
logical :: eof
character :: c, last
last=' '
string => fson_string_create()
do
c = pop_char(unit, eof = eof, skip_ws = .false.)
if (eof) then
write(0,*) "Expecting end of string"
call exit(1)!
else if ('"' == c .and. last .ne. '\') then
exit
else
last = c
call fson_string_append(string, c)
endif
enddo
end function parse_string
!
! PARSE FOR CHARACTERS
!
subroutine parse_for_chars(unit, chars)
integer, intent(inout) :: unit
character(len = *), intent(in) :: chars
integer :: i, length
logical :: eof
character :: c
length = len_trim(chars)
do i = 1, length
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing array."
call exit (1)
else if (c .ne. chars(i:i)) then
write(0,*) "ERROR: Unexpected character.'", c,"'", chars(i:i)
call exit (1)
endif
enddo
end subroutine parse_for_chars
!
! PARSE NUMBER
!
subroutine parse_number(unit, value)
integer, intent(inout) :: unit
type(fson_value), pointer :: value
logical :: eof, negative, decimal, scientific, exp_negative
character :: c
integer*8 :: exp
! fte changed
integer*8 :: integral
double precision :: frac
! first character is either - or a digit
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing number.(1)"
call exit (1)
endif
negative = .false.
if ( "-" == c ) then
negative = .true.
else if( "+" .ne. c ) then
call push_char(c)
endif
! parse the integral
integral = parse_integer(unit)
decimal = .false.
scientific = .false.
exp_negative = .false.
exp = 1
frac = 0
do
! first character is either - or a digit
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing number.(2)"
call exit (1)
else
select case (c)
case (".")
! this is already fractional number
if (decimal) then
! already found a decimal place
write(0,*) "ERROR: Unexpected second decimal place while parsing number."
call exit(1)
endif
decimal = .true.
frac = parse_dblefrac(unit)
case ("e", "E")
! this is already an exponent number
if (scientific) then
! already found a e place
write(0,*) "ERROR: Unexpected second exponent while parsing number."
call exit(1)
endif
scientific = .true.
! check sign of exponent
! first character is either - or a digit
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing number.(3)"
call exit (1)
endif
if ( "-" == c ) then
exp_negative = .true.
else if( "+" .ne. c ) then
call push_char(c)
endif
! this number has an exponent
exp = parse_integer(unit)
case default
! this is a real
if (decimal .or. scientific) then
! add the integral
frac = frac + integral
if (scientific) then
! apply exponent
if ( exp_negative ) then
frac = frac * (0.1D00 ** exp)
else
frac = frac * (1.0D01 ** exp)
endif
endif
! apply negative
if (negative) then
frac = frac * (-1)
endif
value % value_type = TYPE_REAL
value % value_real = frac
else
! this is a integer
! apply negative
if (negative) then
integral = integral * (-1)
endif
value % value_type = TYPE_INTEGER
value % value_integer = integral
endif
call push_char(c)
exit
endselect
endif
enddo
end subroutine
!
! PARSE INTEGER
!
! fte changed
integer*8 function parse_integer(unit) result(integral)
integer, intent(inout) :: unit
logical :: eof
character :: c
integer :: tmp, count
count = 0
integral = 0
do
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing digit."
call exit (1)
else
select case(c)
case ("0":"9")
! digit
read (c, '(i1)') tmp
! shift
if (count > 0) then
integral = integral * 10
endif
! add
integral = integral + tmp
! increase the count
count = count + 1
case default
call push_char(c)
return
endselect
endif
enddo
end function parse_integer
!
! PARSE DOUBLE FRACTION
!
! fte changed
real*8 function parse_dblefrac(unit) result(integral)
integer, intent(inout) :: unit
logical :: eof
character :: c
integer :: tmp
real(8) :: fexp
integral = 0.0D00
fexp = 1.0D00
do
c = pop_char(unit, eof = eof, skip_ws = .true.)
if (eof) then
write(0,*) "ERROR: Unexpected end of file while parsing digit."
call exit (1)
else
select case(c)
case ("0":"9")
! digit
read (c, '(i1)') tmp
! shift
fexp = fexp * 0.1D00
integral = integral + dble(tmp)*fexp
case default
call push_char(c)
return
endselect
endif
enddo
end function parse_dblefrac
!
! POP CHAR
!
recursive character function pop_char(unit, eof, skip_ws) result(popped)
integer, intent(inout) :: unit
logical, intent(out) :: eof
logical, intent(in), optional :: skip_ws
integer :: ios
character :: c
logical :: ignore
eof = .false.
if (.not.present(skip_ws)) then
ignore = .false.
else
ignore = skip_ws
endif
do
if (pushed_index > 0) then
! there is a character pushed back on, most likely from the number parsing
c = pushed_char(pushed_index:pushed_index)
pushed_index = pushed_index - 1
! fte changed
popped = c
exit
else
read (unit = unit, fmt = "(a)", advance = "no", iostat = ios) c
endif
if (ios == end_of_record) then
cycle
else if (ios == end_of_file) then
eof = .true.
exit
else if (iachar(c) < 32) then
! non printing ascii characters
cycle
else if (ignore .and. c == " ") then
cycle
else
popped = c
exit
endif
enddo
end function pop_char
!
! PUSH CHAR
!
subroutine push_char(c)
character, intent(inout) :: c
pushed_index = pushed_index + 1
pushed_char(pushed_index:pushed_index) = c
end subroutine push_char
end module fson
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
!
! File: fson_path_m.f95
! Author: Joseph A. Levin
!
! Created on March 10, 2012, 11:01 PM
!
module fson_path_m
use fson_value_m
use fson_string_m
private
public :: fson_path_get, array_callback
interface fson_path_get
module procedure get_by_path
module procedure get_integer
! fte changed
module procedure get_bigint
module procedure get_real
module procedure get_double
module procedure get_logical
module procedure get_chars
module procedure get_array
end interface fson_path_get
contains
!
! GET BY PATH
!
! $ = root
! @ = this
! . = child object member
! [] = child array element
!
recursive subroutine get_by_path(this, path, p)
type(fson_value), pointer :: this, p
!fte chaged
character(len=*) :: path
integer :: i, length, child_i
character :: c
logical :: array
! default to assuming relative to this
p => this
child_i = 1
array = .false.
length = len_trim(path)
do i=1, length
c = path(i:i)
select case (c)
case ("$")
! root
do while (associated (p % parent))
p => p % parent
enddo
child_i = i + 1
case ("@")
! this
p => this
child_i = i + 1
case (".")
! get child member from p
if (child_i < i) then
p => fson_value_get(p, path(child_i:i-1))
else
child_i = i + 1
cycle
endif
if(.not.associated(p)) then
return
endif
child_i = i+1
case ("[")
! start looking for the array element index
array = .true.
child_i = i + 1
case ("]")
if (.not.array) then
write(0,*) "ERROR: Unexpected ], not missing preceding ["
call exit(1)
endif
array = .false.
child_i = parse_integer(path(child_i:i-1))
p => fson_value_get(p, child_i)
child_i= i + 1
endselect
enddo
! grab the last child if present in the path
if (child_i <= length) then
p => fson_value_get(p, path(child_i:i-1))
if(.not.associated(p)) then
return
else
endif
endif
end subroutine get_by_path
!
! PARSE INTEGER
!
integer function parse_integer(chars) result(integral)
character(len=*) :: chars
character :: c
integer :: tmp, i
integral = 0
do i=1, len_trim(chars)
c = chars(i:i)
select case(c)
case ("0":"9")
! digit
read (c, '(i1)') tmp
! shift
if(i > 1) then
integral = integral * 10
endif
! add
integral = integral + tmp
case default
return
endselect
enddo
end function parse_integer
!
! GET INTEGER
!
subroutine get_integer(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
integer :: value
integer, optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_integer : Unable to resolve path: ", path
call exit(1)
else
value = def
return
endif
endif
if(p % value_type == TYPE_INTEGER) then
value = INT(p % value_integer)
else if (p % value_type == TYPE_REAL) then
value = INT(p % value_real)
else if (p % value_type == TYPE_LOGICAL) then
if (p % value_logical) then
value = 1
else
value = 0
endif
else
write(0,*) "get_integer : Unable to resolve value to integer: ", path
call exit(1)
endif
end subroutine get_integer
!
! GET BIGINT
!
subroutine get_bigint(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
integer*8 :: value
integer*8, optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_bigint : Unable to resolve path: ", path
call exit(1)
else
value = def
return
endif
endif
if(p % value_type == TYPE_INTEGER) then
value = INT8(p % value_integer)
else if (p % value_type == TYPE_REAL) then
value = INT8(p % value_real)
else if (p % value_type == TYPE_LOGICAL) then
if (p % value_logical) then
value = 1
else
value = 0
endif
else
write(0,*) "get_bigint : Unable to resolve value to integer: ", path
call exit(1)
endif
end subroutine get_bigint
!
! GET REAL
!
subroutine get_real(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
real :: value
real, optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_real : Unable to resolve path: ", path
call exit(1)
else
value = def
return
endif
endif
if(p % value_type == TYPE_INTEGER) then
value = REAL(p % value_integer)
else if (p % value_type == TYPE_REAL) then
value = REAL(p % value_real)
else if (p % value_type == TYPE_LOGICAL) then
if (p % value_logical) then
value = 1
else
value = 0
endif
else
write(0,*) "get_real : Unable to resolve value to real: ", path
call exit(1)
endif
end subroutine get_real
!
! GET DOUBLE
!
subroutine get_double(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
double precision :: value
double precision, optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_double : Unable to resolve path: ", path
call exit(1)
else
value = def
return
endif
endif
if(p % value_type == TYPE_INTEGER) then
value = p % value_integer
else if (p % value_type == TYPE_REAL) then
value = p % value_real
else if (p % value_type == TYPE_LOGICAL) then
if (p % value_logical) then
value = 1
else
value = 0
endif
else if(p % value_type == TYPE_NULL ) then
write(0,*) "get_double : WARNING: Unable to resolve value to double: ", p % value_type
write(0,*) "get_double : TYPE_NULL is present!"
value = 0
else
! write(0,*) "get_double : Unable to resolve value to double: ", path
write(0,*) "get_double : Unable to resolve value to double: ", p % value_type
call exit(1)
endif
end subroutine get_double
!
! GET LOGICAL
!
subroutine get_logical(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
logical :: value
logical, optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_logical : Unable to resolve path: ", path
call exit(1)
else
value = def
return
endif
endif
if(p % value_type == TYPE_INTEGER) then
value = (p % value_integer > 0)
else if (p % value_type == TYPE_LOGICAL) then
value = p % value_logical
else
write(0,*) "get_logical : Unable to resolve value to real: ", path
call exit(1)
endif
end subroutine get_logical
!
! GET CHARS
!
subroutine get_chars(this, path, value, def)
type(fson_value), pointer :: this, p
character(len=*), optional :: path
character(len=*) :: value
character(len=*), optional :: def
nullify(p)
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
if(.not.present(def)) then
write(0,*) "get_chars : Unable to resolve path: ", path
call exit(1)
else
do i = 1, len_trim(def)
value(i:i) = def(i:i)
enddo
return
endif
endif
if(p % value_type == TYPE_STRING) then
call fson_string_copy(p % value_string, value)
else
write(0,*) "get_chars : Unable to resolve value to characters: ", path
call exit(1)
endif
end subroutine get_chars
!
! GET ARRAY
!
subroutine get_array(this, path, array_callback)
type(fson_value), pointer :: this, p, element
character(len=*), optional :: path
integer :: index, count
! ELEMENT CALLBACK
interface
subroutine array_callback(element, index, count)
use fson_value_m
type(fson_value), pointer :: element
integer :: index, count
end subroutine array_callback
end interface
nullify(p)
! resolve the path to the value
if(present(path)) then
call get_by_path(this=this, path=path, p=p)
else
p => this
endif
if(.not.associated(p)) then
write(0,*) "get_array : Unable to resolve path: ", path
call exit(1)
endif
if(p % value_type == TYPE_ARRAY) then
count = fson_value_count(p)
do index=1, count
element => fson_value_get(p, index)
call array_callback(element, index, count)
enddo
else
write(0,*) "get_array : Resolved value is not an array. ", path
call exit(1)
endif
end subroutine get_array
end module fson_path_m
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
!
! File: string.f95
! Author: josephalevin
!
! Created on March 7, 2012, 7:40 PM
!
module fson_string_m
private
public :: fson_string, fson_string_create, fson_string_destroy, fson_string_length, fson_string_append, fson_string_clear
public :: fson_string_equals, fson_string_copy
integer, parameter :: BLOCK_SIZE = 32
type fson_string
character (len = BLOCK_SIZE) :: chars
integer :: index = 0
type(fson_string), pointer :: next => null()
end type fson_string
interface fson_string_append
module procedure append_chars, append_string
end interface fson_string_append
interface fson_string_copy
module procedure copy_chars
end interface fson_string_copy
interface fson_string_equals
module procedure equals_string
end interface fson_string_equals
interface fson_string_length
module procedure string_length
end interface fson_string_length
contains
!
! FSON STRING CREATE
!
function fson_string_create(chars) result(new)
character(len=*), optional :: chars
type(fson_string), pointer :: new
allocate(new)
! append chars if available
if(present(chars)) then
call append_chars(new, chars)
endif
end function fson_string_create
!
! FSON STRING CREATE
!
recursive subroutine fson_string_destroy(this)
type(fson_string), pointer :: this
if(associated(this % next)) then
call fson_string_destroy(this % next)
endif
nullify (this % next)
nullify (this)
end subroutine fson_string_destroy
!
! ALLOCATE BLOCK
!
subroutine allocate_block(this)
type(fson_string), pointer :: this
type(fson_string), pointer :: new
if (.not.associated(this % next)) then
allocate(new)
this % next => new
endif
end subroutine allocate_block
!
! APPEND_STRING
!
subroutine append_string(str1, str2)
type(fson_string), pointer :: str1, str2
integer length, i
length = string_length(str2)
do i = 1, length
call append_char(str1, get_char_at(str2, i))
enddo
end subroutine append_string
!
! APPEND_CHARS
!
subroutine append_chars(str, c)
type(fson_string), pointer :: str
character (len = *), intent(in) :: c
integer length, i
length = len(c)
do i = 1, length
call append_char(str, c(i:i))
enddo
end subroutine append_chars
!
! APPEND_CHAR
!
recursive subroutine append_char(str, c)
type(fson_string), pointer :: str
character, intent(in) :: c
if (str % index .GE. BLOCK_SIZE) then
!set down the chain
call allocate_block(str)
call append_char(str % next, c)
else
! set local
str % index = str % index + 1
str % chars(str % index:str % index) = c
endif
end subroutine append_char
!
! COPY CHARS
!
subroutine copy_chars(this, to)
type(fson_string), pointer :: this
character(len = *), intent(inout) :: to
integer :: length
length = min(string_length(this), len(to))
do i = 1, length
to(i:i) = get_char_at(this, i)
enddo
! pad with nothing
do i = length + 1, len(to)
to(i:i) = ""
enddo
end subroutine copy_chars
!
! CLEAR
!
recursive subroutine string_clear(this)
type(fson_string), pointer :: this
if (associated(this % next)) then
call string_clear(this % next)
deallocate(this % next)
nullify (this % next)
endif
this % index = 0
end subroutine string_clear
!
! SIZE
!
recursive integer function string_length(str) result(count)
type(fson_string), pointer :: str
count = str % index
if (str % index == BLOCK_SIZE .AND. associated(str % next)) then
count = count + string_length(str % next)
endif
end function string_length
!
! GET CHAR AT
!
recursive character function get_char_at(this, i) result(c)
type(fson_string), pointer :: this
integer, intent(in) :: i
if (i .LE. this % index) then
c = this % chars(i:i)
else
c = get_char_at(this % next, i - this % index)
endif
end function get_char_at
!
! EQUALS STRING
!
logical function equals_string(this, other) result(equals)
type(fson_string), pointer :: this, other
integer :: i
equals = .false.
if(fson_string_length(this) .ne. fson_string_length(other)) then
equals = .false.
return
else if(fson_string_length(this) == 0) then
equals = .true.
return
endif
do i=1, fson_string_length(this)
if(get_char_at(this, i) .ne. get_char_at(other, i)) then
equals = .false.
return
endif
enddo
equals = .true.
end function equals_string
end module fson_string_m
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
!
! File: value_m.f95
! Author: josephalevin
!
! Created on March 7, 2012, 10:14 PM
!
module fson_value_m
use fson_string_m
implicit none
private
public :: fson_value, fson_value_create, fson_value_destroy, fson_value_add, fson_value_get, fson_value_count
public :: fson_value_print, fson_value_print_pretty
!constants for the value types
integer, public, parameter :: TYPE_UNKNOWN = -1
integer, public, parameter :: TYPE_NULL = 0
integer, public, parameter :: TYPE_OBJECT = 1
integer, public, parameter :: TYPE_ARRAY = 2
integer, public, parameter :: TYPE_STRING = 3
integer, public, parameter :: TYPE_INTEGER = 4
integer, public, parameter :: TYPE_REAL = 5
integer, public, parameter :: TYPE_LOGICAL = 6
!
! FSON VALUE
!
type fson_value
type(fson_string), pointer :: name => null()
integer :: value_type = TYPE_UNKNOWN
logical :: value_logical
! fte changed
integer*8 :: value_integer
double precision :: value_real
character(len=24) :: value_fmt = ''
type(fson_string), pointer :: value_string => null()
type(fson_value), pointer :: next => null()
type(fson_value), pointer :: parent => null()
type(fson_value), pointer :: children => null()
! fte changed 14.12.2017
type(fson_value), pointer :: last_child => null()
integer :: child_count
end type fson_value
!
! FSON VALUE GET
!
! Use either a 1 based index or member name to get the value.
interface fson_value_get
module procedure get_by_index
module procedure get_by_name_chars
module procedure get_by_name_string
end interface fson_value_get
contains
!
! FSON VALUE CREATE
!
function fson_value_create() result(new)
type(fson_value), pointer :: new
integer :: alloc_err
allocate(new,stat=alloc_err)
if(alloc_err.ne.0) then
stop 'ERROR: allocate memory.'
endif
end function fson_value_create
!
! FSON VALUE DESTROY
!
recursive subroutine fson_value_destroy(this)
type(fson_value), pointer :: this, p, el
if(associated(this % children)) then
el => this % children
do while (associated (el))
p => el
el => el % next
nullify(p)
enddo
endif
if(associated(this % next)) then
call fson_value_destroy(this % next)
nullify (this % next)
endif
if(associated(this % name)) then
call fson_string_destroy(this % name)
nullify (this % name)
endif
if(associated(this % value_string)) then
call fson_string_destroy(this % value_string)
nullify (this % value_string)
endif
nullify(this)
end subroutine fson_value_destroy
!
! FSON VALUE ADD
!
! Adds the memeber to the linked list
subroutine fson_value_add(this, member)
type(fson_value), pointer :: this, member, p
! associate the parent
member % parent => this
! add to linked list
if (associated(this % last_child)) then
p => this % last_child
p % next => member
this % last_child => member
this % child_count = this % child_count + 1
else
this % children => member
this % last_child => member
this % child_count = 1
endif
end subroutine
!
! FSON_VALUE_COUNT
!
integer(4) function fson_value_count(this) result(count)
type(fson_value), pointer :: this
count = 0
if(associated(this % children)) then
count = this % child_count
endif
end function
!
! GET BY INDEX
!
function get_by_index(this, index) result(p)
type(fson_value), pointer :: this, p
integer, intent(in) :: index
integer :: i
p => this % children
do i = 1, index - 1
p => p % next
enddo
end function get_by_index
!
! GET BY NAME CHARS
!
function get_by_name_chars(this, name) result(p)
type(fson_value), pointer :: this, p
character(len=*), intent(in) :: name
type(fson_string), pointer :: string
! convert the char array into a string
string => fson_string_create(name)
p => get_by_name_string(this, string)
end function get_by_name_chars
!
! GET BY NAME STRING
!
function get_by_name_string(this, name) result(p)
type(fson_value), pointer :: this, p
type(fson_string), pointer :: name
integer :: i
if(this % value_type .ne. TYPE_OBJECT) then
nullify(p)
return
endif
do i=1, fson_value_count(this)
p => fson_value_get(this, i)
if (fson_string_equals(p%name, name)) then
return
endif
enddo
! didn't find anything
nullify(p)
end function get_by_name_string
!
! COMPACT REAL STRING
!
subroutine compact_real_string(str)
implicit none
character(len=*),intent(inout) :: str !! string representation of a real number.
character(len=len(str)) :: significand
character(len=len(str)) :: expnt
character(len=2) :: separator
integer :: exp_start
integer :: decimal_pos
integer :: sig_trim
integer :: exp_trim
integer :: i !! counter
str = adjustl(str)
exp_start = scan(str,'eEdD')
if (exp_start == 0) exp_start = scan(str,'-+',back=.true.)
decimal_pos = scan(str,'.')
if (exp_start /= 0) separator = str(exp_start:exp_start)
if ( exp_start < decimal_pos ) then !possibly signed, exponent-less float
significand = str
sig_trim = len(trim(significand))
do i = len(trim(significand)),decimal_pos+2,-1 !look from right to left at 0s
!but save one after the decimal place
if (significand(i:i) == '0') then
sig_trim = i-1
else
exit
end if
end do
str = trim(significand(1:sig_trim))
else if (exp_start > decimal_pos) then !float has exponent
significand = str(1:exp_start-1)
sig_trim = len(trim(significand))
do i = len(trim(significand)),decimal_pos+2,-1 !look from right to left at 0s
if (significand(i:i) == '0') then
sig_trim = i-1
else
exit
end if
end do
expnt = adjustl(str(exp_start+1:))
if (expnt(1:1) == '+' .or. expnt(1:1) == '-') then
separator = trim(adjustl(separator))//expnt(1:1)
exp_start = exp_start + 1
expnt = adjustl(str(exp_start+1:))
end if
exp_trim = 1
do i = 1,(len(trim(expnt))-1) !look at exponent leading zeros saving last
if (expnt(i:i) == '0') then
exp_trim = i+1
else
exit
end if
end do
str = trim(adjustl(significand(1:sig_trim)))// &
trim(adjustl(separator))// &
trim(adjustl(expnt(exp_trim:)))
!else ! mal-formed real, BUT this code should be unreachable
end if
end subroutine compact_real_string
!
! FSON VALUE PRINT PRETTY
!
recursive subroutine fson_value_print_pretty(this, indent)
type(fson_value), pointer :: this, element
integer, optional, intent(in) :: indent
character (len = 8192) :: tmp_chars
integer :: tab, i, count, spaces
if (present(indent)) then
tab = indent
else
tab = 0
endif
spaces = tab * 2
select case (this % value_type)
case(TYPE_OBJECT)
print *, repeat(" ", spaces), "{"
count = fson_value_count(this)
do i = 1, count
! get the element
element => fson_value_get(this, i)
! get the name
call fson_string_copy(element % name, tmp_chars)
! print the name
print *, repeat(" ", spaces), '"', trim(tmp_chars), '":'
! recursive print of the element
call fson_value_print_pretty(element, tab + 1)
! print the separator if required
if (i < count) then
print *, repeat(" ", spaces), ","
endif
enddo
print *, repeat(" ", spaces), "}"
case (TYPE_ARRAY)
print *, repeat(" ", spaces), "["
count = fson_value_count(this)
do i = 1, count
! get the element
element => fson_value_get(this, i)
! recursive print of the element
call fson_value_print_pretty(element, tab + 1)
! print the separator if required
if (i < count) then
print *, ","
endif
enddo
print *, repeat(" ", spaces), "]"
case (TYPE_NULL)
print *, repeat(" ", spaces), "null"
case (TYPE_STRING)
call fson_string_copy(this % value_string, tmp_chars)
call fput('"')
do i=1, fson_string_length(this % value_string)
if (ichar(tmp_chars(i:i)).eq.0) exit
call fput(tmp_chars(i:i))
enddo
call fput('"')
case (TYPE_LOGICAL)
if (this % value_logical) then
print *, repeat(" ", spaces), "true"
else
print *, repeat(" ", spaces), "false"
endif
case (TYPE_INTEGER)
print *, repeat(" ", spaces), this % value_integer
case (TYPE_REAL)
print *, repeat(" ", spaces), this % value_real
endselect
end subroutine fson_value_print_pretty
!
! FSON VALUE PRINT
!
recursive subroutine fson_value_print(this)
type(fson_value), pointer :: this, element
character (len = 8192) :: tmp_chars
integer :: i, count
select case (this % value_type)
case(TYPE_OBJECT)
call fput('{')
count = fson_value_count(this)
do i = 1, count
! get the element
element => fson_value_get(this, i)
! get the name
if(associated(element % name)) then
call fson_string_copy(element % name, tmp_chars)
! print the name
write(*,'(3A)',advance='no') '"', trim(tmp_chars), '":'
endif
! recursive print of the element
call fson_value_print(element)
! print the separator if required
if (i < count) then
call fput(',')
endif
enddo
call fput('}')
case (TYPE_ARRAY)
call fput('[')
count = fson_value_count(this)
do i = 1, count
! get the element
element => fson_value_get(this, i)
! recursive print of the element
call fson_value_print(element)
! print the separator if required
if (i < count) then
call fput(',')
endif
enddo
call fput(']')
case (TYPE_NULL)
write(*,'(A)',advance='no') "null"
case (TYPE_STRING)
call fson_string_copy(this % value_string, tmp_chars)
call fput('"')
do i=1, fson_string_length(this % value_string)
if (ichar(tmp_chars(i:i)).eq.0) exit
call fput(tmp_chars(i:i))
enddo
call fput('"')
case (TYPE_LOGICAL)
if (this % value_logical) then
write(*,'(A)',advance='no') "true"
else
write(*,'(A)',advance='no') "false"
endif
case (TYPE_INTEGER)
write(tmp_chars,*) this % value_integer
write(*,'(A)',advance='no') trim(adjustl(tmp_chars))
case (TYPE_REAL)
if(len_trim(this % value_fmt).gt.0) then
write(tmp_chars,this % value_fmt) this % value_real
else
write(tmp_chars,*) this % value_real
endif
call compact_real_string(tmp_chars)
write(*,'(A)',advance='no') trim(adjustl(tmp_chars))
endselect
end subroutine fson_value_print
end module fson_value_m
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
! FSON MODULE
!
! File: fson.f95
! Author: Joseph A. Levin
!
! Created on January 8, 2013
!
program example_basic
! Typical usage should only require an explicit use of the fson module.
! The other modules will be used privatley by fson as required.
! use fson
! declare a pointer variable. Always use a pointer with fson_value.
! type(fson_value), pointer :: value
! parse the json file
! value => fson_parse("test1.json")
! print the parsed data to the console
! call fson_print(value)
! extract data from the parsed value
! clean up
! call fson_destroy(value)
end program example_basic
! Copyright (c) 2012 Joseph A. Levin
!
! Permission is hereby granted, free of charge, to any person obtaining a copy of this
! software and associated documentation files (the "Software"), to deal in the Software
! without restriction, including without limitation the rights to use, copy, modify, merge,
! publish, distribute, sublicense, and/or sell copies of the Software, and to permit
! persons to whom the Software is furnished to do so, subject to the following conditions:
!
! The above copyright notice and this permission notice shall be included in all copies or
! substantial portions of the Software.
!
! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED,
! INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
! PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
! LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT
! OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
! DEALINGS IN THE SOFTWARE.
! FSON MODULE
!
! File: fson.f95
! Author: Joseph A. Levin
!
! Created on March 10, 2012, 5:24 AM
!
program example1
! Typical usage should only require an explicit use of the fson module.
! The other modules will be used privatley by fson as required.
use fson
! declare a pointer variable. Always use a pointer with fson_value.
type(fson_value), pointer :: value
! parse the json file
value => fson_parse("test1.json")
! print the parsed data to the console
call fson_print(value)
! extract data from the parsed value
! clean up
call fson_destroy(value)
end program example1
\ No newline at end of file
{
"firstName": "John",
"lastName" : "Smith",
"age" : 25,
"friend" : true,
"password" : null,
"address" :
{
"streetAddress": "21 2nd Street",
"city" : "New York",
"state" : "NY",
"postalCode" : "10021"
},
"phoneNumber":
[
{
"type" : "home",
"number": "212 555-1234"
},
{
"type" : "fax",
"number": "646 555-4567"
}
]
}
\ No newline at end of file
*
!.gitignore
!*.h
!*.hpp
!*.tcc
!cpp-json/
\ No newline at end of file
#ifndef ARRAY_20110526_H_
#define ARRAY_20110526_H_
namespace json {
class array;
class value;
class array {
friend bool operator==(const array &lhs, const array &rhs);
friend bool operator!=(const array &lhs, const array &rhs);
template <class In>
friend class parser;
private:
using C = std::vector<value>;
public:
using allocator_type = typename C::allocator_type;
using reference = typename C::reference;
using const_reference = typename C::const_reference;
using pointer = typename C::pointer;
using const_pointer = typename C::const_pointer;
using iterator = typename C::iterator;
using const_iterator = typename C::const_iterator;
using reverse_iterator = typename C::reverse_iterator;
using const_reverse_iterator = typename C::const_reverse_iterator;
using difference_type = typename C::difference_type;
using size_type = typename C::size_type;
public:
array() = default;
array(array &&other) = default;
array(const array &other) = default;
array &operator=(array &&rhs) = default;
array &operator=(const array &rhs) = default;
array(std::initializer_list<value> list);
public:
// Added by fte...
reference front() { return values_.front(); }
reference back() { return values_.back(); }
const_reference front() const { return values_.front(); }
const_reference back() const { return values_.back(); }
iterator erase (const_iterator position) { return values_.erase(position); }
iterator erase (const_iterator first, const_iterator last) { return values_.erase(first,last); }
// Added by fte...
iterator begin() { return values_.begin(); }
iterator end() { return values_.end(); }
const_iterator begin() const { return values_.begin(); }
const_iterator end() const { return values_.end(); }
const_iterator cbegin() const { return values_.begin(); }
const_iterator cend() const { return values_.end(); }
reverse_iterator rbegin() { return values_.rbegin(); }
reverse_iterator rend() { return values_.rend(); }
const_reverse_iterator rbegin() const { return values_.rbegin(); }
const_reverse_iterator rend() const { return values_.rend(); }
const_reverse_iterator crbegin() const { return values_.rbegin(); }
const_reverse_iterator crend() const { return values_.rend(); }
public:
size_type size() const { return values_.size(); }
size_type max_size() const { return values_.max_size(); }
bool empty() const { return values_.empty(); }
// Added by fte...
void resize (size_type n) { values_.resize(n); }
void clear() noexcept { values_.clear(); }
// Added by fte...
public:
const value operator[](std::size_t n) const;
value &operator[](std::size_t n);
const value at(std::size_t n) const;
value &at(std::size_t n);
public:
template <class T, class... Args>
array &append(const T &v, Args &&...args);
template <class T>
array &append(T &&v);
template <class T>
array &append(const T &v);
public:
void swap(array &other);
private:
C values_;
};
bool operator==(const array &lhs, const array &rhs);
bool operator!=(const array &lhs, const array &rhs);
inline array::iterator begin(array &arr) { return arr.begin(); }
inline array::iterator end(array &arr) { return arr.end(); }
inline array::const_iterator begin(const array &arr) { return arr.begin(); }
inline array::const_iterator end(const array &arr) { return arr.end(); }
inline array::const_iterator cbegin(const array &arr) { return arr.begin(); }
inline array::const_iterator cend(const array &arr) { return arr.end(); }
inline array::reverse_iterator rbegin(array &arr) { return arr.rbegin(); }
inline array::reverse_iterator rend(array &arr) { return arr.rend(); }
inline array::const_reverse_iterator rbegin(const array &arr) { return arr.rbegin(); }
inline array::const_reverse_iterator rend(const array &arr) { return arr.rend(); }
inline array::const_reverse_iterator crbegin(const array &arr) { return arr.rbegin(); }
inline array::const_reverse_iterator crend(const array &arr) { return arr.rend(); }
}
#endif
#ifndef ARRAY_20120424_TCC_
#define ARRAY_20120424_TCC_
namespace json {
//------------------------------------------------------------------------------
// Name: array
//------------------------------------------------------------------------------
inline array::array(std::initializer_list<value> list) {
for(const auto &x : list) {
values_.emplace_back(x);
}
}
//------------------------------------------------------------------------------
// Name: append
//------------------------------------------------------------------------------
template <class T, class... Args>
array &array::append(const T &v, Args &&...args) {
values_.push_back(value(v));
return append(args...);
}
//------------------------------------------------------------------------------
// Name: append
//------------------------------------------------------------------------------
template <class T>
array &array::append(T &&v) {
values_.push_back(value(std::move(v)));
return *this;
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline const value array::operator[](std::size_t n) const {
return at(n);
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline value &array::operator[](std::size_t n) {
return at(n);
}
//------------------------------------------------------------------------------
// Name: at
//------------------------------------------------------------------------------
inline const value array::at(std::size_t n) const {
if(n < values_.size()) {
return values_[n];
}
throw invalid_index();
}
//------------------------------------------------------------------------------
// Name: at
//------------------------------------------------------------------------------
inline value &array::at(std::size_t n) {
if(n < values_.size()) {
return values_[n];
}
throw invalid_index();
}
//------------------------------------------------------------------------------
// Name: append
//------------------------------------------------------------------------------
template <class T>
array &array::append(const T &v) {
values_.push_back(value(v));
return *this;
}
//------------------------------------------------------------------------------
// Name: swap
//------------------------------------------------------------------------------
inline void array::swap(array &other) {
using std::swap;
swap(values_, other.values_);
}
//------------------------------------------------------------------------------
// Name: operator==
//------------------------------------------------------------------------------
inline bool operator==(const array &lhs, const array &rhs) {
if(lhs.values_.size() == rhs.values_.size()) {
return lhs.values_ == rhs.values_;
}
return false;
}
//------------------------------------------------------------------------------
// Name: operator!=
//------------------------------------------------------------------------------
inline bool operator!=(const array &lhs, const array &rhs) {
return !(lhs == rhs);
}
}
#endif
#ifndef EXCEPTION_20120104_H_
#define EXCEPTION_20120104_H_
namespace json {
// general error
class exception : public std::exception {
public:
exception() : location(-1) {
}
public:
int location;
};
// parsing errors
class boolean_expected : public exception {};
class brace_expected : public exception {};
class bracket_expected : public exception {};
class colon_expected : public exception {};
class hex_character_expected : public exception {};
class quote_expected : public exception {};
class invalid_unicode_character : public exception {};
class keyword_expected : public exception {};
class string_expected : public exception {};
class value_expected : public exception {};
class utf16_surrogate_expected : public exception {};
class invalid_number : public exception {};
class invalid_utf8_string : public exception {};
// usage errors
class invalid_type_cast : public exception {};
class invalid_index : public exception {};
}
#endif
#ifndef JSON_20110525_H_
#define JSON_20110525_H_
/* TODO(eteran): support unicode
00 00 00 xx UTF-32BE
00 xx 00 xx UTF-16BE
xx 00 00 00 UTF-32LE
xx 00 xx 00 UTF-16LE
xx xx xx xx UTF-8
*/
#include <algorithm>
#include <cctype>
#include <cstdint>
#include <exception>
#include <initializer_list>
#include <iostream>
#include <iterator>
#include <memory>
#include <sstream>
#include <string>
#include <type_traits>
#include <unordered_map>
#include <vector>
namespace json {
class value;
class array;
class object;
using object_pointer = std::shared_ptr<object>;
using array_pointer = std::shared_ptr<array>;
// type testing
inline bool is_string(const value &v);
inline bool is_bool(const value &v);
inline bool is_number(const value &v);
inline bool is_object(const value &v);
inline bool is_array(const value &v);
inline bool is_null(const value &v);
// conversion (you get a copy)
inline std::string to_string(const value &v);
inline bool to_bool(const value &v);
inline double to_number(const value &v);
inline int64_t to_integer(const value &v);
inline object to_object(const value &v);
inline array to_array(const value &v);
// interpretation (you get a reference)
inline object &as_object(value &v);
inline array &as_array(value &v);
inline std::string &as_string(value &v);
inline const object &as_object(const value &v);
inline const array &as_array(const value &v);
inline const std::string &as_string(const value &v);
// does the given object have a given key?
inline bool has_key(const value &v, const std::string &key);
inline bool has_key(const object &o, const std::string &key);
// create a value from some JSON
template <class In>
inline value parse(In first, In last);
inline value parse(std::istream &is);
inline value parse(std::istream &&is);
inline value parse(const std::string &s);
// convert a value to a JSON string
enum {
ESCAPE_UNICODE = 0x01,
PRETTY_PRINT = 0x02
};
inline std::string stringify(const value &v, unsigned options);
inline std::string stringify(const array &a, unsigned options);
inline std::string stringify(const object &o, unsigned options);
inline std::string stringify(const value &v);
inline std::string stringify(const array &a);
inline std::string stringify(const object &o);
}
#include "exception.h"
#include "value.h"
#include "object.h"
#include "array.h"
#include "parser.h"
#include "json.tcc"
#include "object.tcc"
#include "array.tcc"
#include "value.tcc"
#include "parser.tcc"
#endif
#ifndef JSON_20110526_TCC_
#define JSON_20110526_TCC_
namespace json {
namespace detail {
template <class In, class Tr>
int distance_in_stream_internal(In first, In current, const Tr&) {
(void)first;
(void)current;
return -1;
}
template <class In>
int distance_in_stream_internal(In first, In current, const std::random_access_iterator_tag &) {
return std::distance(first, current);
}
template <class In>
int distance_in_stream(In first, In current) {
using Cat = typename std::iterator_traits<In>::iterator_category;
return distance_in_stream_internal(first, current, Cat());
}
}
template <class In>
value parse(In first, In last) {
parser<In> p(first, last);
try {
return p.parse();
} catch(exception &e) {
e.location = detail::distance_in_stream(p.begin(), p.current());
throw;
}
}
inline std::string to_string(const value &v) {
return as_string(v);
}
inline bool to_bool(const value &v) {
if(!is_bool(v)) {
throw invalid_type_cast();
}
return v.as_string() == "true";
}
inline double to_number(const value &v) {
if(!is_number(v)) {
throw invalid_type_cast();
}
return stod(as_string(v), 0);
}
inline int64_t to_integer(const value &v) {
if(!is_number(v)) {
throw invalid_type_cast();
}
return stoll(as_string(v), 0);
}
inline object to_object(const value &v) {
return as_object(v);
}
inline array to_array(const value &v) {
return as_array(v);
}
inline object &as_object(value &v) {
if(!is_object(v)) {
throw invalid_type_cast();
}
return v.as_object();
}
inline const object &as_object(const value &v) {
if(!is_object(v)) {
throw invalid_type_cast();
}
return v.as_object();
}
inline array &as_array(value &v) {
if(!is_array(v)) {
throw invalid_type_cast();
}
return v.as_array();
}
inline const array &as_array(const value &v) {
if(!is_array(v)) {
throw invalid_type_cast();
}
return v.as_array();
}
const std::string &as_string(const value &v) {
if(!is_string(v) && !is_bool(v) && !is_number(v) && !is_null(v)) {
throw invalid_type_cast();
}
return v.as_string();
}
std::string &as_string(value &v) {
if(!is_string(v) && !is_bool(v) && !is_number(v) && !is_null(v)) {
throw invalid_type_cast();
}
return v.as_string();
}
inline bool has_key(const value &v, const std::string &key) {
if(is_object(v)) {
return has_key(as_object(v), key);
}
return false;
}
inline bool has_key(const object &o, const std::string &key) {
return o.find(key) != o.end();
}
inline value parse(std::istream &&is) {
return parse(is);
}
inline value parse(std::istream &is) {
return parse((std::istreambuf_iterator<char>(is)), std::istreambuf_iterator<char>());
}
inline value parse(const std::string &s) {
return parse(s.begin(), s.end());
}
inline bool is_string(const value &v) { return (v.type_ == value::type_string); }
inline bool is_bool(const value &v) { return (v.type_ == value::type_boolean); }
inline bool is_number(const value &v) { return (v.type_ == value::type_number); }
inline bool is_object(const value &v) { return (v.type_ == value::type_object); }
inline bool is_array(const value &v) { return (v.type_ == value::type_array); }
inline bool is_null(const value &v) { return (v.type_ == value::type_null); }
namespace detail {
inline std::string escape_string(const std::string &s, unsigned options) {
std::string r;
r.reserve(s.size());
if(options & ESCAPE_UNICODE) {
struct state_t {
unsigned int expected : 4,
seen : 4,
reserved : 24;
};
state_t shift_state = {0,0,0};
uint32_t result = 0;
for(auto it = s.begin(); it != s.end(); ++it) {
const unsigned char ch = *it;
if(shift_state.seen == 0) {
if((ch & 0x80) == 0) {
switch(*it) {
case '\"': r += "\\\""; break;
case '\\': r += "\\\\"; break;
#if 0
case '/': r += "\\/"; break;
#endif
case '\b': r += "\\b"; break;
case '\f': r += "\\f"; break;
case '\n': r += "\\n"; break;
case '\r': r += "\\r"; break;
case '\t': r += "\\t"; break;
default:
r += *it;
break;
}
}else if((ch & 0xe0) == 0xc0) {
// 2 byte
result = ch & 0x1f;
shift_state.expected = 2;
shift_state.seen = 1;
} else if((ch & 0xf0) == 0xe0) {
// 3 byte
result = ch & 0x0f;
shift_state.expected = 3;
shift_state.seen = 1;
} else if((ch & 0xf8) == 0xf0) {
// 4 byte
result = ch & 0x07;
shift_state.expected = 4;
shift_state.seen = 1;
} else if((ch & 0xfc) == 0xf8) {
// 5 byte
throw invalid_utf8_string(); // Restricted by RFC 3629
} else if((ch & 0xfe) == 0xfc) {
// 6 byte
throw invalid_utf8_string(); // Restricted by RFC 3629
} else {
throw invalid_utf8_string(); // should never happen
}
} else if(shift_state.seen < shift_state.expected) {
if((ch & 0xc0) == 0x80) {
result <<= 6;
result |= ch & 0x3f;
// increment the shift state
++shift_state.seen;
if(shift_state.seen == shift_state.expected) {
// done with this character
char buf[5];
if(result < 0xd800 || (result >= 0xe000 && result < 0x10000)) {
r += "\\u";
snprintf(buf, sizeof(buf), "%04X", result);
r += buf;
} else {
result = (result - 0x10000);
r += "\\u";
snprintf(buf, sizeof(buf), "%04X", 0xd800 + ((result >> 10) & 0x3ff));
r += buf;
r += "\\u";
snprintf(buf, sizeof(buf), "%04X", 0xdc00 + (result & 0x3ff));
r += buf;
}
shift_state.seen = 0;
shift_state.expected = 0;
result = 0;
}
} else {
throw invalid_utf8_string(); // should never happen
}
} else {
throw invalid_utf8_string(); // should never happen
}
}
} else {
for(auto it = s.begin(); it != s.end(); ++it) {
switch(*it) {
case '\"': r += "\\\""; break;
case '\\': r += "\\\\"; break;
#if 0
case '/': r += "\\/"; break;
#endif
case '\b': r += "\\b"; break;
case '\f': r += "\\f"; break;
case '\n': r += "\\n"; break;
case '\r': r += "\\r"; break;
case '\t': r += "\\t"; break;
default:
r += *it;
break;
}
}
}
return r;
}
inline std::string escape_string(const std::string &s) {
return escape_string(s, 0);
}
inline std::string value_to_string(const value &v, unsigned options, int indent, bool ignore_initial_ident) {
static const int indent_width = 2;
std::stringstream ss;
std::locale c_locale("C");
ss.imbue(c_locale);
if(!ignore_initial_ident) {
ss << std::string(indent * indent_width, ' ');
}
if(is_string(v)) {
ss << '"' << escape_string(as_string(v), options) << '"';
}
if(is_number(v)) {
ss << as_string(v);
}
if(is_null(v)) {
ss << as_string(v);
}
if(is_bool(v)) {
ss << (to_bool(v) ? "true" : "false");
}
if(is_object(v)) {
const object &o = as_object(v);
ss << "{\n";
if(!o.empty()) {
auto it = o.begin();
auto e = o.end();
++indent;
ss << std::string(indent * indent_width, ' ') << '"' << escape_string(it->first, options) << "\" : " << value_to_string(it->second, options, indent, true);
++it;
for(;it != e; ++it) {
ss << ',';
ss << '\n';
ss << std::string(indent * indent_width, ' ') << '"' << escape_string(it->first, options) << "\" : " << value_to_string(it->second, options, indent, true);
}
--indent;
}
ss << "\n";
ss << std::string(indent * indent_width, ' ') << "}";
}
if(is_array(v)) {
const array &a = as_array(v);
ss << "[\n";
if(!a.empty()) {
auto it = a.begin();
auto e = a.end();
++indent;
ss << value_to_string(*it++, options, indent, false);
for(;it != e; ++it) {
ss << ',';
ss << '\n';
ss << value_to_string(*it, options, indent, false);
}
--indent;
}
ss << "\n";
ss << std::string(indent * indent_width, ' ') << "]";
}
return ss.str();
}
inline std::string value_to_string(const value &v, unsigned options) {
return value_to_string(v, options, 0, false);
}
inline std::string serialize(const value &v, unsigned options) {
std::stringstream ss;
if(is_string(v)) {
ss << '"' << escape_string(as_string(v), options) << '"';
}
if(is_number(v)) {
ss << as_string(v);
}
if(is_null(v)) {
ss << as_string(v);
}
if(is_bool(v)) {
ss << (to_bool(v) ? "true" : "false");
}
if(is_object(v)) {
const object &o = as_object(v);
ss << "{";
if(!o.empty()) {
auto it = o.begin();
auto e = o.end();
ss << '"' << escape_string(it->first, options) << "\":" << serialize(it->second, options);
++it;
for(;it != e; ++it) {
ss << ',';
ss << '"' << escape_string(it->first, options) << "\":" << serialize(it->second, options);
}
}
ss << "}";
}
if(is_array(v)) {
const array &a = as_array(v);
ss << "[";
if(!a.empty()) {
auto it = a.begin();
auto e = a.end();
ss << serialize(*it++, options);
for(;it != e; ++it) {
ss << ',';
ss << serialize(*it, options);
}
}
ss << "]";
}
return ss.str();
}
inline std::string serialize(const array &a, unsigned options) {
return serialize(value(a), options);
}
inline std::string serialize(const object &o, unsigned options) {
return serialize(value(o), options);
}
inline std::string pretty_print(const value &v, unsigned options) {
return value_to_string(v, options);
}
inline std::string pretty_print(const array &a, unsigned options) {
return value_to_string(value(a), options);
}
inline std::string pretty_print(const object &o, unsigned options) {
return value_to_string(value(o), options);
}
}
inline std::string stringify(const value &v, unsigned options) {
if(options & PRETTY_PRINT) {
return detail::pretty_print(v, options);
} else {
return detail::serialize(v, options);
}
}
inline std::string stringify(const array &a, unsigned options) {
if(options & PRETTY_PRINT) {
return detail::pretty_print(a, options);
} else {
return detail::serialize(a, options);
}
}
inline std::string stringify(const object &o, unsigned options) {
if(options & PRETTY_PRINT) {
return detail::pretty_print(o, options);
} else {
return detail::serialize(o, options);
}
}
inline std::string stringify(const value &v) {
return stringify(v, 0);
}
inline std::string stringify(const array &a) {
return stringify(a, 0);
}
inline std::string stringify(const object &o) {
return stringify(o, 0);
}
}
#endif
#ifndef OBJECT_20110526_H_
#define OBJECT_20110526_H_
namespace json {
class object;
class value;
class object {
friend bool operator==(const object &lhs, const object &rhs);
friend bool operator!=(const object &lhs, const object &rhs);
template <class In>
friend class parser;
private:
#ifdef ORDERED_DICT
using C = std::vector<std::pair<std::string, value>>;
#else
using C = std::unordered_map<std::string, value>;
#endif
public:
using allocator_type = typename C::allocator_type;
using reference = typename C::reference;
using const_reference = typename C::const_reference;
using pointer = typename C::pointer;
using const_pointer = typename C::const_pointer;
using iterator = typename C::iterator;
using const_iterator = typename C::const_iterator;
using difference_type = typename C::difference_type;
using size_type = typename C::size_type;
public:
object() = default;
object(const object &other) = default;
object(object &&other) = default;
object &operator=(const object &rhs) = default;
object &operator=(object &&rhs) = default;
object(std::initializer_list<std::pair<std::string, value>> list);
public:
iterator begin() { return values_.begin(); }
iterator end() { return values_.end(); }
const_iterator begin() const { return values_.begin(); }
const_iterator end() const { return values_.end(); }
const_iterator cbegin() const { return values_.begin(); }
const_iterator cend() const { return values_.end(); }
public:
#ifdef ORDERED_DICT
iterator find(const std::string &s) {
return std::find_if(values_.begin(), values_.end(), [&s](const std::pair<std::string, value> &entry) {
return entry.first == s;
});
}
const_iterator find(const std::string &s) const {
return std::find_if(values_.begin(), values_.end(), [&s](const std::pair<std::string, value> &entry) {
return entry.first == s;
});
}
#else
iterator find(const std::string &s) { return values_.find(s); }
const_iterator find(const std::string &s) const { return values_.find(s); }
#endif
public:
size_type size() const { return values_.size(); }
size_type max_size() const { return values_.max_size(); }
bool empty() const { return values_.empty(); }
// Added by fte...
void clear() noexcept { values_.clear(); }
// Added by fte...
public:
const value operator[](const std::string &key) const;
value &operator[](const std::string &key);
const value at(const std::string &key) const;
value &at(const std::string &key);
template <class T>
object &insert(const std::string &key, const T &v);
template <class T>
object &insert(const std::pair<std::string, T> &p);
template <class T>
object &insert(std::pair<std::string, T> &&p);
public:
void swap(object &other);
private:
C values_;
};
bool operator==(const object &lhs, const object &rhs);
bool operator!=(const object &lhs, const object &rhs);
inline object::iterator begin(object &obj) { return obj.begin(); }
inline object::iterator end(object &obj) { return obj.end(); }
inline object::const_iterator begin(const object &obj) { return obj.begin(); }
inline object::const_iterator end(const object &obj) { return obj.end(); }
inline object::const_iterator cbegin(const object &obj) { return obj.begin(); }
inline object::const_iterator cend(const object &obj) { return obj.end(); }
}
#endif
#ifndef OBJECT_20120424_TCC_
#define OBJECT_20120424_TCC_
namespace json {
//------------------------------------------------------------------------------
// Name: object
//------------------------------------------------------------------------------
inline object::object(std::initializer_list<std::pair<std::string, value>> list) {
for(auto &x : list) {
#ifdef ORDERED_DICT
values_.emplace_back(x);
#else
values_.emplace(x.first, x.second);
#endif
}
}
//------------------------------------------------------------------------------
// Name: insert
//------------------------------------------------------------------------------
template <class T>
inline object &object::insert(std::pair<std::string, T> &&p) {
#ifdef ORDERED_DICT
values_.emplace_back(std::move(p));
#else
values_.insert(std::move(p));
#endif
return *this;
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline const value object::operator[](const std::string &key) const {
return at(key);
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline value &object::operator[](const std::string &key) {
return at(key);
}
//------------------------------------------------------------------------------
// Name: at
//------------------------------------------------------------------------------
inline const value object::at(const std::string &key) const {
#ifdef ORDERED_DICT
auto it = std::find_if(values_.begin(), values_.end(), [&key](const std::pair<std::string, value> &entry) {
return entry.first == key;
});
#else
auto it = values_.find(key);
#endif
if(it != values_.end()) {
return it->second;
}
throw invalid_index();
}
//------------------------------------------------------------------------------
// Name: at
//------------------------------------------------------------------------------
inline value &object::at(const std::string &key) {
#ifdef ORDERED_DICT
auto it = std::find_if(values_.begin(), values_.end(), [&key](const std::pair<std::string, value> &entry) {
return entry.first == key;
});
#else
auto it = values_.find(key);
#endif
if(it != values_.end()) {
return it->second;
}
throw invalid_index();
}
//------------------------------------------------------------------------------
// Name: insert
//------------------------------------------------------------------------------
template <class T>
inline object &object::insert(const std::pair<std::string, T> &p) {
#ifdef ORDERED_DICT
values_.emplace_back(p);
#else
values_.insert(p);
#endif
return *this;
}
//------------------------------------------------------------------------------
// Name: insert
//------------------------------------------------------------------------------
template <class T>
inline object &object::insert(const std::string &key, const T &v) {
#ifdef ORDERED_DICT
values_.emplace_back(std::make_pair(key, value(v)));
return *this;
#else
return insert(std::make_pair(key, value(v)));
#endif
}
//------------------------------------------------------------------------------
// Name: swap
//------------------------------------------------------------------------------
inline void object::swap(object &other) {
using std::swap;
swap(values_, other.values_);
}
//------------------------------------------------------------------------------
// Name: operator==
//------------------------------------------------------------------------------
inline bool operator==(const object &lhs, const object &rhs) {
if(lhs.values_.size() == rhs.values_.size()) {
return lhs.values_ == rhs.values_;
}
return false;
}
//------------------------------------------------------------------------------
// Name: operator!=
//------------------------------------------------------------------------------
inline bool operator!=(const object &lhs, const object &rhs) {
return !(lhs == rhs);
}
}
#endif
#ifndef PARSER_20140115_H_
#define PARSER_20140115_H_
namespace json {
class value;
template <class In>
class parser {
public:
parser(In first, In last);
public:
value parse();
public:
const In begin() const { return begin_; }
const In end() const { return end_; }
In current() const { return cur_; }
private:
static constexpr char ArrayBegin = '[';
static constexpr char ArrayEnd = ']';
static constexpr char NameSeparator = ':';
static constexpr char ValueSeparator = ',';
static constexpr char ObjectBegin = '{';
static constexpr char ObjectEnd = '}';
static constexpr char Quote = '"';
private:
array_pointer get_array();
bool get_false();
bool get_true();
std::nullptr_t get_null();
object_pointer get_object();
std::pair<std::string, value> get_pair();
std::string get_number();
std::string get_string();
value get_value();
private:
char peek();
private:
template <class Tr>
std::string get_number(const Tr &);
std::string get_number(const std::random_access_iterator_tag &);
private:
const In begin_;
In cur_;
const In end_;
};
}
#endif
#ifndef PARSER_20140115_TCC_
#define PARSER_20140115_TCC_
namespace json {
namespace detail {
//------------------------------------------------------------------------------
// Name: to_hex
//------------------------------------------------------------------------------
template <class Ch>
unsigned int to_hex(Ch ch) {
static const int hexval[256] = {
0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0x1, 0x2, 0x3, 0x4, 0x5, 0x6, 0x7, 0x8, 0x9, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0xa, 0xb, 0xc, 0xd, 0xe, 0xf, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0,
0x0, 0xa, 0xb, 0xc, 0xd, 0xe, 0xf, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0
};
if(static_cast<unsigned int>(ch) < 256) {
return hexval[static_cast<unsigned int>(ch)];
} else {
return 0;
}
}
//------------------------------------------------------------------------------
// Name: surrogate_pair_to_utf8
//------------------------------------------------------------------------------
template <class Out>
void surrogate_pair_to_utf8(uint16_t w1, uint16_t w2, Out &out) {
uint32_t cp;
if((w1 & 0xfc00) == 0xd800) {
if((w2 & 0xfc00) == 0xdc00) {
cp = 0x10000 + (((static_cast<uint32_t>(w1) & 0x3ff) << 10) | (w2 & 0x3ff));
} else {
throw invalid_unicode_character();
}
} else {
cp = w1;
}
if(cp < 0x80) {
*out++ = static_cast<uint8_t>(cp);
} else if(cp < 0x0800) {
*out++ = static_cast<uint8_t>(0xc0 | ((cp >> 6) & 0x1f));
*out++ = static_cast<uint8_t>(0x80 | (cp & 0x3f));
} else if(cp < 0x10000) {
*out++ = static_cast<uint8_t>(0xe0 | ((cp >> 12) & 0x0f));
*out++ = static_cast<uint8_t>(0x80 | ((cp >> 6) & 0x3f));
*out++ = static_cast<uint8_t>(0x80 | (cp & 0x3f));
} else if(cp < 0x1fffff) {
*out++ = static_cast<uint8_t>(0xf0 | ((cp >> 18) & 0x07));
*out++ = static_cast<uint8_t>(0x80 | ((cp >> 12) & 0x3f));
*out++ = static_cast<uint8_t>(0x80 | ((cp >> 6) & 0x3f));
*out++ = static_cast<uint8_t>(0x80 | (cp & 0x3f));
}
}
}
//------------------------------------------------------------------------------
// Name: parser
//------------------------------------------------------------------------------
template <class In>
parser<In>::parser(In first, In last) : begin_(first), cur_(first), end_(last) {
}
//------------------------------------------------------------------------------
// Name: parse
//------------------------------------------------------------------------------
template <class In>
value parser<In>::parse() {
return get_value();
}
//------------------------------------------------------------------------------
// Name: peek
//------------------------------------------------------------------------------
template <class In>
char parser<In>::peek() {
// first eat up some whitespace
while(cur_ != end_ && std::isspace(*cur_)) {
++cur_;
}
if(cur_ != end_) {
return *cur_;
}
return '\0';
}
//------------------------------------------------------------------------------
// Name: get_false
//------------------------------------------------------------------------------
template <class In>
bool parser<In>::get_false() {
if(cur_ == end_ || *cur_++ != 'f') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'a') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'l') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 's') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'e') { throw boolean_expected(); }
return false;
}
//------------------------------------------------------------------------------
// Name: get_true
//------------------------------------------------------------------------------
template <class In>
bool parser<In>::get_true() {
if(cur_ == end_ || *cur_++ != 't') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'r') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'u') { throw boolean_expected(); }
if(cur_ == end_ || *cur_++ != 'e') { throw boolean_expected(); }
return true;
}
//------------------------------------------------------------------------------
// Name: get_null
//------------------------------------------------------------------------------
template <class In>
std::nullptr_t parser<In>::get_null() {
if(cur_ == end_ || *cur_++ != 'n') { throw keyword_expected(); }
if(cur_ == end_ || *cur_++ != 'u') { throw keyword_expected(); }
if(cur_ == end_ || *cur_++ != 'l') { throw keyword_expected(); }
if(cur_ == end_ || *cur_++ != 'l') { throw keyword_expected(); }
return nullptr;
}
//------------------------------------------------------------------------------
// Name: get_string
//------------------------------------------------------------------------------
template <class In>
std::string parser<In>::get_string() {
if(peek() != Quote) {
throw string_expected();
}
++cur_;
std::string s;
std::back_insert_iterator<std::string> out = back_inserter(s);
while(cur_ != end_ && *cur_ != Quote && *cur_ != '\n') {
if(*cur_ == '\\') {
++cur_;
if(cur_ != end_) {
switch(*cur_) {
case '"': *out++ = '"'; break;
case '\\': *out++ = '\\'; break;
case '/': *out++ = '/'; break;
case 'b': *out++ = '\b'; break;
case 'f': *out++ = '\f'; break;
case 'n': *out++ = '\n'; break;
case 'r': *out++ = '\r'; break;
case 't': *out++ = '\t'; break;
case 'u':
{
// convert \uXXXX escape sequences to UTF-8
char hex[4];
if(cur_ == end_) { throw hex_character_expected(); } hex[0] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[1] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[2] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[3] = *++cur_;
if(!std::isxdigit(hex[0])) throw invalid_unicode_character();
if(!std::isxdigit(hex[1])) throw invalid_unicode_character();
if(!std::isxdigit(hex[2])) throw invalid_unicode_character();
if(!std::isxdigit(hex[3])) throw invalid_unicode_character();
uint16_t w1 = 0;
uint16_t w2 = 0;
w1 |= (detail::to_hex(hex[0]) << 12);
w1 |= (detail::to_hex(hex[1]) << 8);
w1 |= (detail::to_hex(hex[2]) << 4);
w1 |= (detail::to_hex(hex[3]));
if((w1 & 0xfc00) == 0xdc00) {
throw invalid_unicode_character();
}
if((w1 & 0xfc00) == 0xd800) {
// part of a surrogate pair
if(cur_ == end_ || *++cur_ != '\\') { throw utf16_surrogate_expected(); }
if(cur_ == end_ || *++cur_ != 'u') { throw utf16_surrogate_expected(); }
// convert \uXXXX escape sequences to UTF-8
if(cur_ == end_) { throw hex_character_expected(); } hex[0] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[1] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[2] = *++cur_;
if(cur_ == end_) { throw hex_character_expected(); } hex[3] = *++cur_;
if(!std::isxdigit(hex[0])) throw invalid_unicode_character();
if(!std::isxdigit(hex[1])) throw invalid_unicode_character();
if(!std::isxdigit(hex[2])) throw invalid_unicode_character();
if(!std::isxdigit(hex[3])) throw invalid_unicode_character();
w2 |= (detail::to_hex(hex[0]) << 12);
w2 |= (detail::to_hex(hex[1]) << 8);
w2 |= (detail::to_hex(hex[2]) << 4);
w2 |= (detail::to_hex(hex[3]));
}
detail::surrogate_pair_to_utf8(w1, w2, out);
}
break;
default:
*out++ = '\\';
break;
}
}
} else {
*out++ = *cur_;
}
++cur_;
}
if(*cur_ != Quote || cur_ == end_) {
throw quote_expected();
}
++cur_;
return s;
}
//------------------------------------------------------------------------------
// Name: get_number
// Desc: retrieves a JSON number. we get it as a string in order to defer
// conversion to a numeric type until absolutely necessary
//------------------------------------------------------------------------------
template <class In>
std::string parser<In>::get_number() {
using Cat = typename std::iterator_traits<In>::iterator_category;
return get_number(Cat());
}
//------------------------------------------------------------------------------
// Name: get_number
//------------------------------------------------------------------------------
template <class In>
template <class Tr>
std::string parser<In>::get_number(const Tr &) {
std::string s;
std::back_insert_iterator<std::string> out = back_inserter(s);
// JSON numbers fit the regex: -?(0|[1-9][0-9]*)(\.[0-9]+)?([eE][+-]?[0-9]+)?
// -?
if(cur_ != end_ && *cur_ == '-') {
*out++ = *cur_++;
}
// (0|[1-9][0-9]*)
if(cur_ != end_) {
if(*cur_ >= '1' && *cur_ <= '9') {
do {
*out++ = *cur_++;
} while(cur_ != end_ && std::isdigit(*cur_));
} else if(*cur_ == '0') {
*out++ = *cur_++;
} else {
throw invalid_number();
}
}
// (\.[0-9]+)?
if(cur_ != end_ && *cur_ == '.') {
*out++ = *cur_++;
if(!std::isdigit(*cur_)) {
throw invalid_number();
}
while(cur_ != end_ && std::isdigit(*cur_)) {
*out++ = *cur_++;
}
}
// ([eE][+-]?[0-9]+)?
if(cur_ != end_ && (*cur_ == 'e' || *cur_ == 'E')) {
*out++ = *cur_++;
if(cur_ != end_ && (*cur_ == '+' || *cur_ == '-')) {
*out++ = *cur_++;
}
if(!std::isdigit(*cur_)) {
throw invalid_number();
}
while(cur_ != end_ && std::isdigit(*cur_)) {
*out++ = *cur_++;
}
}
return s;
}
//------------------------------------------------------------------------------
// Name: get_number
// Desc: specialized for random access iterators, so we don't do as much work
//------------------------------------------------------------------------------
template <class In>
std::string parser<In>::get_number(const std::random_access_iterator_tag &) {
const In first = cur_;
// -?
if(cur_ != end_ && *cur_ == '-') {
++cur_;
}
// (0|[1-9][0-9]*)
if(cur_ != end_) {
if(*cur_ >= '1' && *cur_ <= '9') {
do {
++cur_;
} while(cur_ != end_ && std::isdigit(*cur_));
} else if(*cur_ == '0') {
++cur_;
} else {
throw invalid_number();
}
}
// (\.[0-9]+)?
if(cur_ != end_ && *cur_ == '.') {
++cur_;
if(!std::isdigit(*cur_)) {
throw invalid_number();
}
while(cur_ != end_ && std::isdigit(*cur_)) {
++cur_;
}
}
// ([eE][+-]?[0-9]+)?
if(cur_ != end_ && (*cur_ == 'e' || *cur_ == 'E')) {
++cur_;
if(cur_ != end_ && (*cur_ == '+' || *cur_ == '-')) {
++cur_;
}
if(!std::isdigit(*cur_)) {
throw invalid_number();
}
while(cur_ != end_ && std::isdigit(*cur_)) {
++cur_;
}
}
return std::string(first, cur_);
}
//------------------------------------------------------------------------------
// Name: get_object
//------------------------------------------------------------------------------
template <class In>
object_pointer parser<In>::get_object() {
object_pointer obj = std::make_shared<object>();
if(peek() != ObjectBegin) {
throw brace_expected();
}
++cur_;
// handle empty object
char tok = peek();
if(tok == ObjectEnd) {
++cur_;
} else {
do {
#ifdef ORDERED_DICT
obj->values_.emplace_back(get_pair());
#else
obj->values_.insert(get_pair());
#endif
tok = peek();
++cur_;
} while(tok == ValueSeparator);
}
if(tok != ObjectEnd) {
throw brace_expected();
}
return obj;
}
//------------------------------------------------------------------------------
// Name: get_array
//------------------------------------------------------------------------------
template <class In>
array_pointer parser<In>::get_array() {
array_pointer arr = std::make_shared<array>();
if(peek() != ArrayBegin) {
throw bracket_expected();
}
++cur_;
// handle empty object
char tok = peek();
if(tok == ArrayEnd) {
++cur_;
} else {
do {
arr->values_.push_back(get_value());
tok = peek();
++cur_;
} while(tok == ValueSeparator);
}
if(tok != ArrayEnd) {
throw bracket_expected();
}
return arr;
}
//------------------------------------------------------------------------------
// Name: get_pair
// Desc: gets a string : value pair (the contents of a JSON object)
//------------------------------------------------------------------------------
template <class In>
std::pair<std::string, value> parser<In>::get_pair() {
std::string key = get_string();
if(peek() != NameSeparator) {
throw colon_expected();
}
++cur_;
return std::make_pair(key, get_value());
}
//------------------------------------------------------------------------------
// Name: get_value
//------------------------------------------------------------------------------
template <class In>
value parser<In>::get_value() {
switch(peek()) {
case ObjectBegin:
return value(get_object());
case ArrayBegin:
return value(get_array());
case Quote:
return value(get_string());
case 't':
return value(get_true());
case 'f':
return value(get_false());
case 'n':
return value(get_null());
default:
return value(get_number(), value::numeric_t());
}
throw value_expected();
}
}
#endif
#ifndef VALUE_20110526_H_
#define VALUE_20110526_H_
namespace json {
class array;
class object;
namespace detail {
template <class T>
constexpr T static_max(T n) {
return n;
}
template <class T, class ... Args>
constexpr T static_max(T n, Args ... args) {
return n > static_max(args...) ? n : static_max(args...);
}
template <class... Types>
struct aligned_traits {
static constexpr std::size_t alignment_value = static_max(alignof(Types)...);
static constexpr std::size_t size_value = static_max(sizeof(Types)...);
};
}
class value {
friend bool is_string(const value &v);
friend bool is_bool(const value &v);
friend bool is_number(const value &v);
friend bool is_object(const value &v);
friend bool is_array(const value &v);
friend bool is_null(const value &v);
friend std::string to_string(const value &v);
friend bool to_bool(const value &v);
friend double to_number(const value &v);
friend object to_object(const value &v);
friend array to_array(const value &v);
friend const object &as_object(const value &v);
friend object &as_object(value &v);
friend const array &as_array(const value &v);
friend array &as_array(value &v);
friend const std::string &as_string(const value &v);
friend std::string &as_string(value &v);
friend bool has_key(const value &v, const std::string &key);
friend bool operator==(const value &lhs, const value &rhs);
friend bool operator!=(const value &lhs, const value &rhs);
template <class In>
friend class parser;
private:
struct numeric_t {};
// create a value from a numeric string, internal use only!
value(std::string s, const numeric_t &);
public:
// intialize from basic types
value(bool b);
value(const array &a);
value(const char *s);
value(const object &o);
value(std::string s);
template <class T, typename = typename std::enable_if<std::is_arithmetic<T>::value>::type>
value(T n);
value(const std::nullptr_t &);
public:
value();
~value();
public:
explicit value(object_pointer o);
explicit value(array_pointer a);
public:
value(const value &other);
value &operator=(const value &rhs);
public:
void swap(value &other);
public:
enum type {
type_invalid,
type_string,
type_number,
type_object,
type_array,
type_boolean,
type_null
};
public:
const value operator[](const std::string &key) const;
const value operator[](std::size_t n) const;
value &operator[](const std::string &key);
value &operator[](std::size_t n);
private:
const std::string &as_string() const;
std::string &as_string();
const object &as_object() const;
object &as_object();
const array &as_array() const;
array &as_array();
private:
struct invalid_t {};
// I would love to use std::aligned_union, but it doesn't seem widely supported
// so instead, we kinda make our own, first we need a type which has the correct
// size and alignment requirements based on the types we want to store
using Tr = detail::aligned_traits<invalid_t, object_pointer, array_pointer, std::string>;
struct storage_type {
alignas(Tr::alignment_value) uint8_t data[Tr::size_value];
};
storage_type value_;
type type_;
};
bool operator==(const value &lhs, const value &rhs);
bool operator!=(const value &lhs, const value &rhs);
}
#endif
#ifndef VALUE_20120424_TCC_
#define VALUE_20120424_TCC_
namespace json {
//------------------------------------------------------------------------------
// Name: ~value
//------------------------------------------------------------------------------
inline value::~value() {
using std::string;
switch(type_) {
case value::type_string:
case value::type_number:
case value::type_null:
case value::type_boolean:
reinterpret_cast<std::string *>(&value_)->~string();
break;
case value::type_array:
reinterpret_cast<array_pointer *>(&value_)->~array_pointer();
break;
case value::type_object:
reinterpret_cast<object_pointer *>(&value_)->~object_pointer();
break;
case value::type_invalid:
break;
}
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value() : type_(type_invalid) {
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(const std::nullptr_t &): type_(type_null) {
new (&value_) std::string("null");
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(object_pointer o) : type_(type_object) {
new (&value_) object_pointer(std::move(o));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(array_pointer a) : type_(type_array) {
new (&value_) array_pointer(std::move(a));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(std::string s, const numeric_t &) : type_(type_number) {
new (&value_) std::string(std::move(s));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(std::string s) : type_(type_string) {
new (&value_) std::string(std::move(s));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
template <class T, typename>
value::value(T n) : type_(type_number) {
new (&value_) std::string(std::to_string(n));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(const char *s) : type_(type_string) {
new (&value_) std::string(s);
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(bool b) : type_(type_boolean) {
new (&value_) std::string(b ? "true" : "false");
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(const value &other) : type_(other.type_) {
// copy from the other object
switch(type_) {
case value::type_string:
case value::type_number:
case value::type_null:
case value::type_boolean:
new (&value_) std::string(*reinterpret_cast<const std::string *>(&other.value_));
break;
case value::type_array:
new (&value_) array_pointer(*reinterpret_cast<const array_pointer *>(&other.value_));
break;
case value::type_object:
new (&value_) object_pointer(*reinterpret_cast<const object_pointer *>(&other.value_));
break;
case value::type_invalid:
break;
}
}
//------------------------------------------------------------------------------
// Name: operator=
//------------------------------------------------------------------------------
inline value &value::operator=(const value &rhs) {
if(this != &rhs) {
value(rhs).swap(*this);
}
return *this;
}
//------------------------------------------------------------------------------
// Name: swap
//------------------------------------------------------------------------------
inline void value::swap(value &other) {
using std::swap;
swap(value_, other.value_);
swap(type_, other.type_);
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline const value value::operator[](const std::string &key) const {
return as_object()[key];
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline const value value::operator[](std::size_t n) const {
return as_array()[n];
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline value &value::operator[](const std::string &key) {
return as_object()[key];
}
//------------------------------------------------------------------------------
// Name: operator[]
//------------------------------------------------------------------------------
inline value &value::operator[](std::size_t n) {
return as_array()[n];
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(const array &a) : type_(type_array) {
new (&value_) array_pointer(std::make_shared<array>(a));
}
//------------------------------------------------------------------------------
// Name: value
//------------------------------------------------------------------------------
inline value::value(const object &o) : type_(type_object) {
new (&value_) object_pointer(std::make_shared<object>(o));
}
//------------------------------------------------------------------------------
// Name: operator==
//------------------------------------------------------------------------------
inline bool operator==(const value &lhs, const value &rhs) {
if(lhs.type_ == rhs.type_) {
switch(lhs.type_) {
case value::type_string:
return as_string(lhs) == as_string(rhs);
case value::type_number:
return to_number(lhs) == to_number(rhs);
case value::type_null:
return true;
case value::type_boolean:
return to_bool(lhs) == to_bool(rhs);
case value::type_array:
return as_array(lhs) == as_array(rhs);
case value::type_object:
return as_object(lhs) == as_object(rhs);
case value::type_invalid:
break;
}
}
return false;
}
//------------------------------------------------------------------------------
// Name: operator!=
//------------------------------------------------------------------------------
inline bool operator!=(const value &lhs, const value &rhs) {
return !(lhs == rhs);
}
//------------------------------------------------------------------------------
// Name: as_string
//------------------------------------------------------------------------------
inline const std::string &value::as_string() const {
switch(type_) {
case value::type_string:
case value::type_number:
case value::type_null:
case value::type_boolean:
return *reinterpret_cast<const std::string *>(&value_);
default:
throw invalid_type_cast();
}
}
//------------------------------------------------------------------------------
// Name: as_string
//------------------------------------------------------------------------------
inline std::string &value::as_string() {
switch(type_) {
case value::type_string:
case value::type_number:
case value::type_null:
case value::type_boolean:
return *reinterpret_cast<std::string *>(&value_);
default:
throw invalid_type_cast();
}
}
//------------------------------------------------------------------------------
// Name: as_object
//------------------------------------------------------------------------------
inline const object &value::as_object() const {
if(type_ != type_object) {
throw invalid_type_cast();
}
return **reinterpret_cast<const object_pointer *>(&value_);
}
//------------------------------------------------------------------------------
// Name: as_object
//------------------------------------------------------------------------------
inline object &value::as_object() {
if(type_ != type_object) {
throw invalid_type_cast();
}
return **reinterpret_cast<object_pointer *>(&value_);
}
//------------------------------------------------------------------------------
// Name: as_array
//------------------------------------------------------------------------------
inline const array &value::as_array() const {
if(type_ != type_array) {
throw invalid_type_cast();
}
return **reinterpret_cast<const array_pointer *>(&value_);
}
//------------------------------------------------------------------------------
// Name: as_array
//------------------------------------------------------------------------------
inline array &value::as_array() {
if(type_ != type_array) {
throw invalid_type_cast();
}
return **reinterpret_cast<array_pointer *>(&value_);
}
}
#endif
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment