argo-0.2022.2.23: Parse and render JSON.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Argo

Synopsis

Documentation

data Value where Source #

A JSON (JavaScript Object Notation) value, as described by RFC 8259. https://datatracker.ietf.org/doc/html/rfc8259

Bundled Patterns

pattern Array :: [Value] -> Value 
pattern Boolean :: Bool -> Value 
pattern Null :: Value 
pattern Number :: Decimal -> Value 
pattern Object :: [Member Value] -> Value 
pattern String :: Text -> Value 

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Argo.Json.Value

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 
Instance details

Defined in Argo.Json.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source # 
Instance details

Defined in Argo.Json.Value

Methods

fromString :: String -> Value #

Generic Value Source # 
Instance details

Defined in Argo.Json.Value

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value Source # 
Instance details

Defined in Argo.Json.Value

Methods

rnf :: Value -> () #

HasCodec Value Source # 
Instance details

Defined in Argo.Class.HasCodec

Lift Value Source # 
Instance details

Defined in Argo.Json.Value

Methods

lift :: Value -> Q Exp #

liftTyped :: Value -> Q (TExp Value) #

type Rep Value Source # 
Instance details

Defined in Argo.Json.Value

data Name where Source #

Bundled Patterns

pattern Name :: Text -> Name 

Instances

Instances details
Eq Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in Argo.Json.Name

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

rnf :: Name -> () #

HasCodec Name Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Name Source #

Lift Name Source # 
Instance details

Defined in Argo.Json.Name

Methods

lift :: Name -> Q Exp #

liftTyped :: Name -> Q (TExp Name) #

HasCodec a => HasCodec (Map Name a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Map Name a) Source #

type Rep Name Source # 
Instance details

Defined in Argo.Json.Name

type Rep Name = D1 ('MetaData "Name" "Argo.Json.Name" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'True) (C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Member value Source #

Constructors

Member Name value 

Instances

Instances details
Lift value => Lift (Member value :: Type) Source # 
Instance details

Defined in Argo.Json.Member

Methods

lift :: Member value -> Q Exp #

liftTyped :: Member value -> Q (TExp (Member value)) #

Eq value => Eq (Member value) Source # 
Instance details

Defined in Argo.Json.Member

Methods

(==) :: Member value -> Member value -> Bool #

(/=) :: Member value -> Member value -> Bool #

Show value => Show (Member value) Source # 
Instance details

Defined in Argo.Json.Member

Methods

showsPrec :: Int -> Member value -> ShowS #

show :: Member value -> String #

showList :: [Member value] -> ShowS #

Generic (Member value) Source # 
Instance details

Defined in Argo.Json.Member

Associated Types

type Rep (Member value) :: Type -> Type #

Methods

from :: Member value -> Rep (Member value) x #

to :: Rep (Member value) x -> Member value #

NFData value => NFData (Member value) Source # 
Instance details

Defined in Argo.Json.Member

Methods

rnf :: Member value -> () #

type Rep (Member value) Source # 
Instance details

Defined in Argo.Json.Member

type Rep (Member value) = D1 ('MetaData "Member" "Argo.Json.Member" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'False) (C1 ('MetaCons "Member" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 value)))

data Indent Source #

Constructors

Spaces Int 
Tab 

Instances

Instances details
Eq Indent Source # 
Instance details

Defined in Argo.Type.Indent

Methods

(==) :: Indent -> Indent -> Bool #

(/=) :: Indent -> Indent -> Bool #

Show Indent Source # 
Instance details

Defined in Argo.Type.Indent

class Typeable a => HasCodec a where Source #

Methods

codec :: Value a Source #

Instances

Instances details
HasCodec Bool Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Bool Source #

HasCodec Char Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Char Source #

HasCodec Double Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Float Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Int Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Int Source #

HasCodec Int8 Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Int8 Source #

HasCodec Int16 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Int32 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Int64 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Integer Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Natural Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Word Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Word Source #

HasCodec Word8 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Word16 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Word32 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Word64 Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec () Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value () Source #

HasCodec String Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Text Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Text Source #

HasCodec Decimal Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Identifier Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec String Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Name Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Name Source #

HasCodec Number Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Null Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value Null Source #

HasCodec Boolean Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Value Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Schema Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec Pointer Source # 
Instance details

Defined in Argo.Class.HasCodec

HasCodec a => HasCodec [a] Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value [a] Source #

HasCodec a => HasCodec (Maybe a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Maybe a) Source #

HasCodec a => HasCodec (NonEmpty a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (NonEmpty a) Source #

HasCodec a => HasCodec (Nullable a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Nullable a) Source #

HasCodec a => HasCodec (Object a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Object a) Source #

HasCodec a => HasCodec (Array a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Array a) Source #

(HasCodec a, HasCodec b) => HasCodec (Either a b) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Either a b) Source #

(HasCodec a, HasCodec b) => HasCodec (a, b) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b) Source #

HasCodec a => HasCodec (Map String a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Map String a) Source #

HasCodec a => HasCodec (Map Text a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Map Text a) Source #

HasCodec a => HasCodec (Map String a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Map String a) Source #

HasCodec a => HasCodec (Map Name a) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (Map Name a) Source #

(HasCodec a, HasCodec b, HasCodec c) => HasCodec (a, b, c) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c) Source #

(HasCodec a, HasCodec b, HasCodec c, HasCodec d) => HasCodec (a, b, c, d) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c, d) Source #

