{-# LANGUAGE DeriveGeneric #-}
module Data.SVD.Types
( AccessType(..)
, toAccessType
, showAccessType
, AddressBlock(..)
, Cluster(..)
, Device(..)
, Dimension(..)
, DimensionIndex(..)
, Interrupt(..)
, Peripheral(..)
, Register(..)
, Field(..)
) where
import Data.Default.Class (Default(def))
import Data.Serialize (Serialize)
import GHC.Generics (Generic)
data Device = Device {
Device -> String
deviceName :: String
, Device -> String
deviceVersion :: String
, Device -> String
deviceDescription :: String
, Device -> Int
deviceAddressUnitBits :: Int
, Device -> Int
deviceWidth :: Int
, Device -> Int
deviceSize :: Int
, Device -> Int
deviceResetValue :: Int
, Device -> Int
deviceResetMask :: Int
, Device -> [Peripheral]
devicePeripherals :: [Peripheral]
} deriving (forall x. Rep Device x -> Device
forall x. Device -> Rep Device x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Device x -> Device
$cfrom :: forall x. Device -> Rep Device x
Generic, Device -> Device -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c== :: Device -> Device -> Bool
Eq, Eq Device
Device -> Device -> Bool
Device -> Device -> Ordering
Device -> Device -> Device
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Device -> Device -> Device
$cmin :: Device -> Device -> Device
max :: Device -> Device -> Device
$cmax :: Device -> Device -> Device
>= :: Device -> Device -> Bool
$c>= :: Device -> Device -> Bool
> :: Device -> Device -> Bool
$c> :: Device -> Device -> Bool
<= :: Device -> Device -> Bool
$c<= :: Device -> Device -> Bool
< :: Device -> Device -> Bool
$c< :: Device -> Device -> Bool
compare :: Device -> Device -> Ordering
$ccompare :: Device -> Device -> Ordering
Ord, Int -> Device -> ShowS
[Device] -> ShowS
Device -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Device] -> ShowS
$cshowList :: [Device] -> ShowS
show :: Device -> String
$cshow :: Device -> String
showsPrec :: Int -> Device -> ShowS
$cshowsPrec :: Int -> Device -> ShowS
Show)
instance Default Device where
def :: Device
def = Device
{ deviceName :: String
deviceName = String
"defaultDev"
, deviceVersion :: String
deviceVersion = forall a. Monoid a => a
mempty
, deviceDescription :: String
deviceDescription = forall a. Monoid a => a
mempty
, deviceAddressUnitBits :: Int
deviceAddressUnitBits = Int
0
, deviceWidth :: Int
deviceWidth = Int
0
, deviceSize :: Int
deviceSize = Int
0
, deviceResetValue :: Int
deviceResetValue = Int
0
, deviceResetMask :: Int
deviceResetMask = Int
0
, devicePeripherals :: [Peripheral]
devicePeripherals = []
}
instance Serialize Device
data Peripheral = Peripheral {
Peripheral -> String
periphName :: String
, Peripheral -> String
periphDescription :: String
, Peripheral -> Maybe String
periphDerivedFrom :: Maybe String
, Peripheral -> String
periphGroupName :: String
, Peripheral -> Int
periphBaseAddress :: Int
, Peripheral -> Maybe AddressBlock
periphAddressBlock :: Maybe AddressBlock
, Peripheral -> [Interrupt]
periphInterrupts :: [Interrupt]
, Peripheral -> [Register]
periphRegisters :: [Register]
, Peripheral -> [Cluster]
periphClusters :: [Cluster]
} deriving (forall x. Rep Peripheral x -> Peripheral
forall x. Peripheral -> Rep Peripheral x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Peripheral x -> Peripheral
$cfrom :: forall x. Peripheral -> Rep Peripheral x
Generic, Peripheral -> Peripheral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Peripheral -> Peripheral -> Bool
$c/= :: Peripheral -> Peripheral -> Bool
== :: Peripheral -> Peripheral -> Bool
$c== :: Peripheral -> Peripheral -> Bool
Eq, Eq Peripheral
Peripheral -> Peripheral -> Bool
Peripheral -> Peripheral -> Ordering
Peripheral -> Peripheral -> Peripheral
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Peripheral -> Peripheral -> Peripheral
$cmin :: Peripheral -> Peripheral -> Peripheral
max :: Peripheral -> Peripheral -> Peripheral
$cmax :: Peripheral -> Peripheral -> Peripheral
>= :: Peripheral -> Peripheral -> Bool
$c>= :: Peripheral -> Peripheral -> Bool
> :: Peripheral -> Peripheral -> Bool
$c> :: Peripheral -> Peripheral -> Bool
<= :: Peripheral -> Peripheral -> Bool
$c<= :: Peripheral -> Peripheral -> Bool
< :: Peripheral -> Peripheral -> Bool
$c< :: Peripheral -> Peripheral -> Bool
compare :: Peripheral -> Peripheral -> Ordering
$ccompare :: Peripheral -> Peripheral -> Ordering
Ord, Int -> Peripheral -> ShowS
[Peripheral] -> ShowS
Peripheral -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Peripheral] -> ShowS
$cshowList :: [Peripheral] -> ShowS
show :: Peripheral -> String
$cshow :: Peripheral -> String
showsPrec :: Int -> Peripheral -> ShowS
$cshowsPrec :: Int -> Peripheral -> ShowS
Show)
instance Default Peripheral where
def :: Peripheral
def = Peripheral
{ periphName :: String
periphName = String
"defaultPeriph"
, periphDescription :: String
periphDescription = forall a. Monoid a => a
mempty
, periphDerivedFrom :: Maybe String
periphDerivedFrom = forall a. Maybe a
Nothing
, periphGroupName :: String
periphGroupName = forall a. Monoid a => a
mempty
, periphBaseAddress :: Int
periphBaseAddress = Int
0
, periphAddressBlock :: Maybe AddressBlock
periphAddressBlock = forall a. Maybe a
Nothing
, periphInterrupts :: [Interrupt]
periphInterrupts = []
, periphRegisters :: [Register]
periphRegisters = []
, periphClusters :: [Cluster]
periphClusters = []
}
instance Serialize Peripheral
data AddressBlock = AddressBlock {
AddressBlock -> Int
addressBlockOffset :: Int
, AddressBlock -> Int
addressBlockSize :: Int
, AddressBlock -> String
addressBlockUsage :: String
} deriving (forall x. Rep AddressBlock x -> AddressBlock
forall x. AddressBlock -> Rep AddressBlock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressBlock x -> AddressBlock
$cfrom :: forall x. AddressBlock -> Rep AddressBlock x
Generic, AddressBlock -> AddressBlock -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressBlock -> AddressBlock -> Bool
$c/= :: AddressBlock -> AddressBlock -> Bool
== :: AddressBlock -> AddressBlock -> Bool
$c== :: AddressBlock -> AddressBlock -> Bool
Eq, Eq AddressBlock
AddressBlock -> AddressBlock -> Bool
AddressBlock -> AddressBlock -> Ordering
AddressBlock -> AddressBlock -> AddressBlock
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AddressBlock -> AddressBlock -> AddressBlock
$cmin :: AddressBlock -> AddressBlock -> AddressBlock
max :: AddressBlock -> AddressBlock -> AddressBlock
$cmax :: AddressBlock -> AddressBlock -> AddressBlock
>= :: AddressBlock -> AddressBlock -> Bool
$c>= :: AddressBlock -> AddressBlock -> Bool
> :: AddressBlock -> AddressBlock -> Bool
$c> :: AddressBlock -> AddressBlock -> Bool
<= :: AddressBlock -> AddressBlock -> Bool
$c<= :: AddressBlock -> AddressBlock -> Bool
< :: AddressBlock -> AddressBlock -> Bool
$c< :: AddressBlock -> AddressBlock -> Bool
compare :: AddressBlock -> AddressBlock -> Ordering
$ccompare :: AddressBlock -> AddressBlock -> Ordering
Ord, Int -> AddressBlock -> ShowS
[AddressBlock] -> ShowS
AddressBlock -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressBlock] -> ShowS
$cshowList :: [AddressBlock] -> ShowS
show :: AddressBlock -> String
$cshow :: AddressBlock -> String
showsPrec :: Int -> AddressBlock -> ShowS
$cshowsPrec :: Int -> AddressBlock -> ShowS
Show)
instance Serialize AddressBlock
data Interrupt = Interrupt {
Interrupt -> String
interruptName :: String
, Interrupt -> String
interruptDescription :: String
, Interrupt -> Int
interruptValue :: Int
} deriving (forall x. Rep Interrupt x -> Interrupt
forall x. Interrupt -> Rep Interrupt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Interrupt x -> Interrupt
$cfrom :: forall x. Interrupt -> Rep Interrupt x
Generic, Interrupt -> Interrupt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Interrupt -> Interrupt -> Bool
$c/= :: Interrupt -> Interrupt -> Bool
== :: Interrupt -> Interrupt -> Bool
$c== :: Interrupt -> Interrupt -> Bool
Eq, Eq Interrupt
Interrupt -> Interrupt -> Bool
Interrupt -> Interrupt -> Ordering
Interrupt -> Interrupt -> Interrupt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Interrupt -> Interrupt -> Interrupt
$cmin :: Interrupt -> Interrupt -> Interrupt
max :: Interrupt -> Interrupt -> Interrupt
$cmax :: Interrupt -> Interrupt -> Interrupt
>= :: Interrupt -> Interrupt -> Bool
$c>= :: Interrupt -> Interrupt -> Bool
> :: Interrupt -> Interrupt -> Bool
$c> :: Interrupt -> Interrupt -> Bool
<= :: Interrupt -> Interrupt -> Bool
$c<= :: Interrupt -> Interrupt -> Bool
< :: Interrupt -> Interrupt -> Bool
$c< :: Interrupt -> Interrupt -> Bool
compare :: Interrupt -> Interrupt -> Ordering
$ccompare :: Interrupt -> Interrupt -> Ordering
Ord, Int -> Interrupt -> ShowS
[Interrupt] -> ShowS
Interrupt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Interrupt] -> ShowS
$cshowList :: [Interrupt] -> ShowS
show :: Interrupt -> String
$cshow :: Interrupt -> String
showsPrec :: Int -> Interrupt -> ShowS
$cshowsPrec :: Int -> Interrupt -> ShowS
Show)
instance Serialize Interrupt
data DimensionIndex
= DimensionIndex_FromTo Int Int
| DimensionIndex_List [String]
deriving (forall x. Rep DimensionIndex x -> DimensionIndex
forall x. DimensionIndex -> Rep DimensionIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DimensionIndex x -> DimensionIndex
$cfrom :: forall x. DimensionIndex -> Rep DimensionIndex x
Generic, DimensionIndex -> DimensionIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DimensionIndex -> DimensionIndex -> Bool
$c/= :: DimensionIndex -> DimensionIndex -> Bool
== :: DimensionIndex -> DimensionIndex -> Bool
$c== :: DimensionIndex -> DimensionIndex -> Bool
Eq, Eq DimensionIndex
DimensionIndex -> DimensionIndex -> Bool
DimensionIndex -> DimensionIndex -> Ordering
DimensionIndex -> DimensionIndex -> DimensionIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DimensionIndex -> DimensionIndex -> DimensionIndex
$cmin :: DimensionIndex -> DimensionIndex -> DimensionIndex
max :: DimensionIndex -> DimensionIndex -> DimensionIndex
$cmax :: DimensionIndex -> DimensionIndex -> DimensionIndex
>= :: DimensionIndex -> DimensionIndex -> Bool
$c>= :: DimensionIndex -> DimensionIndex -> Bool
> :: DimensionIndex -> DimensionIndex -> Bool
$c> :: DimensionIndex -> DimensionIndex -> Bool
<= :: DimensionIndex -> DimensionIndex -> Bool
$c<= :: DimensionIndex -> DimensionIndex -> Bool
< :: DimensionIndex -> DimensionIndex -> Bool
$c< :: DimensionIndex -> DimensionIndex -> Bool
compare :: DimensionIndex -> DimensionIndex -> Ordering
$ccompare :: DimensionIndex -> DimensionIndex -> Ordering
Ord, Int -> DimensionIndex -> ShowS
[DimensionIndex] -> ShowS
DimensionIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DimensionIndex] -> ShowS
$cshowList :: [DimensionIndex] -> ShowS
show :: DimensionIndex -> String
$cshow :: DimensionIndex -> String
showsPrec :: Int -> DimensionIndex -> ShowS
$cshowsPrec :: Int -> DimensionIndex -> ShowS
Show)
instance Serialize DimensionIndex
data Dimension = Dimension {
Dimension -> Int
dimensionSize :: Int
, Dimension -> Int
dimensionIncrement :: Int
, Dimension -> DimensionIndex
dimensionIndex :: DimensionIndex
} deriving (forall x. Rep Dimension x -> Dimension
forall x. Dimension -> Rep Dimension x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Dimension x -> Dimension
$cfrom :: forall x. Dimension -> Rep Dimension x
Generic, Dimension -> Dimension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dimension -> Dimension -> Bool
$c/= :: Dimension -> Dimension -> Bool
== :: Dimension -> Dimension -> Bool
$c== :: Dimension -> Dimension -> Bool
Eq, Eq Dimension
Dimension -> Dimension -> Bool
Dimension -> Dimension -> Ordering
Dimension -> Dimension -> Dimension
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Dimension -> Dimension -> Dimension
$cmin :: Dimension -> Dimension -> Dimension
max :: Dimension -> Dimension -> Dimension
$cmax :: Dimension -> Dimension -> Dimension
>= :: Dimension -> Dimension -> Bool
$c>= :: Dimension -> Dimension -> Bool
> :: Dimension -> Dimension -> Bool
$c> :: Dimension -> Dimension -> Bool
<= :: Dimension -> Dimension -> Bool
$c<= :: Dimension -> Dimension -> Bool
< :: Dimension -> Dimension -> Bool
$c< :: Dimension -> Dimension -> Bool
compare :: Dimension -> Dimension -> Ordering
$ccompare :: Dimension -> Dimension -> Ordering
Ord, Int -> Dimension -> ShowS
[Dimension] -> ShowS
Dimension -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dimension] -> ShowS
$cshowList :: [Dimension] -> ShowS
show :: Dimension -> String
$cshow :: Dimension -> String
showsPrec :: Int -> Dimension -> ShowS
$cshowsPrec :: Int -> Dimension -> ShowS
Show)
instance Serialize Dimension
data Cluster = Cluster {
Cluster -> String
clusterName :: String
, Cluster -> Maybe Dimension
clusterDimension :: Maybe Dimension
, Cluster -> String
clusterDescription :: String
, Cluster -> Int
clusterAddressOffset :: Int
, Cluster -> [Register]
clusterRegisters :: [Register]
, Cluster -> [Cluster]
clusterNested :: [Cluster]
} deriving (forall x. Rep Cluster x -> Cluster
forall x. Cluster -> Rep Cluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cluster x -> Cluster
$cfrom :: forall x. Cluster -> Rep Cluster x
Generic, Cluster -> Cluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cluster -> Cluster -> Bool
$c/= :: Cluster -> Cluster -> Bool
== :: Cluster -> Cluster -> Bool
$c== :: Cluster -> Cluster -> Bool
Eq, Eq Cluster
Cluster -> Cluster -> Bool
Cluster -> Cluster -> Ordering
Cluster -> Cluster -> Cluster
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Cluster -> Cluster -> Cluster
$cmin :: Cluster -> Cluster -> Cluster
max :: Cluster -> Cluster -> Cluster
$cmax :: Cluster -> Cluster -> Cluster
>= :: Cluster -> Cluster -> Bool
$c>= :: Cluster -> Cluster -> Bool
> :: Cluster -> Cluster -> Bool
$c> :: Cluster -> Cluster -> Bool
<= :: Cluster -> Cluster -> Bool
$c<= :: Cluster -> Cluster -> Bool
< :: Cluster -> Cluster -> Bool
$c< :: Cluster -> Cluster -> Bool
compare :: Cluster -> Cluster -> Ordering
$ccompare :: Cluster -> Cluster -> Ordering
Ord, Int -> Cluster -> ShowS
[Cluster] -> ShowS
Cluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cluster] -> ShowS
$cshowList :: [Cluster] -> ShowS
show :: Cluster -> String
$cshow :: Cluster -> String
showsPrec :: Int -> Cluster -> ShowS
$cshowsPrec :: Int -> Cluster -> ShowS
Show)
instance Default Cluster where
def :: Cluster
def = Cluster
{ clusterName :: String
clusterName = String
"defaultCluster"
, clusterDescription :: String
clusterDescription = forall a. Monoid a => a
mempty
, clusterDimension :: Maybe Dimension
clusterDimension = forall a. Maybe a
Nothing
, clusterAddressOffset :: Int
clusterAddressOffset = Int
0
, clusterRegisters :: [Register]
clusterRegisters = []
, clusterNested :: [Cluster]
clusterNested = []
}
instance Serialize Cluster
data Register = Register {
Register -> String
regName :: String
, Register -> String
regDisplayName :: String
, Register -> Maybe Dimension
regDimension :: Maybe Dimension
, Register -> String
regDescription :: String
, Register -> Int
regAddressOffset :: Int
, Register -> Int
regSize :: Int
, Register -> AccessType
regAccess :: AccessType
, Register -> Maybe Int
regResetValue :: Maybe Int
, Register -> [Field]
regFields :: [Field]
} deriving (forall x. Rep Register x -> Register
forall x. Register -> Rep Register x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Register x -> Register
$cfrom :: forall x. Register -> Rep Register x
Generic, Register -> Register -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Register -> Register -> Bool
$c/= :: Register -> Register -> Bool
== :: Register -> Register -> Bool
$c== :: Register -> Register -> Bool
Eq, Eq Register
Register -> Register -> Bool
Register -> Register -> Ordering
Register -> Register -> Register
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Register -> Register -> Register
$cmin :: Register -> Register -> Register
max :: Register -> Register -> Register
$cmax :: Register -> Register -> Register
>= :: Register -> Register -> Bool
$c>= :: Register -> Register -> Bool
> :: Register -> Register -> Bool
$c> :: Register -> Register -> Bool
<= :: Register -> Register -> Bool
$c<= :: Register -> Register -> Bool
< :: Register -> Register -> Bool
$c< :: Register -> Register -> Bool
compare :: Register -> Register -> Ordering
$ccompare :: Register -> Register -> Ordering
Ord, Int -> Register -> ShowS
[Register] -> ShowS
Register -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Register] -> ShowS
$cshowList :: [Register] -> ShowS
show :: Register -> String
$cshow :: Register -> String
showsPrec :: Int -> Register -> ShowS
$cshowsPrec :: Int -> Register -> ShowS
Show)
instance Default Register where
def :: Register
def = Register
{ regName :: String
regName = String
"defaultRegister"
, regDisplayName :: String
regDisplayName = forall a. Monoid a => a
mempty
, regDimension :: Maybe Dimension
regDimension = forall a. Maybe a
Nothing
, regDescription :: String
regDescription = forall a. Monoid a => a
mempty
, regAddressOffset :: Int
regAddressOffset = Int
0
, regSize :: Int
regSize = Int
0
, regAccess :: AccessType
regAccess = AccessType
ReadOnly
, regResetValue :: Maybe Int
regResetValue = forall a. Maybe a
Nothing
, regFields :: [Field]
regFields = []
}
instance Serialize Register
data AccessType
= ReadOnly
| WriteOnly
| ReadWrite
| WriteOnce
| ReadWriteOnce
deriving (forall x. Rep AccessType x -> AccessType
forall x. AccessType -> Rep AccessType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccessType x -> AccessType
$cfrom :: forall x. AccessType -> Rep AccessType x
Generic, AccessType -> AccessType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccessType -> AccessType -> Bool
$c/= :: AccessType -> AccessType -> Bool
== :: AccessType -> AccessType -> Bool
$c== :: AccessType -> AccessType -> Bool
Eq, Eq AccessType
AccessType -> AccessType -> Bool
AccessType -> AccessType -> Ordering
AccessType -> AccessType -> AccessType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AccessType -> AccessType -> AccessType
$cmin :: AccessType -> AccessType -> AccessType
max :: AccessType -> AccessType -> AccessType
$cmax :: AccessType -> AccessType -> AccessType
>= :: AccessType -> AccessType -> Bool
$c>= :: AccessType -> AccessType -> Bool
> :: AccessType -> AccessType -> Bool
$c> :: AccessType -> AccessType -> Bool
<= :: AccessType -> AccessType -> Bool
$c<= :: AccessType -> AccessType -> Bool
< :: AccessType -> AccessType -> Bool
$c< :: AccessType -> AccessType -> Bool
compare :: AccessType -> AccessType -> Ordering
$ccompare :: AccessType -> AccessType -> Ordering
Ord, Int -> AccessType -> ShowS
[AccessType] -> ShowS
AccessType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccessType] -> ShowS
$cshowList :: [AccessType] -> ShowS
show :: AccessType -> String
$cshow :: AccessType -> String
showsPrec :: Int -> AccessType -> ShowS
$cshowsPrec :: Int -> AccessType -> ShowS
Show)
instance Serialize AccessType
data Field = Field {
Field -> String
fieldName :: String
, Field -> String
fieldDescription :: String
, Field -> Maybe Dimension
fieldDimension :: Maybe Dimension
, Field -> Int
fieldBitOffset :: Int
, Field -> Int
fieldBitWidth :: Int
, Field -> Bool
fieldReserved :: Bool
, Field -> Maybe String
fieldRegType :: Maybe String
} deriving (forall x. Rep Field x -> Field
forall x. Field -> Rep Field x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Field x -> Field
$cfrom :: forall x. Field -> Rep Field x
Generic, Field -> Field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq, Eq Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmax :: Field -> Field -> Field
>= :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c< :: Field -> Field -> Bool
compare :: Field -> Field -> Ordering
$ccompare :: Field -> Field -> Ordering
Ord, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Field] -> ShowS
$cshowList :: [Field] -> ShowS
show :: Field -> String
$cshow :: Field -> String
showsPrec :: Int -> Field -> ShowS
$cshowsPrec :: Int -> Field -> ShowS
Show)
instance Default Field where
def :: Field
def = Field
{ fieldName :: String
fieldName = String
"defaultField"
, fieldDescription :: String
fieldDescription = forall a. Monoid a => a
mempty
, fieldDimension :: Maybe Dimension
fieldDimension = forall a. Maybe a
Nothing
, fieldBitOffset :: Int
fieldBitOffset = Int
0
, fieldBitWidth :: Int
fieldBitWidth = Int
0
, fieldReserved :: Bool
fieldReserved = Bool
False
, fieldRegType :: Maybe String
fieldRegType = forall a. Maybe a
Nothing
}
instance Serialize Field
toAccessType :: String -> AccessType
toAccessType :: String -> AccessType
toAccessType String
"read-only" = AccessType
ReadOnly
toAccessType String
"write-only" = AccessType
WriteOnly
toAccessType String
"read-write" = AccessType
ReadWrite
toAccessType String
"writeOnce" = AccessType
WriteOnce
toAccessType String
"read-writeOnce" = AccessType
ReadWriteOnce
toAccessType String
x = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Unable to read AccessType" forall a. [a] -> [a] -> [a]
++ String
x
showAccessType :: AccessType -> String
showAccessType :: AccessType -> String
showAccessType AccessType
ReadOnly = String
"read-only"
showAccessType AccessType
WriteOnly = String
"write-only"
showAccessType AccessType
ReadWrite = String
"read-write"
showAccessType AccessType
WriteOnce = String
"writeOnce"
showAccessType AccessType
ReadWriteOnce = String
"read-writeOnce"