hnix-store-remote-0.7.0.0: Remote hnix store
Copyright(c) John Ericson 2023
Sorki 2023
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Nix.Store.Remote.Serializer

Description

|

Synopsis

NixSerializer

type NixSerializer r e = Serializer (SerialT r e) Source #

mapReaderS :: (r' -> r) -> NixSerializer r e a -> NixSerializer r' e a Source #

mapErrorS :: (e -> e') -> NixSerializer r e a -> NixSerializer r e' a Source #

Errors

data SError Source #

Instances

Instances details
Generic SError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Associated Types

type Rep SError :: Type -> Type #

Methods

from :: SError -> Rep SError x #

to :: Rep SError x -> SError #

Show SError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Eq SError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Methods

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

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

Ord SError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep SError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep SError

Runners

runSerialT :: Monad m => r -> SerialT r e m a -> m (Either e a) Source #

Runner for SerialT

runP :: NixSerializer r e a -> r -> a -> Either e ByteString Source #

Primitives

UTCTime

Combinators

set :: Ord a => NixSerializer r e a -> NixSerializer r e (Set a) Source #

mapS :: Ord k => NixSerializer r e k -> NixSerializer r e v -> NixSerializer r e (Map k v) Source #

ProtoVersion

StorePath

Metadata

OutputName

Signatures

Some HashAlgo

Digest

DSum HashAlgo Digest

Derivation

Derivation

Build

Logger

data LoggerSError Source #

Instances

Instances details
Generic LoggerSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Associated Types

type Rep LoggerSError :: Type -> Type #

Show LoggerSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Eq LoggerSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Ord LoggerSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep LoggerSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep LoggerSError = D1 ('MetaData "LoggerSError" "System.Nix.Store.Remote.Serializer" "hnix-store-remote-0.7.0.0-3KzMSkqSXnCD71veVOrNoM" 'False) ((C1 ('MetaCons "LoggerSError_Prim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "LoggerSError_InvalidOpCode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :+: (C1 ('MetaCons "LoggerSError_TooOldForErrorInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LoggerSError_TooNewForBasicError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LoggerSError_UnknownLogFieldType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))))

Handshake

data HandshakeSError Source #

Instances

Instances details
Generic HandshakeSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Associated Types

type Rep HandshakeSError :: Type -> Type #

Show HandshakeSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Eq HandshakeSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Ord HandshakeSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep HandshakeSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep HandshakeSError = D1 ('MetaData "HandshakeSError" "System.Nix.Store.Remote.Serializer" "hnix-store-remote-0.7.0.0-3KzMSkqSXnCD71veVOrNoM" 'False) (C1 ('MetaCons "HandshakeSError_InvalidWorkerMagic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :+: C1 ('MetaCons "HandshakeSError_InvalidTrustedFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

Worker protocol

Request

data RequestSError Source #

Instances

Instances details
Generic RequestSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Associated Types

type Rep RequestSError :: Type -> Type #

Show RequestSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Eq RequestSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Ord RequestSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep RequestSError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep RequestSError = D1 ('MetaData "RequestSError" "System.Nix.Store.Remote.Serializer" "hnix-store-remote-0.7.0.0-3KzMSkqSXnCD71veVOrNoM" 'False) ((C1 ('MetaCons "RequestSError_NotYetImplemented" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorkerOp)) :+: C1 ('MetaCons "RequestSError_ReservedOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorkerOp))) :+: (C1 ('MetaCons "RequestSError_PrimGet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: (C1 ('MetaCons "RequestSError_PrimPut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "RequestSError_PrimWorkerOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)))))

Reply

data ReplySError Source #

Instances

Instances details
Generic ReplySError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Associated Types

type Rep ReplySError :: Type -> Type #

Show ReplySError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Eq ReplySError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

Ord ReplySError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep ReplySError Source # 
Instance details

Defined in System.Nix.Store.Remote.Serializer

type Rep ReplySError = D1 ('MetaData "ReplySError" "System.Nix.Store.Remote.Serializer" "hnix-store-remote-0.7.0.0-3KzMSkqSXnCD71veVOrNoM" 'False) (((C1 ('MetaCons "ReplySError_PrimGet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "ReplySError_PrimPut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError))) :+: (C1 ('MetaCons "ReplySError_DerivationOutput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "ReplySError_GCResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)))) :+: ((C1 ('MetaCons "ReplySError_Metadata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "ReplySError_Missing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError))) :+: (C1 ('MetaCons "ReplySError_Realisation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: (C1 ('MetaCons "ReplySError_RealisationWithId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SError)) :+: C1 ('MetaCons "ReplySError_UnexpectedFalseOpSuccess" 'PrefixI 'False) (U1 :: Type -> Type)))))

opSuccess :: NixSerializer r ReplySError SuccessCodeReply Source #

Parse a bool returned at the end of simple operations. This is always 1 (True) so we assert that it really is so. Errors for these operations are indicated via Logger_Error.

Realisation

BuildResult

GCResult

GCResult

Missing

Maybe (Metadata StorePath)