module Hydra.Ext.Avro.SchemaJson where import Hydra.Kernel import Hydra.Ext.Json.Serde import Hydra.Ext.Json.Eliminate import qualified Hydra.Ext.Org.Apache.Avro.Schema as Avro import qualified Hydra.Json as Json import qualified Control.Monad as CM import qualified Data.List as L import qualified Data.Map as M import qualified Data.Maybe as Y avro_aliases :: String avro_aliases = String "aliases" avro_array :: String avro_array = String "array" avro_ascending :: String avro_ascending = String "ascending" avro_boolean :: String avro_boolean = String "boolean" avro_bytes :: String avro_bytes = String "bytes" avro_default :: String avro_default = String "default" avro_descending :: String avro_descending = String "descending" avro_doc :: String avro_doc = String "doc" avro_double :: String avro_double = String "double" avro_enum :: String avro_enum = String "enum" avro_fields :: String avro_fields = String "fields" avro_fixed :: String avro_fixed = String "fixed" avro_float :: String avro_float = String "float" avro_ignore :: String avro_ignore = String "ignore" avro_int :: String avro_int = String "int" avro_items :: String avro_items = String "items" avro_long :: String avro_long = String "long" avro_map :: String avro_map = String "map" avro_name :: String avro_name = String "name" avro_namespace :: String avro_namespace = String "namespace" avro_null :: String avro_null = String "null" avro_order :: String avro_order = String "order" avro_record :: String avro_record = String "record" avro_size :: String avro_size = String "size" avro_string :: String avro_string = String "string" avro_symbols :: String avro_symbols = String "symbols" avro_type :: String avro_type = String "type" avro_values :: String avro_values = String "values" avroSchemaJsonCoder :: Coder s s Avro.Schema Json.Value avroSchemaJsonCoder :: forall s. Coder s s Schema Value avroSchemaJsonCoder = Coder { coderEncode :: Schema -> Flow s Value coderEncode = \Schema schema -> String -> Flow s Value forall a. String -> Flow s a forall (m :: * -> *) a. MonadFail m => String -> m a fail String "not implemented", coderDecode :: Value -> Flow s Schema coderDecode = Value -> Flow s Schema forall s. Value -> Flow s Schema decodeNamedSchema} avroSchemaStringCoder :: Coder s s Avro.Schema String avroSchemaStringCoder :: forall s. Coder s s Schema String avroSchemaStringCoder = Coder { coderEncode :: Schema -> Flow s String coderEncode = \Schema schema -> Value -> String jsonValueToString (Value -> String) -> Flow s Value -> Flow s String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Coder s s Schema Value -> Schema -> Flow s Value forall s1 s2 v1 v2. Coder s1 s2 v1 v2 -> v1 -> Flow s1 v2 coderEncode Coder s s Schema Value forall s. Coder s s Schema Value avroSchemaJsonCoder Schema schema, coderDecode :: String -> Flow s Schema coderDecode = \String s -> do Value json <- case String -> Either String Value stringToJsonValue String s of Left String msg -> String -> Flow s Value forall a. String -> Flow s a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Flow s Value) -> String -> Flow s Value forall a b. (a -> b) -> a -> b $ String "failed to parse JSON: " String -> String -> String forall a. [a] -> [a] -> [a] ++ String msg Right Value j -> Value -> Flow s Value forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure Value j Coder s s Schema Value -> Value -> Flow s Schema forall s1 s2 v1 v2. Coder s1 s2 v1 v2 -> v2 -> Flow s2 v1 coderDecode Coder s s Schema Value forall s. Coder s s Schema Value avroSchemaJsonCoder Value json} decodeAliases :: M.Map String Json.Value -> Flow s (Maybe [String]) decodeAliases :: forall s. Map String Value -> Flow s (Maybe [String]) decodeAliases Map String Value m = do Maybe [Value] aliasesJson <- String -> Map String Value -> Flow s (Maybe [Value]) forall s. String -> Map String Value -> Flow s (Maybe [Value]) optArray String avro_aliases Map String Value m case Maybe [Value] aliasesJson of Maybe [Value] Nothing -> Maybe [String] -> Flow s (Maybe [String]) forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure Maybe [String] forall a. Maybe a Nothing Just [Value] a -> [String] -> Maybe [String] forall a. a -> Maybe a Just ([String] -> Maybe [String]) -> Flow s [String] -> Flow s (Maybe [String]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Value -> Flow s String) -> [Value] -> Flow s [String] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] CM.mapM Value -> Flow s String forall s. Value -> Flow s String expectString [Value] a decodeEnum :: M.Map String Json.Value -> Flow s Avro.NamedType decodeEnum :: forall s. Map String Value -> Flow s NamedType decodeEnum Map String Value m = do [Value] symbolsJson <- String -> Map String Value -> Flow s [Value] forall s. String -> Map String Value -> Flow s [Value] requireArray String avro_symbols Map String Value m [String] symbols <- (Value -> Flow s String) -> [Value] -> Flow s [String] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] CM.mapM Value -> Flow s String forall s. Value -> Flow s String expectString [Value] symbolsJson Maybe String dflt <- String -> Map String Value -> Flow s (Maybe String) forall s. String -> Map String Value -> Flow s (Maybe String) optString String avro_default Map String Value m NamedType -> Flow s NamedType forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (NamedType -> Flow s NamedType) -> NamedType -> Flow s NamedType forall a b. (a -> b) -> a -> b $ Enum_ -> NamedType Avro.NamedTypeEnum (Enum_ -> NamedType) -> Enum_ -> NamedType forall a b. (a -> b) -> a -> b $ [String] -> Maybe String -> Enum_ Avro.Enum_ [String] symbols Maybe String dflt decodeField :: M.Map String Json.Value -> Flow s Avro.Field decodeField :: forall s. Map String Value -> Flow s Field decodeField Map String Value m = do String fname <- String -> Map String Value -> Flow s String forall s. String -> Map String Value -> Flow s String requireString String avro_name Map String Value m Maybe String doc <- String -> Map String Value -> Flow s (Maybe String) forall s. String -> Map String Value -> Flow s (Maybe String) optString String avro_doc Map String Value m Schema typ <- String -> Map String Value -> Flow s Value forall s. String -> Map String Value -> Flow s Value require String avro_type Map String Value m Flow s Value -> (Value -> Flow s Schema) -> Flow s Schema forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Value -> Flow s Schema forall s. Value -> Flow s Schema decodeSchema let dflt :: Maybe Value dflt = String -> Map String Value -> Maybe Value opt String avro_default Map String Value m Maybe Order order <- case String -> Map String Value -> Maybe Value opt String avro_order Map String Value m of Maybe Value Nothing -> Maybe Order -> Flow s (Maybe Order) forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure Maybe Order forall a. Maybe a Nothing Just Value o -> Order -> Maybe Order forall a. a -> Maybe a Just (Order -> Maybe Order) -> Flow s Order -> Flow s (Maybe Order) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Value -> Flow s String forall s. Value -> Flow s String expectString Value o Flow s String -> (String -> Flow s Order) -> Flow s Order forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= String -> Flow s Order forall s. String -> Flow s Order decodeOrder) Maybe [String] aliases <- Map String Value -> Flow s (Maybe [String]) forall s. Map String Value -> Flow s (Maybe [String]) decodeAliases Map String Value m let anns :: Map String Value anns = Map String Value -> Map String Value getAnnotations Map String Value m Field -> Flow s Field forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (Field -> Flow s Field) -> Field -> Flow s Field forall a b. (a -> b) -> a -> b $ String -> Maybe String -> Schema -> Maybe Value -> Maybe Order -> Maybe [String] -> Map String Value -> Field Avro.Field String fname Maybe String doc Schema typ Maybe Value dflt Maybe Order order Maybe [String] aliases Map String Value anns decodeFixed :: M.Map String Json.Value -> Flow s Avro.NamedType decodeFixed :: forall s. Map String Value -> Flow s NamedType decodeFixed Map String Value m = do Int size <- Double -> Int forall {a} {b}. (RealFrac a, Integral b) => a -> b doubleToInt (Double -> Int) -> Flow s Double -> Flow s Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> Map String Value -> Flow s Double forall s. String -> Map String Value -> Flow s Double requireNumber String avro_size Map String Value m NamedType -> Flow s NamedType forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (NamedType -> Flow s NamedType) -> NamedType -> Flow s NamedType forall a b. (a -> b) -> a -> b $ Fixed -> NamedType Avro.NamedTypeFixed (Fixed -> NamedType) -> Fixed -> NamedType forall a b. (a -> b) -> a -> b $ Int -> Fixed Avro.Fixed Int size where doubleToInt :: a -> b doubleToInt a d = if a d a -> a -> Bool forall a. Ord a => a -> a -> Bool < a 0 then a -> b forall b. Integral b => a -> b forall a b. (RealFrac a, Integral b) => a -> b ceiling a d else a -> b forall b. Integral b => a -> b forall a b. (RealFrac a, Integral b) => a -> b floor a d decodeNamedSchema :: Json.Value -> Flow s Avro.Schema decodeNamedSchema :: forall s. Value -> Flow s Schema decodeNamedSchema Value value = do Map String Value m <- Value -> Flow s (Map String Value) forall s. Value -> Flow s (Map String Value) expectObject Value value String name <- String -> Map String Value -> Flow s String forall s. String -> Map String Value -> Flow s String requireString String avro_name Map String Value m Maybe String ns <- String -> Map String Value -> Flow s (Maybe String) forall s. String -> Map String Value -> Flow s (Maybe String) optString String avro_namespace Map String Value m String typ <- String -> Map String Value -> Flow s String forall s. String -> Map String Value -> Flow s String requireString String avro_type Map String Value m NamedType nt <- case String -> Map String (Map String Value -> Flow s NamedType) -> Maybe (Map String Value -> Flow s NamedType) forall k a. Ord k => k -> Map k a -> Maybe a M.lookup String typ Map String (Map String Value -> Flow s NamedType) forall {s}. Map String (Map String Value -> Flow s NamedType) decoders of Maybe (Map String Value -> Flow s NamedType) Nothing -> String -> String -> Flow s NamedType forall s x. String -> String -> Flow s x unexpected String "Avro type" (String -> Flow s NamedType) -> String -> Flow s NamedType forall a b. (a -> b) -> a -> b $ String -> String forall a. Show a => a -> String show String typ Just Map String Value -> Flow s NamedType d -> Map String Value -> Flow s NamedType d Map String Value m Maybe [String] aliases <- Map String Value -> Flow s (Maybe [String]) forall s. Map String Value -> Flow s (Maybe [String]) decodeAliases Map String Value m Maybe String doc <- String -> Map String Value -> Flow s (Maybe String) forall s. String -> Map String Value -> Flow s (Maybe String) optString String avro_doc Map String Value m let anns :: Map String Value anns = Map String Value -> Map String Value getAnnotations Map String Value m Schema -> Flow s Schema forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (Schema -> Flow s Schema) -> Schema -> Flow s Schema forall a b. (a -> b) -> a -> b $ Named -> Schema Avro.SchemaNamed (Named -> Schema) -> Named -> Schema forall a b. (a -> b) -> a -> b $ String -> Maybe String -> Maybe [String] -> Maybe String -> NamedType -> Map String Value -> Named Avro.Named String name Maybe String ns Maybe [String] aliases Maybe String doc NamedType nt Map String Value anns where decoders :: Map String (Map String Value -> Flow s NamedType) decoders = [(String, Map String Value -> Flow s NamedType)] -> Map String (Map String Value -> Flow s NamedType) forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ (String avro_enum, Map String Value -> Flow s NamedType forall s. Map String Value -> Flow s NamedType decodeEnum), (String avro_fixed, Map String Value -> Flow s NamedType forall s. Map String Value -> Flow s NamedType decodeFixed), (String avro_record, Map String Value -> Flow s NamedType forall s. Map String Value -> Flow s NamedType decodeRecord)] decodeOrder :: String -> Flow s Avro.Order decodeOrder :: forall s. String -> Flow s Order decodeOrder String o = case String -> Map String Order -> Maybe Order forall k a. Ord k => k -> Map k a -> Maybe a M.lookup String o Map String Order orderMap of Maybe Order Nothing -> String -> String -> Flow s Order forall s x. String -> String -> Flow s x unexpected String "ordering" (String -> Flow s Order) -> String -> Flow s Order forall a b. (a -> b) -> a -> b $ String -> String forall a. Show a => a -> String show String o Just Order order -> Order -> Flow s Order forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure Order order where orderMap :: Map String Order orderMap = [(String, Order)] -> Map String Order forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ (String avro_ascending, Order Avro.OrderAscending), (String avro_descending, Order Avro.OrderDescending), (String avro_ignore, Order Avro.OrderIgnore)] decodeRecord :: M.Map String Json.Value -> Flow s Avro.NamedType decodeRecord :: forall s. Map String Value -> Flow s NamedType decodeRecord Map String Value m = do [Field] fields <- String -> Map String Value -> Flow s [Value] forall s. String -> Map String Value -> Flow s [Value] requireArray String avro_fields Map String Value m Flow s [Value] -> ([Value] -> Flow s [Map String Value]) -> Flow s [Map String Value] forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= (Value -> Flow s (Map String Value)) -> [Value] -> Flow s [Map String Value] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] CM.mapM Value -> Flow s (Map String Value) forall s. Value -> Flow s (Map String Value) expectObject Flow s [Map String Value] -> ([Map String Value] -> Flow s [Field]) -> Flow s [Field] forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= (Map String Value -> Flow s Field) -> [Map String Value] -> Flow s [Field] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] CM.mapM Map String Value -> Flow s Field forall s. Map String Value -> Flow s Field decodeField NamedType -> Flow s NamedType forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (NamedType -> Flow s NamedType) -> NamedType -> Flow s NamedType forall a b. (a -> b) -> a -> b $ Record -> NamedType Avro.NamedTypeRecord (Record -> NamedType) -> Record -> NamedType forall a b. (a -> b) -> a -> b $ [Field] -> Record Avro.Record [Field] fields decodeSchema :: Json.Value -> Flow s Avro.Schema decodeSchema :: forall s. Value -> Flow s Schema decodeSchema Value v = case Value v of Json.ValueArray [Value] els -> Union -> Schema Avro.SchemaUnion (Union -> Schema) -> Flow s Union -> Flow s Schema forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ([Schema] -> Union Avro.Union ([Schema] -> Union) -> Flow s [Schema] -> Flow s Union forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ((Value -> Flow s Schema) -> [Value] -> Flow s [Schema] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] CM.mapM Value -> Flow s Schema forall s. Value -> Flow s Schema decodeSchema [Value] els)) Json.ValueObject Map String Value m -> do String typ <- String -> Map String Value -> Flow s String forall s. String -> Map String Value -> Flow s String requireString String avro_type Map String Value m case String -> Map String (Map String Value -> Flow s Schema) -> Maybe (Map String Value -> Flow s Schema) forall k a. Ord k => k -> Map k a -> Maybe a M.lookup String typ Map String (Map String Value -> Flow s Schema) forall {s}. Map String (Map String Value -> Flow s Schema) decoders of Maybe (Map String Value -> Flow s Schema) Nothing -> String -> String -> Flow s Schema forall s x. String -> String -> Flow s x unexpected String "\"array\" or \"map\"" (String -> Flow s Schema) -> String -> Flow s Schema forall a b. (a -> b) -> a -> b $ String -> String forall a. Show a => a -> String show String typ Just Map String Value -> Flow s Schema d -> Map String Value -> Flow s Schema d Map String Value m where decoders :: Map String (Map String Value -> Flow s Schema) decoders = [(String, Map String Value -> Flow s Schema)] -> Map String (Map String Value -> Flow s Schema) forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ (String avro_array, \Map String Value m -> do Schema items <- String -> Map String Value -> Flow s Value forall s. String -> Map String Value -> Flow s Value require String avro_items Map String Value m Flow s Value -> (Value -> Flow s Schema) -> Flow s Schema forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Value -> Flow s Schema forall s. Value -> Flow s Schema decodeSchema Schema -> Flow s Schema forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (Schema -> Flow s Schema) -> Schema -> Flow s Schema forall a b. (a -> b) -> a -> b $ Array -> Schema Avro.SchemaArray (Array -> Schema) -> Array -> Schema forall a b. (a -> b) -> a -> b $ Schema -> Array Avro.Array Schema items), (String avro_enum, \Map String Value m -> Value -> Flow s Schema forall s. Value -> Flow s Schema decodeNamedSchema (Value -> Flow s Schema) -> Value -> Flow s Schema forall a b. (a -> b) -> a -> b $ Map String Value -> Value Json.ValueObject Map String Value m), (String avro_fixed, \Map String Value m -> Value -> Flow s Schema forall s. Value -> Flow s Schema decodeNamedSchema (Value -> Flow s Schema) -> Value -> Flow s Schema forall a b. (a -> b) -> a -> b $ Map String Value -> Value Json.ValueObject Map String Value m), (String avro_map, \Map String Value m -> do Schema values <- String -> Map String Value -> Flow s Value forall s. String -> Map String Value -> Flow s Value require String avro_values Map String Value m Flow s Value -> (Value -> Flow s Schema) -> Flow s Schema forall a b. Flow s a -> (a -> Flow s b) -> Flow s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Value -> Flow s Schema forall s. Value -> Flow s Schema decodeSchema Schema -> Flow s Schema forall a. a -> Flow s a forall (m :: * -> *) a. Monad m => a -> m a return (Schema -> Flow s Schema) -> Schema -> Flow s Schema forall a b. (a -> b) -> a -> b $ Map_ -> Schema Avro.SchemaMap (Map_ -> Schema) -> Map_ -> Schema forall a b. (a -> b) -> a -> b $ Schema -> Map_ Avro.Map_ Schema values), (String avro_record, \Map String Value m -> Value -> Flow s Schema forall s. Value -> Flow s Schema decodeNamedSchema (Value -> Flow s Schema) -> Value -> Flow s Schema forall a b. (a -> b) -> a -> b $ Map String Value -> Value Json.ValueObject Map String Value m)] Json.ValueString String s -> Schema -> Flow s Schema forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure (Schema -> Flow s Schema) -> Schema -> Flow s Schema forall a b. (a -> b) -> a -> b $ case String -> Map String Primitive -> Maybe Primitive forall k a. Ord k => k -> Map k a -> Maybe a M.lookup String s Map String Primitive schemas of Just Primitive prim -> Primitive -> Schema Avro.SchemaPrimitive Primitive prim Maybe Primitive Nothing -> String -> Schema Avro.SchemaReference String s where schemas :: Map String Primitive schemas = [(String, Primitive)] -> Map String Primitive forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ (String avro_boolean, Primitive Avro.PrimitiveBoolean), (String avro_bytes, Primitive Avro.PrimitiveBytes), (String avro_double, Primitive Avro.PrimitiveDouble), (String avro_float, Primitive Avro.PrimitiveFloat), (String avro_int, Primitive Avro.PrimitiveInt), (String avro_long, Primitive Avro.PrimitiveLong), (String avro_null, Primitive Avro.PrimitiveNull), (String avro_string, Primitive Avro.PrimitiveString)] Value Json.ValueNull -> Schema -> Flow s Schema forall a. a -> Flow s a forall (f :: * -> *) a. Applicative f => a -> f a pure (Schema -> Flow s Schema) -> Schema -> Flow s Schema forall a b. (a -> b) -> a -> b $ Primitive -> Schema Avro.SchemaPrimitive (Primitive -> Schema) -> Primitive -> Schema forall a b. (a -> b) -> a -> b $ Primitive Avro.PrimitiveNull Value _ -> String -> String -> Flow s Schema forall s x. String -> String -> Flow s x unexpected String "JSON array, object, or string" (String -> Flow s Schema) -> String -> Flow s Schema forall a b. (a -> b) -> a -> b $ Value -> String forall a. Show a => a -> String show Value v getAnnotations :: M.Map String Json.Value -> M.Map String Json.Value getAnnotations :: Map String Value -> Map String Value getAnnotations = [(String, Value)] -> Map String Value forall k a. Ord k => [(k, a)] -> Map k a M.fromList ([(String, Value)] -> Map String Value) -> (Map String Value -> [(String, Value)]) -> Map String Value -> Map String Value forall b c a. (b -> c) -> (a -> b) -> a -> c . [Maybe (String, Value)] -> [(String, Value)] forall a. [Maybe a] -> [a] Y.catMaybes ([Maybe (String, Value)] -> [(String, Value)]) -> (Map String Value -> [Maybe (String, Value)]) -> Map String Value -> [(String, Value)] forall b c a. (b -> c) -> (a -> b) -> a -> c . ((String, Value) -> Maybe (String, Value)) -> [(String, Value)] -> [Maybe (String, Value)] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (String, Value) -> Maybe (String, Value) forall {b}. (String, b) -> Maybe (String, b) toPair ([(String, Value)] -> [Maybe (String, Value)]) -> (Map String Value -> [(String, Value)]) -> Map String Value -> [Maybe (String, Value)] forall b c a. (b -> c) -> (a -> b) -> a -> c . Map String Value -> [(String, Value)] forall k a. Map k a -> [(k, a)] M.toList where toPair :: (String, b) -> Maybe (String, b) toPair (String k, b v) = if Int -> String -> String forall a. Int -> [a] -> [a] L.take Int 1 String k String -> String -> Bool forall a. Eq a => a -> a -> Bool == String "@" then (String, b) -> Maybe (String, b) forall a. a -> Maybe a Just (Int -> String -> String forall a. Int -> [a] -> [a] L.drop Int 1 String k, b v) else Maybe (String, b) forall a. Maybe a Nothing