cdp-0.0.2.0: A library for the Chrome Devtools Protocol
Safe HaskellNone
LanguageHaskell2010

CDP.Definition

Synopsis

Documentation

data Version Source #

Constructors

Version 

Instances

Instances details
Eq Version Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Version Source # 
Instance details

Defined in CDP.Definition

Generic Version Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

FromJSON Version Source # 
Instance details

Defined in CDP.Definition

type Rep Version Source # 
Instance details

Defined in CDP.Definition

type Rep Version = D1 ('MetaData "Version" "CDP.Definition" "cdp-0.0.2.0-inplace" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionMinor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "versionMajor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Items Source #

Constructors

Items 

Instances

Instances details
Eq Items Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Items Source # 
Instance details

Defined in CDP.Definition

Methods

showsPrec :: Int -> Items -> ShowS #

show :: Items -> String #

showList :: [Items] -> ShowS #

Generic Items Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Items :: Type -> Type #

Methods

from :: Items -> Rep Items x #

to :: Rep Items x -> Items #

FromJSON Items Source # 
Instance details

Defined in CDP.Definition

type Rep Items Source # 
Instance details

Defined in CDP.Definition

type Rep Items = D1 ('MetaData "Items" "CDP.Definition" "cdp-0.0.2.0-inplace" 'False) (C1 ('MetaCons "Items" 'PrefixI 'True) (S1 ('MetaSel ('Just "itemsType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "itemsRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data Property Source #

Instances

Instances details
Eq Property Source # 
Instance details

Defined in CDP.Definition

Show Property Source # 
Instance details

Defined in CDP.Definition

Generic Property Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Property :: Type -> Type #

Methods

from :: Property -> Rep Property x #

to :: Rep Property x -> Property #

FromJSON Property Source # 
Instance details

Defined in CDP.Definition

type Rep Property Source # 
Instance details

Defined in CDP.Definition

data Command Source #

Instances

Instances details
Eq Command Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Command Source # 
Instance details

Defined in CDP.Definition

Generic Command Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Command :: Type -> Type #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

FromJSON Command Source # 
Instance details

Defined in CDP.Definition

type Rep Command Source # 
Instance details

Defined in CDP.Definition

data Type Source #

Instances

Instances details
Eq Type Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Type Source # 
Instance details

Defined in CDP.Definition

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

FromJSON Type Source # 
Instance details

Defined in CDP.Definition

type Rep Type Source # 
Instance details

Defined in CDP.Definition

data Event Source #

Instances

Instances details
Eq Event Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Event Source # 
Instance details

Defined in CDP.Definition

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

FromJSON Event Source # 
Instance details

Defined in CDP.Definition

type Rep Event Source # 
Instance details

Defined in CDP.Definition

type Rep Event = D1 ('MetaData "Event" "CDP.Definition" "cdp-0.0.2.0-inplace" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) ((S1 ('MetaSel ('Just "eventExperimental") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "eventName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "eventParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Property]) :*: (S1 ('MetaSel ('Just "eventDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "eventDeprecated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

data Domain Source #

Instances

Instances details
Eq Domain Source # 
Instance details

Defined in CDP.Definition

Methods

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

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

Show Domain Source # 
Instance details

Defined in CDP.Definition

Generic Domain Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep Domain :: Type -> Type #

Methods

from :: Domain -> Rep Domain x #

to :: Rep Domain x -> Domain #

FromJSON Domain Source # 
Instance details

Defined in CDP.Definition

type Rep Domain Source # 
Instance details

Defined in CDP.Definition

data TopLevel Source #

Constructors

TopLevel 

Instances

Instances details
Eq TopLevel Source # 
Instance details

Defined in CDP.Definition

Show TopLevel Source # 
Instance details

Defined in CDP.Definition

Generic TopLevel Source # 
Instance details

Defined in CDP.Definition

Associated Types

type Rep TopLevel :: Type -> Type #

Methods

from :: TopLevel -> Rep TopLevel x #

to :: Rep TopLevel x -> TopLevel #

FromJSON TopLevel Source # 
Instance details

Defined in CDP.Definition

type Rep TopLevel Source # 
Instance details

Defined in CDP.Definition

type Rep TopLevel = D1 ('MetaData "TopLevel" "CDP.Definition" "cdp-0.0.2.0-inplace" 'False) (C1 ('MetaCons "TopLevel" 'PrefixI 'True) (S1 ('MetaSel ('Just "topLevelVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version) :*: S1 ('MetaSel ('Just "topLevelDomains") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Domain])))

parse :: FilePath -> IO TopLevel Source #

Use parser to get TopLevel object