module Schema ( Schema, viewSchema, schemaTable, schemaForm, ) where #ifdef ghcjs_HOST_OS import Data.Text qualified as T #endif import Control.Applicative ((<|>)) import Data.Aeson qualified as A import Data.Aeson.Key qualified as AK import Data.Aeson.KeyMap qualified as AM import Data.List import Data.Map qualified as M import Data.Maybe import Data.Scientific (fromFloatDigits) import Data.Set qualified as S import Form qualified as F import Miso import Miso.String (MisoString, fromMisoString, intercalate, toMisoString) import Route import Safe data Schema = Schema { id :: MisoString, schema :: MisoString, properties :: M.Map MisoString Property, required :: S.Set MisoString, title :: MisoString, type_ :: MisoString } deriving (Show, Eq) instance A.FromJSON Schema where parseJSON = A.withObject "Schema" $ \v -> Schema <$> v A..: "$id" <*> v A..: "$schema" <*> v A..: "properties" <*> v A..: "required" <*> v A..: "title" <*> v A..: "type" #ifdef ghcjs_HOST_OS instance A.FromJSONKey MisoString where parseJSON = fromMisoString @T.Text <$> parseJSON #endif data Property = Type MisoString | Reference MisoString | Union [MisoString] deriving (Show, Eq) instance A.FromJSON Property where parseJSON = A.withObject "Property" $ \v -> (Type <$> v A..: "type") <|> (Reference <$> v A..: "$ref") <|> (fmap Union $ traverse (A..: "type") =<< v A..: "oneOf") viewSchema :: Schema -> View action viewSchema schema = ol_ [] $ ( \(k, v) -> li_ [] $ [ text (toMisoString k), text ":", text ( case v of Type v -> toMisoString v Reference v -> "reference to " <> toMisoString v Union vs -> Miso.String.intercalate " or " vs ), text (if k `S.member` schema.required then "" else "?") ] ) <$> (M.toList schema.properties) schemaTable :: MisoString -> Schema -> [A.Object] -> View action schemaTable collection schema values = table_ [] [thead, tbody] where thead = thead_ [] $ [ tr_ [] $ [ th_ [] [text (toMisoString k)] | k <- M.keys schema.properties ] ] tbody = tbody_ [] $ [ tr_ [] [ td_ [] $ [ case (k, getO (AK.fromText (fromMisoString k)) value) of ("$fileName", A.String fn) -> a_ [ href_ (routeToMisoString (EditValue collection (toMisoString fn))) ] [ text (toMisoString fn) ] (_, v) -> text $ case v of A.String s -> toMisoString s _ -> toMisoString (A.encode v) ] | k <- M.keys schema.properties ] | value <- values ] schemaForm :: Schema -> F.Form A.Object A.Object schemaForm schema = fmap mergeJson . sequence . catMaybes $ ( \((AK.fromText . fromMisoString) -> k, v) -> case v of Type "string" -> Just $ if toMisoString (AK.toText k) `S.member` schema.required then AM.singleton k <$> ( F.mapValues (getO k) (setO k) $ fmap (A.String . fromMisoString) . F.mapValues fromJson toJson $ F.inputText (toMisoString (AK.toString k)) ) else AM.singleton k <$> ( F.mapValues (getO k) (setO k) $ fmap (maybe A.Null (A.String . fromMisoString)) . F.mapValues fromJson toJson $ F.optional (F.inputText (toMisoString (AK.toString k))) ) Type "number" -> Just $ if toMisoString (AK.toText k) `S.member` schema.required then AM.singleton k <$> ( F.mapValues (getO k) (setO k) $ fmap ((A.Number . fromFloatDigits)) . F.mapValues fromJson toJson $ F.inputNumber (toMisoString (AK.toString k)) ) else AM.singleton k <$> ( F.mapValues (getO k) (setO k) $ fmap (maybe A.Null (A.Number . fromFloatDigits)) . F.mapValues fromJson toJson $ F.optional (F.inputNumber (toMisoString (AK.toString k))) ) Reference _ -> Nothing Union (map F.stringToTypeName -> typeStrings) -> let inputFromOutput = \case A.String x -> pure (F.StringType, M.singleton F.StringType (toMisoString x)) A.Number x -> pure (F.NumberType, M.singleton F.NumberType (toMisoString (show x))) _ -> fail "" inputFromInput = A.fromJSON inputDef = ( fromMaybe F.StringType (headMay typeStrings), M.empty ) in Just $ if toMisoString (AK.toText k) `S.member` schema.required then AM.singleton k <$> ( fmap A.toJSON $ F.mapValues (getInput k inputFromOutput inputFromInput inputDef) (setInput k A.toJSON) $ F.inputUnion (toMisoString (AK.toString k)) typeStrings ) else AM.singleton k <$> ( fmap A.toJSON $ F.mapValues (getInput k inputFromOutput inputFromInput inputDef) (setInput k A.toJSON) $ F.optional (F.inputUnion (toMisoString (AK.toString k)) typeStrings) ) _ -> Nothing ) <$> (M.toList schema.properties) mergeJson :: [A.Object] -> A.Object mergeJson = foldl' mergeObject AM.empty mergeObject :: A.Object -> A.Object -> A.Object mergeObject kvs kvs' = AM.union kvs kvs' fromJson :: A.Value -> MisoString fromJson (A.String x) = toMisoString x fromJson _ = "" toJson :: MisoString -> A.Value -> A.Value toJson x _ = A.String (fromMisoString x) getO :: AK.Key -> A.Object -> A.Value getO k kvs = fromMaybe A.Null (AM.lookup k kvs) setO :: AK.Key -> A.Value -> A.Object -> A.Object setO k v kvs = AM.insert k v kvs -- | Used in `mapValues (getInput ...) (setInput ..)`. -- -- Suppose *input" is an `A.Object`, this function is concerned with getting a sub-form model from within that object, given a *key* and the *subform's type*. -- -- The input model can be in three different states: -- -- - (1) The input object has been converted from an output model, no modification has been done on it. The value in question corresponds to the output model, which may be different from the corresponding form value. -- - (2) The input object had been modified, and so the value in question conforms structurally to the input value. -- - (3) The input object is in an undefined state, ie. this should not happen. -- -- The first three arguments `(A.Value -> A.Result i)`, `(A.Value -> A.Result i)`, `i` correspond to these cases and are tested for in order of (2), (1), (3). getInput :: AK.Key -> (A.Value -> A.Result i) -> (A.Value -> A.Result i) -> i -> A.Object -> i getInput k f1 f2 f3 kvs = let v = getO k kvs in case f2 v <|> f1 v of A.Error _ -> f3 A.Success x -> x setInput :: AK.Key -> (i -> A.Value) -> i -> A.Object -> A.Object setInput k f i kvs = setO k (f i) kvs