you're telling me a puppy coded this??
{-# LANGUAGE DerivingStrategies #-}

-- | Code and utilities related to the WebFinger protocol.
module Puppy.Protocol.WebFinger (
  JRD,
  Handle (..),
  parseHandle,
  lookupLocal,
  queryRemote,
) where

import Data.Aeson ((.=))
import Data.Text (Text)
import Effectful
import Puppy.Logging
import qualified Data.Aeson as JSON
import qualified Data.Text as T

-- | A JSON Resource Descriptor.
newtype JRD = JRD JSON.Value
  deriving newtype (JSON.FromJSON, JSON.ToJSON)

data Handle
  = Handle { actorName :: Text, nodeName :: Text }

parseHandle :: Text -> Maybe Handle
parseHandle = check . build . preprocess
  where
    check h = case h of
      Handle "" _ -> Nothing
      Handle _ "" -> Nothing
      handle -> Just handle
    preprocess = T.dropWhile (== '@') 
    build = Handle
      <$> T.takeWhile (/= '@')
      <*> T.takeWhileEnd (/= '@')

lookupLocal 
  :: (Log :> es) 
  => Handle 
  -> Eff es (Maybe JRD)
lookupLocal (Handle actorName nodeName) = scope "lookupLocal" $ do
  pure (Just $ JRD $ JSON.object [
    "subject" .= JSON.String ("acct:" <> actorName <> "@" <> nodeName),
    "links" .= [JSON.object [
        "rel"  .= JSON.String "self",
        "type" .= JSON.String "application/activity+json",
        "href" .= JSON.String ("https://" <> nodeName <> "/ap/a/" <> actorName)
      ]]
    ])

queryRemote :: Handle -> Eff es (Maybe JRD)
queryRemote = undefined