| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Telescope.Asdf.Class
Synopsis
- class ToAsdf a where
- class FromAsdf a where
- parseInteger :: forall a (es :: [Effect]). (Integral a, Parser :> es) => Value -> Eff es a
- parseAnyList :: forall a (es :: [Effect]). (FromAsdf a, FromNDArray [a], Parser :> es) => Value -> Eff es [a]
- parseNode :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Node -> Eff es a
- (.:) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Object -> Key -> Eff es a
- (.:?) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Object -> Key -> Eff es (Maybe a)
- (!) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => [Node] -> Int -> Eff es a
- class GToObject (f :: k -> Type) where
- class GToNode (f :: k -> Type) where
- class GParseObject (f :: k -> Type) where
- class GParseKey (f :: k -> Type) where
Documentation
Convert a type to an Asdf Value or Node. The generic instance will encode to an Object with field names matching record selectors
data Example = Example
{ name :: Text
, age :: Int
, tags :: [Text]
}
deriving (Generic, ToAsdf)
instance ToAsdf Example where
schema _ = "tag:example.org/schemas/example-1.0.0"Minimal complete definition
Nothing
Methods
toValue :: a -> Value Source #
Specify how an object encodes to a Value
instance User ToAsdf where
toValue user =
Object
[ ("name", toNode user.name)
, ("age", toNode user.age)
]schema :: a -> SchemaTag Source #
Specify the schema for a type
instance ToAsdf Unit where schema _ = "!unit/unit-1.0.0"
anchor :: a -> Maybe Anchor Source #
Specify that this node be saved as an anchor
instance ToAsdf Config where anchor _ = Just "globalConfig"
Manually control all aspects of how this is converted to a Node
Instances
class FromAsdf a where Source #
Parse an Asdf Value or Node into a type. The generic instance will decode an Object with field names matching record selectors
data Example = Example
{ name :: Text
, age :: Int
, tags :: [Text]
}
deriving (Generic, FromAsdf)Minimal complete definition
Nothing
Methods
parseValue :: forall (es :: [Effect]). Parser :> es => Value -> Eff es a Source #
Specify how a type is parsed from a Value
instance FromAsdf Integer where
parseValue = \case
Integer n -> pure $ fromIntegral n
node -> expected "Integer" nodeInstances
parseAnyList :: forall a (es :: [Effect]). (FromAsdf a, FromNDArray [a], Parser :> es) => Value -> Eff es [a] Source #
Flexibly parse lists from either Array or NDArray
parseNode :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Node -> Eff es a Source #
Parse a node, ignoring the schema tag
(.:) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Object -> Key -> Eff es a Source #
Parse a key from an Object
instance FromAsdf User where
parseValue = \case
Object o -> do
name <- o .: "name"
age <- o .: "age"
pure $ User{name, age}(.:?) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => Object -> Key -> Eff es (Maybe a) Source #
Parse an optional key from an Object
(!) :: forall a (es :: [Effect]). (FromAsdf a, Parser :> es) => [Node] -> Int -> Eff es a Source #
Parse a child at the given array index - > instance FromAsdf Friends where > parseValue = case > Array ns -> do > best <- ns ! 0 > second <- ns ! 1 > other <- mapM parseNode ns > pure $ Friends{best, second, other}
class GToObject (f :: k -> Type) where Source #
Generically serialize records to an Object
class GToNode (f :: k -> Type) where Source #
Generically serialize record values to a Node
class GParseObject (f :: k -> Type) where Source #
Generically parse Objects into records
Methods
gParseObject :: forall (es :: [Effect]) (p :: k). Parser :> es => Object -> Eff es (f p) Source #
Instances
| (GParseObject f, GParseObject g) => GParseObject (f :*: g :: k -> Type) Source # | |
Defined in Telescope.Asdf.Class | |
| GParseObject f => GParseObject (M1 C c f :: k -> Type) Source # | |
| GParseObject f => GParseObject (M1 D c f :: k -> Type) Source # | |
| (GParseKey f, Selector s) => GParseObject (M1 S s f :: k -> Type) Source # | |
class GParseKey (f :: k -> Type) where Source #
Generically parse a key from an Object into a record value
Methods
gParseKey :: forall (es :: [Effect]) (p :: k). Parser :> es => Object -> Key -> Eff es (f p) Source #