support web:bind alias redirect

This commit is contained in:
voidlizard 2025-02-06 16:03:28 +03:00
parent 2628d7efa0
commit 95b93698ac
2 changed files with 84 additions and 56 deletions

View File

@ -42,6 +42,7 @@ import Codec.Serialise (deserialiseOrFail)
import Data.Aeson (object, (.=)) import Data.Aeson (object, (.=))
import Data.ByteString.Lazy.Char8 qualified as LBS8 import Data.ByteString.Lazy.Char8 qualified as LBS8
import Data.Text qualified as Text import Data.Text qualified as Text
import Data.Text.Lazy qualified as LT
import Data.HashMap.Strict qualified as HM import Data.HashMap.Strict qualified as HM
import Control.Monad.Reader import Control.Monad.Reader
import Lens.Micro.Platform (view) import Lens.Micro.Platform (view)
@ -255,10 +256,17 @@ httpWorker (PeerConfig syn) pmeta = do
-- pattern WebRef :: forall {s} . sEither (L -- pattern WebRef :: forall {s} . sEither (L
webRef :: forall c s . (IsContext c, s ~ HBS2Basic) => Syntax c -> Maybe (Text, Either (LWWRefKey s) HashRef) data WebRefAction s =
RefTree HashRef
| RefRef (LWWRefKey s)
| RefRedirect Text
webRef :: forall c s . (IsContext c, s ~ HBS2Basic) => Syntax c -> Maybe (Text, WebRefAction s)
webRef = \case webRef = \case
ListVal [TextLike "web:bind", TextLike name, TextLike "tree", HashLike h] -> Just (name, Right h) ListVal [TextLike "web:bind", TextLike name, TextLike "tree", HashLike h] -> Just (name, RefTree h)
ListVal [TextLike "web:bind", TextLike name, TextLike "ref", SignPubKeyLike k] -> Just (name, Left (LWWRefKey k)) ListVal [TextLike "web:bind", TextLike name, TextLike "ref", SignPubKeyLike k] -> Just (name, RefRef (LWWRefKey k))
ListVal [TextLike "web:bind", TextLike name, TextLike "redirect", TextLike re] -> Just (name, RefRedirect re)
_ -> Nothing _ -> Nothing
noWebRoot :: [Syntax c] -> [Syntax c] noWebRoot :: [Syntax c] -> [Syntax c]
@ -272,6 +280,8 @@ getTreeHash :: forall e s . (s ~ Encryption e, ForSignedBox s, IsRefPubKey s, s
getTreeHash sto part what'' = void $ flip runContT pure do getTreeHash sto part what'' = void $ flip runContT pure do
callCC \exit -> do
flip fix (mempty, what'', 0) $ \again (p, what',i) -> do flip fix (mempty, what'', 0) $ \again (p, what',i) -> do
let what = fromHashRef what' let what = fromHashRef what'
@ -293,13 +303,22 @@ getTreeHash sto part what'' = void $ flip runContT pure do
| ListVal [SymbolVal "file-name:", LitStrVal w] <- meta | ListVal [SymbolVal "file-name:", LitStrVal w] <- meta
] ]
let ce = headMay let ce = headMay
[ show (pretty w) [ show (pretty w)
| ListVal [SymbolVal "content-encoding:", StringLike w] <- meta | ListVal [SymbolVal "content-encoding:", StringLike w] <- meta
] ]
let parts = (Nothing, Right what') : [ (Just name, w)
let re = headMay
[ show (pretty w)
| ListVal [SymbolVal "web:redirect", StringLike w] <- meta
]
for_ re $ \l -> do
lift $ redirect (fromString l)
exit ()
let parts = (Nothing, RefTree what') : [ (Just name, w)
| ( webRef @C -> Just (name, w) ) <- meta | ( webRef @C -> Just (name, w) ) <- meta
] & HM.fromList ] & HM.fromList
@ -334,8 +353,12 @@ getTreeHash sto part what'' = void $ flip runContT pure do
debug $ red "META" <+> pretty meta <+> line <+> pretty (HM.keys parts) debug $ red "META" <+> pretty meta <+> line <+> pretty (HM.keys parts)
key <- case HM.lookup part parts of key <- case HM.lookup part parts of
Just (Right key) -> pure key Just (RefTree key) -> pure key
Just (Left lww) -> lookupLWWRef @e sto lww Just (RefRef lww) -> lookupLWWRef @e sto lww
Just (RefRedirect s) -> do
lift $ redirect (LT.fromStrict s)
exit ()
_ -> pure (HashRef what) _ -> pure (HashRef what)
elbs <- lift $ runExceptT $ readFromMerkle sto (SimpleKey (coerce key)) elbs <- lift $ runExceptT $ readFromMerkle sto (SimpleKey (coerce key))

View File

@ -44,6 +44,7 @@ module Data.Config.Suckless.Syntax
, pattern TextLikeList , pattern TextLikeList
, pattern Nil , pattern Nil
, pattern OpaqueVal , pattern OpaqueVal
, pattern MatchOpaqueVal
) )
where where
@ -133,6 +134,10 @@ pattern Nil <- ListVal []
pattern OpaqueVal :: forall {c} . Opaque -> Syntax c pattern OpaqueVal :: forall {c} . Opaque -> Syntax c
pattern OpaqueVal box <- OpaqueValue box pattern OpaqueVal box <- OpaqueValue box
-- by @qnikst, thanks, dude
pattern MatchOpaqueVal :: forall c a . (IsContext c, Typeable a) => a -> Syntax c
pattern MatchOpaqueVal o <- (OpaqueVal (fromOpaque -> Just o))
data family Context c :: Type data family Context c :: Type
isOpaqueOf :: forall a c . (Typeable a, IsContext c) => Syntax c -> Maybe a isOpaqueOf :: forall a c . (Typeable a, IsContext c) => Syntax c -> Maybe a