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

module API.User where

import Data.Text (Text)
import Data.UUID (UUID)
import Effectful
import Puppy.Context
import Puppy.Crypto.RNG (genRSA, genUUID, RNG)
import Puppy.Database
import Puppy.Protocol.ActivityStreams
import Puppy.Types
import qualified Crypto.PubKey.RSA as RSA

createUser
  :: (ServerInfo :> es, DB :> es, RNG :> es)
  => Text
  -> Eff es ()
createUser userName = transaction $ do
  -- Generate the user's ID
  userId <- genUUID
  -- Create default channel
  mainChannel <- createChannel userName
  insertNewUser (User {
    userId,
    userName,
    mainChannel
  })
  
createChannel
  :: (ServerInfo :> es, DB :> es, RNG :> es)
  => Text
  -> Eff es UUID
createChannel accountName = do
  (publicKey, privateKey) <- genRSA
  actorId <- createActor accountName publicKey
  channelId <- genUUID
  insertNewChannel (Channel {
    linkedActorId = actorId,
    privateKeyPem = privateKey,
    channelId,
    settings = (ChannelSettings { autoAcceptFollows = True })
  })
  return channelId

createActor
  :: (ServerInfo :> es, DB :> es)
  => Text
  -> RSA.PublicKey
  -> Eff es Text
createActor accountName publicKeyPem = do
  Id actorId <- localActorId accountName
  insertNewActor (Actor {
    id          = Id actorId,
    inbox       = Just $ Inbox (actorId <> "/inbox"),
    outbox      = Just $ Id (actorId <> "/outbox"),
    followers   = Just $ Id (actorId <> "/followers"),
    following   = Just $ Id (actorId <> "/following"),
    accountName,
    displayName = Nothing,
    summary     = Nothing,
    publicKey   = PublicKey {
      id = Id (actorId <> "#key"),
      owner = Id actorId,
      publicKeyPem
    },
    locked      = True,
    subtype     = Person
  })
  return actorId