-- Copyright (c) 2010 John Millikin
--
-- 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.

module Data.JSON.Types
	( -- * DOM-based
	  Root (..)
	, Object
	, Array
	, Value (..)
	, Atom (..)
	
	-- * Event-based
	, Event (..)
	) where
import Data.Map (Map)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Data.String (IsString, fromString)

-- | Each JSON document has a single /root/, which may be either an 'Object'
-- or 'Array'.
--
-- Some parsers allow non-container roots, but portable libraries should
-- not depend on this incorrect behavior.
data Root
	= RootObject Object
	| RootArray Array
	deriving (Show, Eq)

-- | Objects store unordered associations between textual keys and 'Value's.
type Object = Map Text Value

-- | Arrays are ordered sequences of 'Value's.
type Array = [Value]

data Value
	= ValueObject Object
	| ValueArray Array
	| ValueAtom Atom
	deriving (Show, Eq)

instance IsString Value where
	fromString = ValueAtom . fromString

data Atom
	= AtomNull
	| AtomBoolean Bool
	
	-- | JSON numbers may be of arbitrary length and precision. Using
	-- 'Rational' allows any valid parsed number to be stored; however,
	-- note that only rationals with a finite decimal expansion can be
	-- fully serialized. For example, attempting to serialize @(1 % 3)@
	-- will lose precision.
	| AtomNumber Rational
	
	| AtomText Text
	deriving (Show, Eq)

instance IsString Atom where
	fromString = AtomText . T.pack

data Event
	= EventBeginObject
	| EventEndObject
	| EventBeginArray
	| EventEndArray
	| EventAttributeName Text
	| EventAtom Atom
	deriving (Show, Eq)