module Ribosome.App.Templates.Flake where

import Exon (exon)

import Ribosome.App.Data (
  Branch (Branch),
  Cachix (Cachix),
  CachixKey (CachixKey),
  CachixName (CachixName),
  FlakeUrl (FlakeUrl),
  Github (Github),
  GithubOrg (GithubOrg),
  GithubRepo (GithubRepo),
  ProjectName (ProjectName),
  )

githubAttrs :: Github -> Text
githubAttrs :: Github -> Text
githubAttrs (Github (GithubOrg Text
org) (GithubRepo Text
repo)) =
  [exon|
    githubOrg = "#{org}";
    githubRepo = "#{repo}";|]

cachixAttrs :: Cachix -> Text
cachixAttrs :: Cachix -> Text
cachixAttrs (Cachix (CachixName Text
name) (CachixKey Text
key)) =
  [exon|
    cachixName = "#{name}";
    cachixKey = "#{key}";|]

flakeNix ::
  FlakeUrl ->
  ProjectName ->
  Branch ->
  Maybe Github ->
  Maybe Cachix ->
  Text
flakeNix :: FlakeUrl
-> ProjectName -> Branch -> Maybe Github -> Maybe Cachix -> Text
flakeNix (FlakeUrl Text
flakeUrl) (ProjectName Text
name) (Branch Text
branch) Maybe Github
github Maybe Cachix
cachix =
  [exon|{
  description = "A Neovim Plugin";

  inputs = {
    ribosome.url = "#{flakeUrl}";
  };

  outputs = { ribosome, ... }: ribosome.lib.flake ({ config, lib, ... }: {
    base = ./.;
    packages.#{name} = ./packages/#{name};
    main = "#{name}";
    exe = "#{name}";
    branch = "#{branch}";#{foldMap githubAttrs github}#{foldMap cachixAttrs cachix}
    depsFull = [ribosome];
    devGhc.compiler = "ghc902";
    overrides = { buildInputs, pkgs, ... }: {
      #{name} = buildInputs [pkgs.neovim pkgs.tmux pkgs.xterm];
    };
    hpack.packages = import ./ops/hpack.nix { inherit config lib; };
    hackage.versionFile = "ops/version.nix";
    ghcid.shellConfig.buildInputs = with config.pkgs; [pkgs.neovim pkgs.tmux];
    ghci = {
      preludePackage = "prelate";
      preludeModule = "Prelate";
      args = ["-fplugin=Polysemy.Plugin"];
    };
  });
}
|]