module Hix.NixExpr where

import Data.List.NonEmpty ((<|))
import qualified Data.Text as Text
import Exon (exon)

import Hix.Class.EncodeNix (EncodeNix (encodeNix))
import Hix.Data.NixExpr (Expr (..), ExprAttr (ExprAttr, ExprAttrNil))

indent ::
  Functor t =>
  Int ->
  t Text ->
  t Text
indent :: forall (t :: * -> *). Functor t => Int -> t Text -> t Text
indent Int
n =
  (Text -> Text) -> t Text -> t Text
forall a b. (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Text -> Text
Text.replicate Int
n Text
" " <>)

withSemicolon :: NonEmpty Text -> NonEmpty Text
withSemicolon :: NonEmpty Text -> NonEmpty Text
withSemicolon = \case
  Text
e :| [] ->
    [Text
e Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";"]
  Text
h :| Text
h1 : [Text]
t -> Text
h Text -> NonEmpty Text -> NonEmpty Text
forall a. a -> NonEmpty a -> NonEmpty a
<| NonEmpty Text -> NonEmpty Text
withSemicolon (Text
h1 Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| [Text]
t)

renderAttrs :: Int -> [ExprAttr] -> [Text]
renderAttrs :: Int -> [ExprAttr] -> [Text]
renderAttrs Int
ind [ExprAttr]
attrs =
  [ExprAttr]
attrs [ExprAttr] -> (ExprAttr -> [Text]) -> [Text]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    ExprAttr Text
k Expr
v ->
      case Int -> Expr -> NonEmpty Text
renderExpr Int
ind Expr
v of
        Text
e :| [] -> [Item [Text]
[exon|#{k} = #{e};|]]
        Text
h :| (Text
h1 : [Text]
t) -> [exon|#{k} = #{h}|] Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty Text -> NonEmpty Text
withSemicolon (Text
h1 Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| [Text]
t))
    ExprAttr
ExprAttrNil ->
      []

renderExpr :: Int -> Expr -> NonEmpty Text
renderExpr :: Int -> Expr -> NonEmpty Text
renderExpr Int
ind = \case
  Expr
ExprNull -> [Text
Item (NonEmpty Text)
"null"]
  ExprString Text
s -> Int -> NonEmpty Text -> NonEmpty Text
forall (t :: * -> *). Functor t => Int -> t Text -> t Text
indent Int
ind [Item (NonEmpty Text)
[exon|"#{Text.replace "\"" "\\\"" s}"|]]
  ExprLit Text
e -> [Text
Item (NonEmpty Text)
e]
  ExprList [Expr]
l -> Text
"[" Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| (Int -> [Text] -> [Text]
forall (t :: * -> *). Functor t => Int -> t Text -> t Text
indent (Int
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty Text -> [Text])
-> (Expr -> NonEmpty Text) -> Expr -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Expr -> NonEmpty Text
renderExpr Int
ind (Expr -> [Text]) -> [Expr] -> [Text]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Expr]
l)) [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
Item [Text]
"]"]
  ExprAttrs [ExprAttr]
a -> case Int -> [ExprAttr] -> [Text]
renderAttrs Int
ind [ExprAttr]
a of
    [] -> [Text
Item (NonEmpty Text)
"{}"]
    [Text]
as -> Text
"{" Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| Int -> [Text] -> [Text]
forall (t :: * -> *). Functor t => Int -> t Text -> t Text
indent (Int
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) [Text]
as [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
Item [Text]
"}"]
  ExprPrefix Text
p (Int -> Expr -> NonEmpty Text
renderExpr Int
ind -> Text
h :| [Text]
t) ->
    [exon|#{p} #{h}|] Text -> [Text] -> NonEmpty Text
forall a. a -> [a] -> NonEmpty a
:| [Text]
t

renderRootExpr :: Expr -> Text
renderRootExpr :: Expr -> Text
renderRootExpr =
  [Text] -> Text
Text.unlines ([Text] -> Text) -> (Expr -> [Text]) -> Expr -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty Text -> [Text])
-> (Expr -> NonEmpty Text) -> Expr -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Expr -> NonEmpty Text
renderExpr Int
0

checkEmpty ::
  Text ->
  Expr ->
  ExprAttr
checkEmpty :: Text -> Expr -> ExprAttr
checkEmpty Text
key = \case
  ExprString Text
value | Text -> Bool
Text.null Text
value ->
    ExprAttr
ExprAttrNil
  ExprList [Expr]
value | [Expr] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Expr]
value ->
    ExprAttr
ExprAttrNil
  Expr
value ->
    Text -> Expr -> ExprAttr
ExprAttr Text
key Expr
value

singleOpt ::
  EncodeNix a =>
  Text ->
  (e -> Maybe a) ->
  e ->
  ExprAttr
