module Stratosphere.IoTWireless.DeviceProfile.LoRaWANDeviceProfileProperty (
LoRaWANDeviceProfileProperty(..), mkLoRaWANDeviceProfileProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data LoRaWANDeviceProfileProperty
=
LoRaWANDeviceProfileProperty {LoRaWANDeviceProfileProperty -> ()
haddock_workaround_ :: (),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classBTimeout :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
factoryPresetFreqsList :: (Prelude.Maybe (ValueList Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Text)
macVersion :: (Prelude.Maybe (Value Prelude.Text)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxDutyCycle :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Text)
regParamsRevision :: (Prelude.Maybe (Value Prelude.Text)),
LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: (Prelude.Maybe (Value Prelude.Text)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDataRate2 :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: (Prelude.Maybe (Value Prelude.Integer)),
LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supports32BitFCnt :: (Prelude.Maybe (Value Prelude.Bool)),
LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: (Prelude.Maybe (Value Prelude.Bool)),
LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: (Prelude.Maybe (Value Prelude.Bool)),
LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: (Prelude.Maybe (Value Prelude.Bool))}
deriving stock (LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool
(LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool)
-> (LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool)
-> Eq LoRaWANDeviceProfileProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool
== :: LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool
$c/= :: LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool
/= :: LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> Bool
Prelude.Eq, Int -> LoRaWANDeviceProfileProperty -> ShowS
[LoRaWANDeviceProfileProperty] -> ShowS
LoRaWANDeviceProfileProperty -> String
(Int -> LoRaWANDeviceProfileProperty -> ShowS)
-> (LoRaWANDeviceProfileProperty -> String)
-> ([LoRaWANDeviceProfileProperty] -> ShowS)
-> Show LoRaWANDeviceProfileProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoRaWANDeviceProfileProperty -> ShowS
showsPrec :: Int -> LoRaWANDeviceProfileProperty -> ShowS
$cshow :: LoRaWANDeviceProfileProperty -> String
show :: LoRaWANDeviceProfileProperty -> String
$cshowList :: [LoRaWANDeviceProfileProperty] -> ShowS
showList :: [LoRaWANDeviceProfileProperty] -> ShowS
Prelude.Show)
mkLoRaWANDeviceProfileProperty :: LoRaWANDeviceProfileProperty
mkLoRaWANDeviceProfileProperty :: LoRaWANDeviceProfileProperty
mkLoRaWANDeviceProfileProperty
= LoRaWANDeviceProfileProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), classBTimeout :: Maybe (Value Integer)
classBTimeout = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
classCTimeout :: Maybe (Value Integer)
classCTimeout = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
factoryPresetFreqsList :: Maybe (ValueList Integer)
factoryPresetFreqsList = Maybe (ValueList Integer)
forall a. Maybe a
Prelude.Nothing,
macVersion :: Maybe (Value Text)
macVersion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, maxDutyCycle :: Maybe (Value Integer)
maxDutyCycle = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
maxEirp :: Maybe (Value Integer)
maxEirp = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, pingSlotDr :: Maybe (Value Integer)
pingSlotDr = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
pingSlotFreq :: Maybe (Value Integer)
pingSlotFreq = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, pingSlotPeriod :: Maybe (Value Integer)
pingSlotPeriod = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
regParamsRevision :: Maybe (Value Text)
regParamsRevision = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, rfRegion :: Maybe (Value Text)
rfRegion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
rxDataRate2 :: Maybe (Value Integer)
rxDataRate2 = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, rxDelay1 :: Maybe (Value Integer)
rxDelay1 = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
rxDrOffset1 :: Maybe (Value Integer)
rxDrOffset1 = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, rxFreq2 :: Maybe (Value Integer)
rxFreq2 = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
supports32BitFCnt :: Maybe (Value Bool)
supports32BitFCnt = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
supportsClassB :: Maybe (Value Bool)
supportsClassB = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing, supportsClassC :: Maybe (Value Bool)
supportsClassC = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
supportsJoin :: Maybe (Value Bool)
supportsJoin = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties LoRaWANDeviceProfileProperty where
toResourceProperties :: LoRaWANDeviceProfileProperty -> ResourceProperties
toResourceProperties LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::IoTWireless::DeviceProfile.LoRaWANDeviceProfile",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassBTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
classBTimeout,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassCTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
classCTimeout,
Key -> ValueList Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FactoryPresetFreqsList"
(ValueList Integer -> (Key, Value))
-> Maybe (ValueList Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Integer)
factoryPresetFreqsList,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MacVersion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
macVersion,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MaxDutyCycle" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxDutyCycle,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MaxEirp" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxEirp,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotDr" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotDr,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotFreq" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotFreq,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotPeriod" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotPeriod,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RegParamsRevision" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
regParamsRevision,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RfRegion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
rfRegion,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDataRate2" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDataRate2,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDelay1" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDelay1,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDrOffset1" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDrOffset1,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxFreq2" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxFreq2,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Supports32BitFCnt" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supports32BitFCnt,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsClassB" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsClassB,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsClassC" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsClassC,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsJoin" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsJoin])}
instance JSON.ToJSON LoRaWANDeviceProfileProperty where
toJSON :: LoRaWANDeviceProfileProperty -> Value
toJSON LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassBTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
classBTimeout,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassCTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
classCTimeout,
Key -> ValueList Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FactoryPresetFreqsList"
(ValueList Integer -> (Key, Value))
-> Maybe (ValueList Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Integer)
factoryPresetFreqsList,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MacVersion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
macVersion,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MaxDutyCycle" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxDutyCycle,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MaxEirp" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxEirp,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotDr" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotDr,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotFreq" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotFreq,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PingSlotPeriod" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
pingSlotPeriod,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RegParamsRevision" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
regParamsRevision,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RfRegion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
rfRegion,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDataRate2" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDataRate2,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDelay1" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDelay1,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxDrOffset1" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxDrOffset1,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RxFreq2" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
rxFreq2,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Supports32BitFCnt" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supports32BitFCnt,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsClassB" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsClassB,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsClassC" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsClassC,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SupportsJoin" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
supportsJoin]))
instance Property "ClassBTimeout" LoRaWANDeviceProfileProperty where
type PropertyType "ClassBTimeout" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "ClassBTimeout" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "ClassBTimeout" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{classBTimeout :: Maybe (Value Integer)
classBTimeout = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClassBTimeout" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "ClassCTimeout" LoRaWANDeviceProfileProperty where
type PropertyType "ClassCTimeout" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "ClassCTimeout" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "ClassCTimeout" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{classCTimeout :: Maybe (Value Integer)
classCTimeout = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClassCTimeout" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "FactoryPresetFreqsList" LoRaWANDeviceProfileProperty where
type PropertyType "FactoryPresetFreqsList" LoRaWANDeviceProfileProperty = ValueList Prelude.Integer
set :: PropertyType "FactoryPresetFreqsList" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "FactoryPresetFreqsList" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{factoryPresetFreqsList :: Maybe (ValueList Integer)
factoryPresetFreqsList = ValueList Integer -> Maybe (ValueList Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FactoryPresetFreqsList" LoRaWANDeviceProfileProperty
ValueList Integer
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "MacVersion" LoRaWANDeviceProfileProperty where
type PropertyType "MacVersion" LoRaWANDeviceProfileProperty = Value Prelude.Text
set :: PropertyType "MacVersion" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "MacVersion" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{macVersion :: Maybe (Value Text)
macVersion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MacVersion" LoRaWANDeviceProfileProperty
Value Text
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "MaxDutyCycle" LoRaWANDeviceProfileProperty where
type PropertyType "MaxDutyCycle" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "MaxDutyCycle" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "MaxDutyCycle" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{maxDutyCycle :: Maybe (Value Integer)
maxDutyCycle = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxDutyCycle" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "MaxEirp" LoRaWANDeviceProfileProperty where
type PropertyType "MaxEirp" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "MaxEirp" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "MaxEirp" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{maxEirp :: Maybe (Value Integer)
maxEirp = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxEirp" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "PingSlotDr" LoRaWANDeviceProfileProperty where
type PropertyType "PingSlotDr" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "PingSlotDr" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "PingSlotDr" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{pingSlotDr :: Maybe (Value Integer)
pingSlotDr = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PingSlotDr" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "PingSlotFreq" LoRaWANDeviceProfileProperty where
type PropertyType "PingSlotFreq" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "PingSlotFreq" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "PingSlotFreq" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{pingSlotFreq :: Maybe (Value Integer)
pingSlotFreq = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PingSlotFreq" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "PingSlotPeriod" LoRaWANDeviceProfileProperty where
type PropertyType "PingSlotPeriod" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "PingSlotPeriod" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "PingSlotPeriod" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{pingSlotPeriod :: Maybe (Value Integer)
pingSlotPeriod = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PingSlotPeriod" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RegParamsRevision" LoRaWANDeviceProfileProperty where
type PropertyType "RegParamsRevision" LoRaWANDeviceProfileProperty = Value Prelude.Text
set :: PropertyType "RegParamsRevision" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RegParamsRevision" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{regParamsRevision :: Maybe (Value Text)
regParamsRevision = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RegParamsRevision" LoRaWANDeviceProfileProperty
Value Text
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RfRegion" LoRaWANDeviceProfileProperty where
type PropertyType "RfRegion" LoRaWANDeviceProfileProperty = Value Prelude.Text
set :: PropertyType "RfRegion" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RfRegion" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{rfRegion :: Maybe (Value Text)
rfRegion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RfRegion" LoRaWANDeviceProfileProperty
Value Text
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RxDataRate2" LoRaWANDeviceProfileProperty where
type PropertyType "RxDataRate2" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "RxDataRate2" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RxDataRate2" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{rxDataRate2 :: Maybe (Value Integer)
rxDataRate2 = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RxDataRate2" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RxDelay1" LoRaWANDeviceProfileProperty where
type PropertyType "RxDelay1" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "RxDelay1" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RxDelay1" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{rxDelay1 :: Maybe (Value Integer)
rxDelay1 = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RxDelay1" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RxDrOffset1" LoRaWANDeviceProfileProperty where
type PropertyType "RxDrOffset1" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "RxDrOffset1" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RxDrOffset1" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{rxDrOffset1 :: Maybe (Value Integer)
rxDrOffset1 = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RxDrOffset1" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "RxFreq2" LoRaWANDeviceProfileProperty where
type PropertyType "RxFreq2" LoRaWANDeviceProfileProperty = Value Prelude.Integer
set :: PropertyType "RxFreq2" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "RxFreq2" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{rxFreq2 :: Maybe (Value Integer)
rxFreq2 = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RxFreq2" LoRaWANDeviceProfileProperty
Value Integer
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "Supports32BitFCnt" LoRaWANDeviceProfileProperty where
type PropertyType "Supports32BitFCnt" LoRaWANDeviceProfileProperty = Value Prelude.Bool
set :: PropertyType "Supports32BitFCnt" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "Supports32BitFCnt" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{supports32BitFCnt :: Maybe (Value Bool)
supports32BitFCnt = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Supports32BitFCnt" LoRaWANDeviceProfileProperty
Value Bool
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "SupportsClassB" LoRaWANDeviceProfileProperty where
type PropertyType "SupportsClassB" LoRaWANDeviceProfileProperty = Value Prelude.Bool
set :: PropertyType "SupportsClassB" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "SupportsClassB" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{supportsClassB :: Maybe (Value Bool)
supportsClassB = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SupportsClassB" LoRaWANDeviceProfileProperty
Value Bool
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "SupportsClassC" LoRaWANDeviceProfileProperty where
type PropertyType "SupportsClassC" LoRaWANDeviceProfileProperty = Value Prelude.Bool
set :: PropertyType "SupportsClassC" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "SupportsClassC" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{supportsClassC :: Maybe (Value Bool)
supportsClassC = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SupportsClassC" LoRaWANDeviceProfileProperty
Value Bool
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
instance Property "SupportsJoin" LoRaWANDeviceProfileProperty where
type PropertyType "SupportsJoin" LoRaWANDeviceProfileProperty = Value Prelude.Bool
set :: PropertyType "SupportsJoin" LoRaWANDeviceProfileProperty
-> LoRaWANDeviceProfileProperty -> LoRaWANDeviceProfileProperty
set PropertyType "SupportsJoin" LoRaWANDeviceProfileProperty
newValue LoRaWANDeviceProfileProperty {Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: LoRaWANDeviceProfileProperty -> ()
classBTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
classCTimeout :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
factoryPresetFreqsList :: LoRaWANDeviceProfileProperty -> Maybe (ValueList Integer)
macVersion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
maxDutyCycle :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
maxEirp :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotDr :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotFreq :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
pingSlotPeriod :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
regParamsRevision :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rfRegion :: LoRaWANDeviceProfileProperty -> Maybe (Value Text)
rxDataRate2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDelay1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxDrOffset1 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
rxFreq2 :: LoRaWANDeviceProfileProperty -> Maybe (Value Integer)
supports32BitFCnt :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassB :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsClassC :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
supportsJoin :: LoRaWANDeviceProfileProperty -> Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
supportsJoin :: Maybe (Value Bool)
..}
= LoRaWANDeviceProfileProperty
{supportsJoin :: Maybe (Value Bool)
supportsJoin = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SupportsJoin" LoRaWANDeviceProfileProperty
Value Bool
newValue, Maybe (ValueList Integer)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
haddock_workaround_ :: ()
classBTimeout :: Maybe (Value Integer)
classCTimeout :: Maybe (Value Integer)
factoryPresetFreqsList :: Maybe (ValueList Integer)
macVersion :: Maybe (Value Text)
maxDutyCycle :: Maybe (Value Integer)
maxEirp :: Maybe (Value Integer)
pingSlotDr :: Maybe (Value Integer)
pingSlotFreq :: Maybe (Value Integer)
pingSlotPeriod :: Maybe (Value Integer)
regParamsRevision :: Maybe (Value Text)
rfRegion :: Maybe (Value Text)
rxDataRate2 :: Maybe (Value Integer)
rxDelay1 :: Maybe (Value Integer)
rxDrOffset1 :: Maybe (Value Integer)
rxFreq2 :: Maybe (Value Integer)
supports32BitFCnt :: Maybe (Value Bool)
supportsClassB :: Maybe (Value Bool)
supportsClassC :: Maybe (Value Bool)
..}