{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Biz.Namespace
  ( Namespace (..),
    Ext (..),
    fromPath,
    fromContent,
    fromHaskellModule,
    toPath,
    toHaskellModule,
    toSchemeModule,
  )
where

import Alpha
import qualified Data.Aeson as Aeson
import qualified Data.Char as Char
import qualified Data.List as List
import qualified Data.List.Split as List
import qualified Text.Regex.Applicative as Regex

data Ext = Hs | Scm | Nix | Md | Css | Py | Sh | Keys | Json | None
  deriving (Eq, Show, Generic, Aeson.ToJSON)

data Namespace = Namespace {path :: [String], ext :: Ext}
  deriving (Eq, Show, Generic, Aeson.ToJSON)

fromPath :: String -> String -> Maybe Namespace
fromPath bizRoot absPath =
  List.stripPrefix bizRoot absPath
    +> List.stripPrefix "/"
    +> Regex.match (Namespace </ rePath <* dot <*> reExt)

fromContent :: String -> Maybe Namespace
fromContent c = case Regex.findFirstInfix haskellModule c of
  Nothing -> Nothing
  Just (_, Namespace {..}, _) -> Just <| Namespace (filter (/= ".") path) ext
  where
    haskellModule =
      Namespace
        </ (Regex.string "\nmodule " *> Regex.many (name <|> dot))
        <*> pure Hs

toHaskellModule :: Namespace -> String
toHaskellModule (Namespace parts Hs) = joinWith "." parts
toHaskellModule (Namespace {..}) =
  panic <| "can't convert " <> show ext <> " to a Haskell module"

fromHaskellModule :: String -> Namespace
fromHaskellModule s = Namespace (List.splitOn "." s) Hs

toPath :: Namespace -> FilePath
toPath (Namespace parts ext) =
  joinWith "/" parts
    <> "."
    <> lowercase (show ext)

toSchemeModule :: Namespace -> String
toSchemeModule (Namespace parts Scm) = "(" ++ joinWith " " parts ++ ")"
toSchemeModule (Namespace {..}) =
  panic <| "can't convert " <> show ext <> " to a Scheme module"

dot :: Regex.RE Char String
dot = Regex.some <| Regex.sym '.'

name :: Regex.RE Char String
name =
  Regex.many (Regex.psym Char.isUpper)
    <> Regex.many (Regex.psym Char.isAlphaNum)

rePath :: Regex.RE Char [String]
rePath = Regex.many (name <* Regex.string "/" <|> name)

reExt :: Regex.RE Char Ext
reExt =
  Nix <$ Regex.string "nix"
    <|> Hs <$ Regex.string "hs"
    <|> Scm <$ Regex.string "scm"
    <|> Md <$ Regex.string "md"
    <|> Css <$ Regex.string "css"
    <|> Py <$ Regex.string "py"
    <|> Sh <$ Regex.string "sh"
    <|> Keys <$ Regex.string "pub"
    <|> Json <$ Regex.string "json"