Safe Haskell | None |
---|---|
Language | Haskell2010 |
Accessors.Dynamic
Synopsis
- type DTree = Either DField DData
- data DData = DData String DConstructor
- data DConstructor
- = DConstructor String [(Maybe String, DTree)]
- | DSum DSimpleEnum
- data DSimpleEnum = DSimpleEnum [String] Int
- data DField
- toDData :: forall a. Lookup a => a -> DTree
- updateLookupable :: Lookup a => a -> DTree -> Either String a
- describeDField :: DField -> String
- sameDFieldType :: DField -> DField -> Bool
- diffDTrees :: String -> DTree -> DTree -> [String]
- denumToString :: DSimpleEnum -> Either String String
- denumToStringOrMsg :: DSimpleEnum -> String
- denumSetString :: DSimpleEnum -> String -> Either String DSimpleEnum
- denumSetIndex :: DSimpleEnum -> Int -> Either String DSimpleEnum
Documentation
Constructors
DData String DConstructor |
Instances
Eq DData Source # | |
Data DData Source # | |
Defined in Accessors.Dynamic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DData -> c DData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DData # dataTypeOf :: DData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DData) # gmapT :: (forall b. Data b => b -> b) -> DData -> DData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DData -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DData -> r # gmapQ :: (forall d. Data d => d -> u) -> DData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DData -> m DData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DData -> m DData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DData -> m DData # | |
Ord DData Source # | |
Show DData Source # | |
Generic DData Source # | |
Binary DData Source # | |
Serialize DData Source # | |
type Rep DData Source # | |
Defined in Accessors.Dynamic type Rep DData = D1 ('MetaData "DData" "Accessors.Dynamic" "generic-accessors-0.7.1.0-L9H18b7SnGe5zF1Su5kqVy" 'False) (C1 ('MetaCons "DData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DConstructor))) |
data DConstructor Source #
Constructors
DConstructor String [(Maybe String, DTree)] | |
DSum DSimpleEnum |
Instances
data DSimpleEnum Source #
Constructors
DSimpleEnum [String] Int |
Instances
a dynamic field
Constructors
DDouble Double | |
DFloat Float | |
DInt8 Int8 | |
DInt16 Int16 | |
DInt32 Int32 | |
DInt64 Int64 | |
DWord8 Word8 | |
DWord16 Word16 | |
DWord32 Word32 | |
DWord64 Word64 | |
DString String | |
DUnit | |
DSorry |
Instances
updateLookupable :: Lookup a => a -> DTree -> Either String a Source #
Update something using a dynamic representation
describeDField :: DField -> String Source #
some utility functions for working with DSimpleEnums
denumToString :: DSimpleEnum -> Either String String Source #
Get the constructor string or an error message.
denumToStringOrMsg :: DSimpleEnum -> String Source #
Get the constructor string or an error message without telling which is which.
denumSetString :: DSimpleEnum -> String -> Either String DSimpleEnum Source #
Try to update an enum with its constructor. Fail if not a valid constructor.
denumSetIndex :: DSimpleEnum -> Int -> Either String DSimpleEnum Source #
Try to update an enum with its index. Fail if out of bounds.