{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE NoImplicitPrelude           #-}
{-# LANGUAGE TemplateHaskell             #-}
{-# LANGUAGE RecordWildCards             #-}

-- |
-- Module:      SwiftNav.SBP.User
-- Copyright:   Copyright (C) 2015-2021 Swift Navigation, Inc.
-- License:     MIT
-- Contact:     https://support.swiftnav.com
-- Stability:   experimental
-- Portability: portable
--
-- \< Messages reserved for use by the user. \>

module SwiftNav.SBP.User
  ( module SwiftNav.SBP.User
  ) where

import BasicPrelude
import Control.Lens
import Control.Monad.Loops
import Data.Binary
import Data.Binary.Get
import Data.Binary.IEEE754
import Data.Binary.Put
import Data.ByteString.Lazy    hiding (ByteString)
import Data.Int
import Data.Word
import SwiftNav.SBP.TH
import SwiftNav.SBP.Types

{-# ANN module ("HLint: ignore Use camelCase"::String) #-}
{-# ANN module ("HLint: ignore Redundant do"::String) #-}
{-# ANN module ("HLint: ignore Use newtype instead of data"::String) #-}


msgUserData :: Word16
msgUserData :: Word16
msgUserData = Word16
0x0800

-- | SBP class for message MSG_USER_DATA (0x0800).
--
-- This message can contain any application specific user data up to a maximum
-- length of 255 bytes per message.
data MsgUserData = MsgUserData
  { MsgUserData -> [Word8]
_msgUserData_contents :: ![Word8]
    -- ^ User data payload
  } deriving ( Int -> MsgUserData -> ShowS
[MsgUserData] -> ShowS
MsgUserData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgUserData] -> ShowS
$cshowList :: [MsgUserData] -> ShowS
show :: MsgUserData -> String
$cshow :: MsgUserData -> String
showsPrec :: Int -> MsgUserData -> ShowS
$cshowsPrec :: Int -> MsgUserData -> ShowS
Show, ReadPrec [MsgUserData]
ReadPrec MsgUserData
Int -> ReadS MsgUserData
ReadS [MsgUserData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgUserData]
$creadListPrec :: ReadPrec [MsgUserData]
readPrec :: ReadPrec MsgUserData
$creadPrec :: ReadPrec MsgUserData
readList :: ReadS [MsgUserData]
$creadList :: ReadS [MsgUserData]
readsPrec :: Int -> ReadS MsgUserData
$creadsPrec :: Int -> ReadS MsgUserData
Read, MsgUserData -> MsgUserData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgUserData -> MsgUserData -> Bool
$c/= :: MsgUserData -> MsgUserData -> Bool
== :: MsgUserData -> MsgUserData -> Bool
$c== :: MsgUserData -> MsgUserData -> Bool
Eq )

instance Binary MsgUserData where
  get :: Get MsgUserData
get = do
    [Word8]
_msgUserData_contents <- forall (m :: * -> *) a. Monad m => m Bool -> m a -> m [a]
whileM (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Bool
isEmpty) Get Word8
getWord8
    forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgUserData {[Word8]
_msgUserData_contents :: [Word8]
_msgUserData_contents :: [Word8]
..}

  put :: MsgUserData -> Put
put MsgUserData {[Word8]
_msgUserData_contents :: [Word8]
_msgUserData_contents :: MsgUserData -> [Word8]
..} = do
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Word8 -> Put
putWord8 [Word8]
_msgUserData_contents

$(makeSBP 'msgUserData ''MsgUserData)
$(makeJSON "_msgUserData_" ''MsgUserData)
$(makeLenses ''MsgUserData)