singleOpt :: forall a e. EncodeNix a => Text -> (e -> Maybe a) -> e -> ExprAttr
singleOpt Text
key e -> Maybe a
get e
entity =
  ExprAttr -> (a -> ExprAttr) -> Maybe a -> ExprAttr
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ExprAttr
ExprAttrNil (Text -> Expr -> ExprAttr
checkEmpty Text
key (Expr -> ExprAttr) -> (a -> Expr) -> a -> ExprAttr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Expr
forall a. EncodeNix a => a -> Expr
encodeNix) (e -> Maybe a
get e
entity)

single ::
  EncodeNix a =>
  Text ->
  (e -> a) ->
  e ->
  ExprAttr
single :: forall a e. EncodeNix a => Text -> (e -> a) -> e -> ExprAttr
single Text
key e -> a
get =
  Text -> (e -> Maybe a) -> e -> ExprAttr
forall a e. EncodeNix a => Text -> (e -> Maybe a) -> e -> ExprAttr
singleOpt Text
key (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> (e -> a) -> e -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> a
get)

multiOpt ::
  EncodeNix a =>
  Text ->
  (e -> Maybe [a]) ->
  e ->
  ExprAttr
multiOpt :: forall a e.
EncodeNix a =>
Text -> (e -> Maybe [a]) -> e -> ExprAttr
multiOpt Text
key e -> Maybe [a]
get e
entity =
  ExprAttr -> ([a] -> ExprAttr) -> Maybe [a] -> ExprAttr
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ExprAttr
ExprAttrNil (Text -> Expr -> ExprAttr
checkEmpty Text
key (Expr -> ExprAttr) -> ([a] -> Expr) -> [a] -> ExprAttr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Expr
forall a. EncodeNix a => a -> Expr
encodeNix) (e -> Maybe [a]
get e
entity)

multi ::
  EncodeNix a =>
  Text ->
  (e -> [a]) ->
  e ->
  ExprAttr
multi :: forall a e. EncodeNix a => Text -> (e -> [a]) -> e -> ExprAttr
multi Text
key e -> [a]
get =
  Text -> (e -> Maybe [a]) -> e -> ExprAttr
forall a e.
EncodeNix a =>
Text -> (e -> Maybe [a]) -> e -> ExprAttr
multiOpt Text
key ([a] -> Maybe [a]
forall a. a -> Maybe a
Just ([a] -> Maybe [a]) -> (e -> [a]) -> e -> Maybe [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> [a]
get)

multiOrSingle ::
   a e .
  EncodeNix a =>
  Text ->
  (e -> [a]) ->
  e ->
  ExprAttr
multiOrSingle :: forall a e. EncodeNix a => Text -> (e -> [a]) -> e -> ExprAttr
multiOrSingle Text
key e -> [a]
get e
entity =
  [a] -> ExprAttr
check (e -> [a]
get e
entity)
  where
    check :: [a] -> ExprAttr
    check :: [a] -> ExprAttr
check [] = ExprAttr
ExprAttrNil
    check [Item [a]
sing] = Text -> Expr -> ExprAttr
ExprAttr Text
key (a -> Expr
forall a. EncodeNix a => a -> Expr
encodeNix a
Item [a]
sing)
    check [a]
values = Text -> Expr -> ExprAttr
ExprAttr Text
key ([a] -> Expr
forall a. EncodeNix a => a -> Expr
encodeNix [a]
values)

mkAttrs :: [e -> ExprAttr] -> e -> [ExprAttr]
mkAttrs :: forall e. [e -> ExprAttr] -> e -> [ExprAttr]
mkAttrs [e -> ExprAttr]
a e
e =
  (((e -> ExprAttr) -> ExprAttr) -> [e -> ExprAttr] -> [ExprAttr]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((e -> ExprAttr) -> e -> ExprAttr
forall a b. (a -> b) -> a -> b
$ e
e) [e -> ExprAttr]
a)

notNil :: ExprAttr -> Bool
notNil :: ExprAttr -> Bool
notNil = \case
  ExprAttr
ExprAttrNil -> Bool
False
  ExprAttr
_ -> Bool
True

nonEmptyAttrs :: Text -> [ExprAttr] -> ExprAttr
nonEmptyAttrs :: Text -> [ExprAttr] -> ExprAttr
nonEmptyAttrs Text
key =
  (ExprAttr -> Bool) -> [ExprAttr] -> [ExprAttr]
forall a. (a -> Bool) -> [a] -> [a]
filter ExprAttr -> Bool
notNil ([ExprAttr] -> [ExprAttr])
-> ([ExprAttr] -> ExprAttr) -> [ExprAttr] -> ExprAttr
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> \case
    [] -> ExprAttr
ExprAttrNil
    [ExprAttr]
as -> Text -> Expr -> ExprAttr
ExprAttr Text
key ([ExprAttr] -> Expr
ExprAttrs [ExprAttr]
as)