module Network.RPCA.Util where import Control.Concurrent.STM import Data.Word import Data.Bits import qualified Data.Sequence as Seq -- | These are the errors which can occur. You'll find the code in the -- reply_code member of the Rpcreply data ErrorCode = ErrNone -- ^ no error occured | ErrServiceUnknown -- ^ the service was unknown at the remote end | ErrMethodUnknown -- ^ the method was unknown at the remote end | ErrTransportFailed -- ^ the connection died | ErrTimeout -- ^ the request timed out | ErrPayloadParseFailed -- ^ remote end failed to deserialise the payload | ErrReplyPayloadParseFailed -- ^ local parsing of the reply failed deriving (Enum, Eq, Show) -- | Atomically update a value by applying a function to it and return -- the old value updateTVar :: (a -> a) -- ^ function to apply -> TVar a -- ^ value to update -> STM a updateTVar f var = do old <- readTVar var writeTVar var $ f old return old -- | This assumes a little endian system because I can't find a nice way to probe -- the endianness htons :: Word16 -> Word16 htons x = ((x .&. 255) `shiftL` 8) .|. (x `shiftR` 8) seqToList :: Seq.Seq a -> [a] seqToList s = case Seq.viewl s of x Seq.:< xs -> x : seqToList xs Seq.EmptyL -> []