Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- class ToAsdf a where
- class FromAsdf a where
- decodeM :: (FromAsdf a, MonadIO m, MonadThrow m) => ByteString -> m a
- decodeEither :: (FromAsdf a, MonadIO m) => ByteString -> m (Either String a)
- decode :: forall a (es :: [Effect]). (FromAsdf a, IOE :> es, Error AsdfError :> es) => ByteString -> Eff es a
- encodeM :: (ToAsdf a, MonadIO m, MonadThrow m) => a -> m ByteString
- encode :: forall a (es :: [Effect]). (ToAsdf a, IOE :> es, Error AsdfError :> es) => a -> Eff es ByteString
- data AsdfError
- class FromNDArray a where
- fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es a
- class ToNDArray a where
- toNDArray :: a -> NDArrayData
- data SchemaTag
- data Node = Node {}
- data Value
- type Key = Text
- type Object = [(Key, Node)]
- fromValue :: Value -> Node
- data NDArrayData = NDArrayData {}
- jsonPointer :: Text -> JSONPointer
- jsonReference :: Text -> JSONReference
- data JSONReference = JSONReference {
- uri :: Text
- pointer :: JSONPointer
- newtype JSONPointer = JSONPointer Path
- newtype Anchor = Anchor {}
- data Parser (a :: Type -> Type) b
- data Asdf = Asdf {}
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"
Nothing
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)
Nothing
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" node
Instances
decodeM :: (FromAsdf a, MonadIO m, MonadThrow m) => ByteString -> m a Source #
Decode a ByteString
to a FromAsdf
decodeEither :: (FromAsdf a, MonadIO m) => ByteString -> m (Either String a) Source #
Decode a ByteString
to a FromAsdf
decode :: forall a (es :: [Effect]). (FromAsdf a, IOE :> es, Error AsdfError :> es) => ByteString -> Eff es a Source #
Decode a ByteString
to a FromAsdf
encodeM :: (ToAsdf a, MonadIO m, MonadThrow m) => a -> m ByteString Source #
Encode a ToAsdf
to a ByteString
encode :: forall a (es :: [Effect]). (ToAsdf a, IOE :> es, Error AsdfError :> es) => a -> Eff es ByteString Source #
Encode a ToAsdf
to a ByteString
Instances
Exception AsdfError Source # | |
Defined in Telescope.Asdf.Error toException :: AsdfError -> SomeException # fromException :: SomeException -> Maybe AsdfError # displayException :: AsdfError -> String # | |
Show AsdfError Source # | |
Eq AsdfError Source # | |
class FromNDArray a where Source #
Convert an NDArrayData
into a type
https:/asdf-standard.readthedocs.ioenlatestgeneratedstsci.eduasdfcorendarray-1.1.0.html
fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es a Source #
Instances
FromNDArray [Text] Source # | |
Defined in Telescope.Asdf.NDArray fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es [Text] Source # | |
BinaryValue a => FromNDArray [[a]] Source # | |
Defined in Telescope.Asdf.NDArray fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es [[a]] Source # | |
BinaryValue a => FromNDArray [a] Source # | |
Defined in Telescope.Asdf.NDArray fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es [a] Source # | |
(BinaryValue a, Prim a, AxesIndex ix) => FromNDArray (Array D ix a) Source # | |
Defined in Telescope.Asdf.NDArray fromNDArray :: forall (es :: [Effect]). Parser :> es => NDArrayData -> Eff es (Array D ix a) Source # |
class ToNDArray a where Source #
Convert a type to an NDArrayData
https:/asdf-standard.readthedocs.ioenlatestgeneratedstsci.eduasdfcorendarray-1.1.0.html
toNDArray :: a -> NDArrayData Source #
Instances
(BinaryValue a, IsDataType a) => ToNDArray [[a]] Source # | |
Defined in Telescope.Asdf.NDArray toNDArray :: [[a]] -> NDArrayData Source # | |
(BinaryValue a, IsDataType a) => ToNDArray [a] Source # | |
Defined in Telescope.Asdf.NDArray toNDArray :: [a] -> NDArrayData Source # | |
(BinaryValue a, IsDataType a, Prim a, AxesIndex ix, PutArray ix) => ToNDArray (Array D ix a) Source # | |
Defined in Telescope.Asdf.NDArray |
Specify a schema using schema
from ToAsdf
All allowed node values. We can't use Aeson's Value, because it doesn't support tags, binary data, or references
Bool !Bool | |
Number !Scientific | |
Integer !Integer | |
String !Text | |
NDArray !NDArrayData | RawBinary !ByteString |
Array ![Node] | |
Object !Object | |
Reference !JSONReference | |
Alias !Anchor | |
Null |
data NDArrayData Source #
In-tree representation of an NDArray. You can parse a file as this and get it back. Not really what we want though but in haskell we can't easily just parse a multi-dimensional array we could do a simpler representation. Using an ADT
Instances
Show NDArrayData Source # | |
Defined in Telescope.Asdf.NDArray.Types showsPrec :: Int -> NDArrayData -> ShowS # show :: NDArrayData -> String # showList :: [NDArrayData] -> ShowS # | |
Eq NDArrayData Source # | |
Defined in Telescope.Asdf.NDArray.Types (==) :: NDArrayData -> NDArrayData -> Bool # (/=) :: NDArrayData -> NDArrayData -> Bool # | |
FromAsdf NDArrayData Source # | |
Defined in Telescope.Asdf.Class parseValue :: forall (es :: [Effect]). Parser :> es => Value -> Eff es NDArrayData Source # | |
ToAsdf NDArrayData Source # | |
Defined in Telescope.Asdf.Class |
jsonPointer :: Text -> JSONPointer Source #
jsonReference :: Text -> JSONReference Source #
data JSONReference Source #
JSONReference | |
|
Instances
Show JSONReference Source # | |
Defined in Telescope.Asdf.Node showsPrec :: Int -> JSONReference -> ShowS # show :: JSONReference -> String # showList :: [JSONReference] -> ShowS # | |
Eq JSONReference Source # | |
Defined in Telescope.Asdf.Node (==) :: JSONReference -> JSONReference -> Bool # (/=) :: JSONReference -> JSONReference -> Bool # |
newtype JSONPointer Source #
Instances
Show JSONPointer Source # | |
Defined in Telescope.Asdf.Node showsPrec :: Int -> JSONPointer -> ShowS # show :: JSONPointer -> String # showList :: [JSONPointer] -> ShowS # | |
Eq JSONPointer Source # | |
Defined in Telescope.Asdf.Node (==) :: JSONPointer -> JSONPointer -> Bool # (/=) :: JSONPointer -> JSONPointer -> Bool # |
data Parser (a :: Type -> Type) b Source #
Instances
type DispatchOf Parser Source # | |
Defined in Telescope.Data.Parser |