(HasCodec a, HasCodec b, HasCodec c, HasCodec d, HasCodec e) => HasCodec (a, b, c, d, e) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c, d, e) Source #

(HasCodec a, HasCodec b, HasCodec c, HasCodec d, HasCodec e, HasCodec f) => HasCodec (a, b, c, d, e, f) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c, d, e, f) Source #

(HasCodec a, HasCodec b, HasCodec c, HasCodec d, HasCodec e, HasCodec f, HasCodec g) => HasCodec (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c, d, e, f, g) Source #

(HasCodec a, HasCodec b, HasCodec c, HasCodec d, HasCodec e, HasCodec f, HasCodec g, HasCodec h) => HasCodec (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Argo.Class.HasCodec

Methods

codec :: Value (a, b, c, d, e, f, g, h) Source #

newtype Pointer Source #

A JSON pointer, as described by RFC 6901. https://datatracker.ietf.org/doc/html/rfc6901

Constructors

Pointer [Token] 

Instances

Instances details
Eq Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

Methods

(==) :: Pointer -> Pointer -> Bool #

(/=) :: Pointer -> Pointer -> Bool #

Show Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

Generic Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

Associated Types

type Rep Pointer :: Type -> Type #

Methods

from :: Pointer -> Rep Pointer x #

to :: Rep Pointer x -> Pointer #

NFData Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

Methods

rnf :: Pointer -> () #

HasCodec Pointer Source # 
Instance details

Defined in Argo.Class.HasCodec

Lift Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

Methods

lift :: Pointer -> Q Exp #

liftTyped :: Pointer -> Q (TExp Pointer) #

type Rep Pointer Source # 
Instance details

Defined in Argo.Pointer.Pointer

type Rep Pointer = D1 ('MetaData "Pointer" "Argo.Pointer.Pointer" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'True) (C1 ('MetaCons "Pointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Token])))

newtype Token Source #

Constructors

Token Text 

Instances

Instances details
Eq Token Source # 
Instance details

Defined in Argo.Pointer.Token

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Show Token Source # 
Instance details

Defined in Argo.Pointer.Token

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

IsString Token Source # 
Instance details

Defined in Argo.Pointer.Token

Methods

fromString :: String -> Token #

Generic Token Source # 
Instance details

Defined in Argo.Pointer.Token

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

NFData Token Source # 
Instance details

Defined in Argo.Pointer.Token

Methods

rnf :: Token -> () #

Lift Token Source # 
Instance details

Defined in Argo.Pointer.Token

Methods

lift :: Token -> Q Exp #

liftTyped :: Token -> Q (TExp Token) #

type Rep Token Source # 
Instance details

Defined in Argo.Pointer.Token

type Rep Token = D1 ('MetaData "Token" "Argo.Pointer.Token" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'True) (C1 ('MetaCons "Token" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Decimal where Source #

Bundled Patterns

pattern Decimal :: Integer -> Integer -> Decimal 

Instances

Instances details
Eq Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

Methods

(==) :: Decimal -> Decimal -> Bool #

(/=) :: Decimal -> Decimal -> Bool #

Show Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

Generic Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

Associated Types

type Rep Decimal :: Type -> Type #

Methods

from :: Decimal -> Rep Decimal x #

to :: Rep Decimal x -> Decimal #

NFData Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

Methods

rnf :: Decimal -> () #

HasCodec Decimal Source # 
Instance details

Defined in Argo.Class.HasCodec

Lift Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

Methods

lift :: Decimal -> Q Exp #

liftTyped :: Decimal -> Q (TExp Decimal) #

type Rep Decimal Source # 
Instance details

Defined in Argo.Type.Decimal

type Rep Decimal = D1 ('MetaData "Decimal" "Argo.Type.Decimal" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'False) (C1 ('MetaCons "Decimal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data Schema Source #

Instances

Instances details
Eq Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Methods

(==) :: Schema -> Schema -> Bool #

(/=) :: Schema -> Schema -> Bool #

Show Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Generic Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Associated Types

type Rep Schema :: Type -> Type #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Semigroup Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Monoid Schema Source # 
Instance details

Defined in Argo.Schema.Schema

NFData Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Methods

rnf :: Schema -> () #

HasCodec Schema Source # 
Instance details

Defined in Argo.Class.HasCodec

Lift Schema Source # 
Instance details

Defined in Argo.Schema.Schema

Methods

lift :: Schema -> Q Exp #

liftTyped :: Schema -> Q (TExp Schema) #

type Rep Schema Source # 
Instance details

Defined in Argo.Schema.Schema

type Rep Schema = D1 ('MetaData "Schema" "Argo.Schema.Schema" "argo-0.2022.2.23-4XPruXmLyuVHtCz0cP5FeE" 'False) (((C1 ('MetaCons "Array" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Schema (NonEmpty Schema))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Schema)))) :+: (C1 ('MetaCons "Boolean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Const" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))) :+: (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Integer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer))) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Number" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Name, Schema)]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Schema)))) :+: C1 ('MetaCons "OneOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Schema])))) :+: (C1 ('MetaCons "Ref" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier)) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type)))))