module Main where #ifndef ghcjs_HOST_OS import Data.Maybe import Data.String import Language.Javascript.JSaddle.Warp as JSaddle import Network.HTTP.Simple #else import Data.ByteString.Char8 qualified as B import Data.Maybe import Data.String import JavaScript.Web.XMLHttpRequest import Miso.String qualified as J #endif import Data.Aeson qualified as A import Data.Aeson.Key qualified as AK import Data.Aeson.KeyMap qualified as AM import Data.ByteString.Lazy.Char8 qualified as LB import Data.Default import Data.Function import Data.List import Data.Map qualified as M import Data.Text qualified as T import Form qualified as F import GHC.Generics (Generic) import Miso import Miso.String (toMisoString) import NeatInterpolation qualified as Q data Model = Model { schema :: Maybe (Either String Schema), posts :: Maybe (Either String [A.Value]), input :: Maybe A.Value } deriving (Show, Eq, Generic, Default) data Schema = Schema { id :: String, schema :: String, title :: String, type_ :: SchemaType } deriving (Show, Eq) instance A.FromJSON Schema where parseJSON = A.withObject "Schema" ( \v -> Schema <$> v A..: "$id" <*> v A..: "$schema" <*> v A..: "title" <*> A.parseJSON (A.Object v) ) data SchemaType = Object (M.Map String String) deriving (Show, Eq) instance A.FromJSON SchemaType where parseJSON = A.withObject "SchemaType" ( \v -> v A..: "type" >>= \case ("object" :: String) -> Object <$> v A..: "properties" ) data Action = NoOp | Init | FetchSchema | SetSchema (Either String Schema) | FetchPosts | SetPosts (Either String [A.Value]) | FormChanged A.Value | FormSubmitted A.Value deriving (Show, Eq) #ifndef ghcjs_HOST_OS runApp :: JSM () -> IO () runApp f = JSaddle.debugOr 8080 (f >> syncPoint) JSaddle.jsaddleApp #else runApp :: IO () -> IO () runApp app = app #endif main :: IO () main = runApp $ startApp App {..} where initialAction = Init model = def update = updateModel view = viewModel events = defaultEvents subs = [] mountPoint = Nothing logLevel = Off updateModel :: Action -> Model -> Effect Action Model updateModel action m = case action of NoOp -> noEff m Init -> batchEff m [pure FetchSchema, pure FetchPosts] FetchSchema -> m <# do SetSchema <$> fetchSchema SetSchema schema -> let setSchema :: Either String Schema -> Model -> Model setSchema schema m = m {schema = Just schema} in noEff (setSchema schema m) FetchPosts -> m <# do SetPosts <$> fetchPosts SetPosts posts -> let setPosts :: Either String [A.Value] -> Model -> Model setPosts posts m = m {posts = Just posts} in noEff (setPosts posts m) FormChanged (Just -> input) -> noEff m {input} FormSubmitted output -> m <# do const NoOp <$> consoleLog (toMisoString (A.encode output)) fetchSchema :: JSM (Either String Schema) fetchSchema = A.eitherDecode <$> fetch (fromString "http://localhost:8081/posts.schema.json") fetchPosts :: JSM (Either String [A.Value]) fetchPosts = A.eitherDecode <$> fetch ( fromString "http://localhost:8081" & setRequestMethod "POST" & setRequestBodyLBS "SELECT posts FROM posts" ) fetch :: Request -> JSM LB.ByteString fetch req = LB.fromStrict . getResponseBody <$> httpBS req #ifdef ghcjs_HOST_OS httpBS :: Request -> JSM (Response B.ByteString) httpBS req = xhrByteString req instance IsString Request where fromString uri = Request { reqMethod = GET, reqURI = J.pack uri, reqLogin = Nothing, reqHeaders = [], reqWithCredentials = False, reqData = NoData } setRequestMethod :: B.ByteString -> Request -> Request setRequestMethod "POST" req = req {reqMethod = POST} setRequestBodyLBS :: LB.ByteString -> Request -> Request setRequestBodyLBS body req = req {reqData = StringData (J.pack (LB.unpack body))} getResponseBody :: Response B.ByteString -> B.ByteString getResponseBody = fromMaybe "" . contents #endif viewModel :: Model -> View Action viewModel model = let input = fromMaybe (A.Object AM.empty) model.input in div_ [] $ [ viewCss, viewHeader, nav_ [] [viewCollections], main_ [] $ [ maybe (text "..") (either err viewSchema) model.schema, maybe (text "..") (either err viewPosts) model.posts, maybe (text "..") (either err (viewForm input)) model.schema, viewInput input ] ] viewCss :: View Action viewCss = node HTML "style" Nothing [type_ "text/css"] [ text ( toMisoString [Q.text| /* normalize */ * { box-sizing: border-box; } body { margin: 0; min-height: 100vh; } /* typography */ html { font: Iosevka; } /* layout */ body > div { display: flex; flex-flow: row nowrap; min-height: 100vh; padding-top: 64px; align-items: stretch; } header { position: fixed; top: 0; left: 0; width: 100%; height: 64px; } nav, main { min-height: 100%; } nav { flex: 0 0 200px; } main { flex: 1 1 auto; } /* borders */ header { border-bottom: 1px solid gray; } nav { border-right: 1px solid gray; } /* padding */ nav, header, main { padding: 16px; } /* scrolling */ body > div { overflow: visible; } header { overflow: visible; } nav, main { overflow: auto; } /* header */ header { display: flex; align-items: center; } header section { margin-left: auto; } header section:first-child { margin-left: 0; } |] ) ] err :: String -> View Action err = text . toMisoString . ("err! " <>) viewHeader :: View Action viewHeader = header_ [] $ [ section_ [] [h1_ [] [text "acms"]], section_ [] [viewBranch] ] viewBranch :: View Action viewBranch = select_ [] [option_ [] [text "main"]] viewCollections :: View Action viewCollections = section_ [] $ [ span_ [] [text "collections"], ol_ [] [li_ [] [a_ [href_ "#"] [text "posts"]]] ] viewSchema :: Schema -> View Action viewSchema schema = case schema.type_ of Object properties -> ol_ [] $ ( \(k, v) -> li_ [] $ [ text (toMisoString k), text ":", text (toMisoString v) ] ) <$> (M.toList properties) viewForm :: A.Value -> Schema -> View Action viewForm input = fmap (either FormChanged FormSubmitted) . flip F.runForm input . schemaForm viewInput :: A.Value -> View Action viewInput input = pre_ [] [text (toMisoString (A.encode input))] schemaForm :: Schema -> F.Form A.Value A.Value schemaForm schema = fmap mergeJson . sequence $ case schema.type_ of Object properties -> ( \(AK.fromString -> k, "string") -> A.Object . AM.singleton k <$> ( F.mapValues (getO k) (setO k) $ jsonString (AK.toString k) ) ) <$> (M.toList properties) mergeJson :: [A.Value] -> A.Value mergeJson = foldl' mergeObject (A.Object AM.empty) mergeObject :: A.Value -> A.Value -> A.Value mergeObject (A.Object kvs) (A.Object kvs') = A.Object (AM.union kvs kvs') fromJson :: A.Value -> T.Text fromJson (A.String x) = x fromJson _ = "" toJson :: T.Text -> A.Value -> A.Value toJson x _ = A.String x getO :: AK.Key -> A.Value -> A.Value getO k (A.Object kvs) = fromMaybe A.Null (AM.lookup k kvs) setO :: AK.Key -> A.Value -> A.Value -> A.Value setO k v (A.Object kvs) = A.Object (AM.insert k v kvs) jsonString :: String -> F.Form A.Value A.Value jsonString = fmap A.String . F.mapValues fromJson toJson . F.string viewPosts :: [A.Value] -> View Action viewPosts posts = ol_ [] (viewPost <$> posts) where viewPost post = pre_ [] [text (toMisoString (A.encode post))]