hgreet-0.1.0.0: Haskell module to interact with the greetd daemon trough it's IPC protocol.
Safe HaskellNone
LanguageHaskell2010

HGreet.Packet

Synopsis

Documentation

data Request Source #

Constructors

CreateSession

Creates a session and initiates a login atempted for the given user. The session is ready to be started if a success is returned.

Fields

PostAuthMessageResponse

Answers an authentication message. If the message was informative (info, error), then a response does not need to be set in this message. Tht session is ready to be started if a success is returned.

Fields

StartSession

Requests for the session to be started using the provided command line. The session will start after the greeter process terminates.

Fields

CancelSession

Cancel the session that is currently under configuration.

Instances

Instances details
Eq Request Source # 
Instance details

Defined in HGreet.Packet

Methods

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

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

Show Request Source # 
Instance details

Defined in HGreet.Packet

Generic Request Source # 
Instance details

Defined in HGreet.Packet

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

ToJSON Request Source # 
Instance details

Defined in HGreet.Packet

type Rep Request Source # 
Instance details

Defined in HGreet.Packet

type Rep Request = D1 ('MetaData "Request" "HGreet.Packet" "hgreet-0.1.0.0-L18MbcRjDZbE3raonslubm" 'False) ((C1 ('MetaCons "CreateSession" 'PrefixI 'True) (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PostAuthMessageResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "respone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :+: (C1 ('MetaCons "StartSession" 'PrefixI 'True) (S1 ('MetaSel ('Just "cmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "CancelSession" 'PrefixI 'False) (U1 :: Type -> Type)))

data Response Source #

Constructors

Success

Indicates that the request succeeded.

Error

Indicates that the request failed.

AuthMessage

Indicates that an authentication message needs to be answered to continue trough the authenticaltion flow. There are no limits on the number and type of messages that may be required for authentication to succeed, and a greeter should not make any assumptions about the messages. Must be answerd with either PostAuthMessageResponse or CancelSession.

Instances

Instances details
Eq Response Source # 
Instance details

Defined in HGreet.Packet

Show Response Source # 
Instance details

Defined in HGreet.Packet

Generic Response Source # 
Instance details

Defined in HGreet.Packet

Associated Types

type Rep Response :: Type -> Type #

Methods

from :: Response -> Rep Response x #

to :: Rep Response x -> Response #

FromJSON Response Source # 
Instance details

Defined in HGreet.Packet

type Rep Response Source # 
Instance details

Defined in HGreet.Packet

type Rep Response = D1 ('MetaData "Response" "HGreet.Packet" "hgreet-0.1.0.0-L18MbcRjDZbE3raonslubm" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Error" 'PrefixI 'True) (S1 ('MetaSel ('Just "error_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrorType) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "AuthMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "auth_message_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AuthMessageType) :*: S1 ('MetaSel ('Just "auth_message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data AuthMessageType Source #

Constructors

Visible

Indicates that the input from the user should be visible when they answer this question.

Secret

Indicates that input from the user should be considered secret when they answer this question.

Info

Indicates that this message is informative, not a question.

ErrorType

Indicates that this message is an error, not a question.

data ErrorType Source #

Constructors

AuthError

Indicates that authentication failed. THis is not a fatal error, and is likely caused by incorrect credentials. Handle as appropriate.

OtherError

A general error. See the error description for more information.

Instances

Instances details
Eq ErrorType Source # 
Instance details

Defined in HGreet.Packet

Show ErrorType Source # 
Instance details

Defined in HGreet.Packet

FromJSON ErrorType Source # 
Instance details

Defined in HGreet.Packet

encodeRequest Source #

Arguments

:: Request

Raw Request packet to encode.

-> ByteString

Encoded Request packet.

Encode a Request packet as a UTF-8 JSON ByteString to be sent to the greetd socket.

decodeResponse Source #

Arguments

:: ByteString

Encoded Response packet.

-> Response

Decoded raw Response packet.

Decode a Response packet from a ByteString received from the greetd socket.

encodeLen :: Int -> ByteString Source #

Encode a length as a 32-bit integer in native byte order encapsulated in a Lazy ByteString.

decodeLen :: ByteString -> Int Source #

Decode a length as a 32-bit integer in native byte order from a Lazy ByteString.