Skip to content
Snippets Groups Projects
Commit 027df473 authored by Jean-Paul Calderone's avatar Jean-Paul Calderone
Browse files

Embed the yaml in the Haskell :/

getFilesDir gives us our _data_ directory.
Nothing yet writes out a servers.yaml there so we won't ever find it.
There is something called "assets".
Maybe that is the kind of thing we want to distribute/load.
For now, we know how to distribute Haskell code, so put it there.
parent b59d9ac7
No related branches found
No related tags found
1 merge request!51Add a real loadGrid function
......@@ -31,6 +31,7 @@ library
, obelisk-frontend
, obelisk-generated-static
, obelisk-route
, raw-strings-qq
, reflex-dom-core
, req
, tahoe-capabilities
......
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module MagicFolder where
import Text.RawString.QQ (r)
import Data.Text
import qualified Data.Text as T
import Data.Yaml (decodeEither')
import Tahoe.Announcement (Announcements)
import Control.Monad.IO.Class (MonadIO(liftIO))
import FrontendPaths (getFilesDir)
import qualified Data.ByteString as B
import Control.Exception (SomeException, try)
import Control.Exception (SomeException)
newtype MagicFolder = MagicFolder Text deriving (Eq, Ord, Show)
data FolderEntry
......@@ -28,20 +29,22 @@ data FolderEntry
-- This reads "servers.yaml" from the application-private files directory.
loadGrid :: MonadIO m => m (Either Text Announcements)
loadGrid = liftIO $ do
p <- getFilesDir
case p of
Nothing -> pure $ Left "Could not find configuration files directory"
Just dirname -> do
announcementsBytes <- try $ B.readFile (announcementPath dirname)
case announcementsBytes of
Left err -> pure $ Left $ T.concat ["Could not read grid configuration: ", T.pack $ show (err :: SomeException)]
Right bytes ->
case decodeEither' bytes of
Left err -> pure $ Left $ T.concat ["Could not parse grid configuration: ", T.pack $ show err]
Right ann -> pure $ Right ann
-- | Construct the path to the announcements file, given a base directory to
-- start from.
announcementPath :: FilePath -> FilePath
announcementPath = (<> "/" <> "servers.yaml")
case announcementsBytes of
Left err -> pure $ Left $ T.concat ["Could not read grid configuration: ", T.pack $ show (err :: SomeException)]
Right bytes ->
case decodeEither' bytes of
Left err -> pure $ Left $ T.concat ["Could not parse grid configuration: ", T.pack $ show err]
Right ann -> pure $ Right ann
where
-- TODO: Figure out how we can distribute this yaml in a separate file and
-- still be able to get at its contents, even on Android.
announcementsBytes =
Right [r|
storage:
v0-roiqkiw76qcj7gcilbbut52rsxofubqugqtgnap3rgncutdueoda:
ann:
anonymous-storage-FURL: pb://gnuer2axzoq3ggnn7gjoybmfqsjvaow3@tcp:localhost:46185/sxytycucj5eeunlx6modfazq5byp2hpb
nickname: storage001
anonymous-storage-NURLs:
- pb://4cD3anuFqhz81xiI2dtRj7eDJLsCFNXrHZZExUXotfE@localhost:46185/sxytycucj5eeunlx6modfazq5byp2hpb#v=1
|]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment