wsjtx-udp-0.1.0.6: WSJT-X UDP protocol

Copyright(c) Marc Fontaine 2017-2018
LicenseBSD3
MaintainerMarc.Fontaine@gmx.de
Stabilityexperimental
PortabilityGHC-only
Safe HaskellNone
LanguageHaskell2010

WSJTX.UDP.NetworkMessage

Contents

Description

The package types of the WSJT-X UDP protocol. See NetworkMessage.hpp in WSJT-X sources.

Documentation

data Heartbeat Source #

Instances

Eq Heartbeat Source # 
Read Heartbeat Source # 
Show Heartbeat Source # 
Generic Heartbeat Source # 

Associated Types

type Rep Heartbeat :: * -> * #

ToJSON Heartbeat Source # 
FromJSON Heartbeat Source # 
type Rep Heartbeat Source # 
type Rep Heartbeat = D1 * (MetaData "Heartbeat" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Heartbeat" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "heartbeat_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "heartbeat_maximum_schema_number") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32))) ((:*:) * (S1 * (MetaSel (Just Symbol "heartbeat_version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "heartbeat_revision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

data Status Source #

Instances

Eq Status Source # 

Methods

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

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

Read Status Source # 
Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
FromJSON Status Source # 
type Rep Status Source # 
type Rep Status = D1 * (MetaData "Status" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Status" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "status_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "status_dial_frequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64))) ((:*:) * (S1 * (MetaSel (Just Symbol "status_mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "status_dx_call") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "status_report") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "status_tx_mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "status_tx_enabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "status_transmitting") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "status_decoding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "status_rx_df") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32))) ((:*:) * (S1 * (MetaSel (Just Symbol "status_tx_df") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "status_de_call") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "status_de_grid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "status_dx_grid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "status_tx_watchdog") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "status_submode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "status_fast_mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))))))

data Decode Source #

Instances

Eq Decode Source # 

Methods

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

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

Read Decode Source # 
Show Decode Source # 
Generic Decode Source # 

Associated Types

type Rep Decode :: * -> * #

Methods

from :: Decode -> Rep Decode x #

to :: Rep Decode x -> Decode #

ToJSON Decode Source # 
FromJSON Decode Source # 
type Rep Decode Source # 

data Clear Source #

Constructors

Clear 

Instances

Eq Clear Source # 

Methods

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

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

Read Clear Source # 
Show Clear Source # 

Methods

showsPrec :: Int -> Clear -> ShowS #

show :: Clear -> String #

showList :: [Clear] -> ShowS #

Generic Clear Source # 

Associated Types

type Rep Clear :: * -> * #

Methods

from :: Clear -> Rep Clear x #

to :: Rep Clear x -> Clear #

ToJSON Clear Source # 
FromJSON Clear Source # 
type Rep Clear Source # 
type Rep Clear = D1 * (MetaData "Clear" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Clear" PrefixI True) (S1 * (MetaSel (Just Symbol "clear_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Reply Source #

Instances

Eq Reply Source # 

Methods

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

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

Read Reply Source # 
Show Reply Source # 

Methods

showsPrec :: Int -> Reply -> ShowS #

show :: Reply -> String #

showList :: [Reply] -> ShowS #

Generic Reply Source # 

Associated Types

type Rep Reply :: * -> * #

Methods

from :: Reply -> Rep Reply x #

to :: Rep Reply x -> Reply #

ToJSON Reply Source # 
FromJSON Reply Source # 
type Rep Reply Source # 

data Logged Source #

Instances

Eq Logged Source # 

Methods

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

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

Read Logged Source # 
Show Logged Source # 
Generic Logged Source # 

Associated Types

type Rep Logged :: * -> * #

Methods

from :: Logged -> Rep Logged x #

to :: Rep Logged x -> Logged #

ToJSON Logged Source # 
FromJSON Logged Source # 
type Rep Logged Source # 
type Rep Logged = D1 * (MetaData "Logged" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Logged" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "logged_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_date_time_off") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64)) (S1 * (MetaSel (Just Symbol "logged_dx_call") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_dx_grid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_dial_frequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64)) (S1 * (MetaSel (Just Symbol "logged_mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "logged_report_send") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_report_received") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "logged_tx_power") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_comments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "logged_name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "logged_date_time_on") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64)))))))

data Close Source #

Constructors

Close 

Instances

Eq Close Source # 

Methods

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

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

Read Close Source # 
Show Close Source # 

Methods

showsPrec :: Int -> Close -> ShowS #

show :: Close -> String #

showList :: [Close] -> ShowS #

Generic Close Source # 

Associated Types

type Rep Close :: * -> * #

Methods

from :: Close -> Rep Close x #

to :: Rep Close x -> Close #

ToJSON Close Source # 
FromJSON Close Source # 
type Rep Close Source # 
type Rep Close = D1 * (MetaData "Close" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Close" PrefixI True) (S1 * (MetaSel (Just Symbol "close_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Replay Source #

Constructors

Replay 

Instances

Eq Replay Source # 

Methods

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

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

Read Replay Source # 
Show Replay Source # 
Generic Replay Source # 

Associated Types

type Rep Replay :: * -> * #

Methods

from :: Replay -> Rep Replay x #

to :: Rep Replay x -> Replay #

ToJSON Replay Source # 
FromJSON Replay Source # 
type Rep Replay Source # 
type Rep Replay = D1 * (MetaData "Replay" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "Replay" PrefixI True) (S1 * (MetaSel (Just Symbol "replay_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data HaltTx Source #

Instances

Eq HaltTx Source # 

Methods

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

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

Read HaltTx Source # 
Show HaltTx Source # 
Generic HaltTx Source # 

Associated Types

type Rep HaltTx :: * -> * #

Methods

from :: HaltTx -> Rep HaltTx x #

to :: Rep HaltTx x -> HaltTx #

ToJSON HaltTx Source # 
FromJSON HaltTx Source # 
type Rep HaltTx Source # 
type Rep HaltTx = D1 * (MetaData "HaltTx" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) (C1 * (MetaCons "HaltTx" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "haltTx_client_id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "haltTx_auto_tx_only") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))

data FreeText Source #

data Package Source #

Instances

Eq Package Source # 

Methods

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

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

Read Package Source # 
Show Package Source # 
Generic Package Source # 

Associated Types

type Rep Package :: * -> * #

Methods

from :: Package -> Rep Package x #

to :: Rep Package x -> Package #

ToJSON Package Source # 
FromJSON Package Source # 
type Rep Package Source # 
type Rep Package = D1 * (MetaData "Package" "WSJTX.UDP.NetworkMessage" "wsjtx-udp-0.1.0.6-F3knoFZgLyJGFzhYwISN3d" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PHeartbeat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Heartbeat))) (C1 * (MetaCons "PStatus" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Status)))) ((:+:) * (C1 * (MetaCons "PDecode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Decode))) ((:+:) * (C1 * (MetaCons "PClear" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Clear))) (C1 * (MetaCons "PReply" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Reply)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PLogged" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Logged))) ((:+:) * (C1 * (MetaCons "PClose" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Close))) (C1 * (MetaCons "PReplay" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Replay))))) ((:+:) * (C1 * (MetaCons "PHaltTx" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HaltTx))) ((:+:) * (C1 * (MetaCons "PFreeText" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FreeText))) (C1 * (MetaCons "OtherPackage" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Word8])))))))

Orphan instances