{-# LANGUAGE ConstraintKinds         #-}
{-# LANGUAGE FlexibleContexts        #-}
{-# LANGUAGE FlexibleInstances       #-}
{-# LANGUAGE FunctionalDependencies  #-}
{-# LANGUAGE UndecidableInstances    #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module HaskellCI.OptionsGrammar (
    OptionsGrammar (..),
    (C.^^^),
    metaActionHelp,
    ParsecPretty,
    Help, MetaVar, BashCompletionAction
)  where

import HaskellCI.Prelude

import qualified Distribution.Compat.Lens        as C
import qualified Distribution.FieldGrammar       as C
import qualified Distribution.Fields             as C
import qualified Distribution.Parsec             as C
import qualified Distribution.Pretty             as C
import qualified Distribution.Types.PackageName  as C
import qualified Distribution.Types.VersionRange as C
import qualified Options.Applicative             as O

import HaskellCI.Newtypes

-- | Help text for option.
type Help    = String

-- | Meta variable for option argument.
type MetaVar = String

-- | Bash completion action for option argument.
--   Example: @"file"@ or @"directory"@.
--
-- See <https://github.com/pcapriotti/optparse-applicative#actions-and-completers>
-- and <https://www.gnu.org/software/bash/manual/html_node/Programmable-Completion-Builtins.html>.
type BashCompletionAction = String

class
    ( C.FieldGrammar c p
    , c Range, c (Identity C.VersionRange)
    , c (C.List C.NoCommaFSep C.Token' String)
    , c (C.List C.FSep C.Token' String)
    , c (AlaSet C.NoCommaFSep C.Token' String)
    , c (AlaSet C.NoCommaFSep (Identity Version) Version)
    , c (C.List C.CommaVCat NoCommas String)
    , c (C.List C.NoCommaFSep (Identity C.PackageName) C.PackageName)
    , c (C.List C.FSep (Identity C.PackageName) C.PackageName)
    )
    => OptionsGrammar c p | p -> c
  where
    metaCompleterHelp :: MetaVar -> O.Completer -> Help -> p s a -> p s a
    metaCompleterHelp String
_ Completer
_ String
_ = p s a -> p s a
forall a. a -> a
id

    metahelp :: MetaVar -> Help -> p s a -> p s a
    metahelp String
_ String
_ = p s a -> p s a
forall a. a -> a
id

    help :: Help -> p s a -> p s a
    help String
_ = p s a -> p s a
forall a. a -> a
id

    -- we treat range fields specially in options
    rangeField :: C.FieldName -> C.ALens' s C.VersionRange -> C.VersionRange -> p s C.VersionRange
    rangeField FieldName
fn = FieldName
-> (VersionRange -> Range)
-> ALens' s VersionRange
-> VersionRange
-> p s VersionRange
forall b a s.
(c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> p s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
C.optionalFieldDefAla FieldName
fn VersionRange -> Range
Range

metaActionHelp :: OptionsGrammar c p => MetaVar -> BashCompletionAction -> Help -> p s a -> p s a
metaActionHelp :: forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> String -> p s a -> p s a
metaActionHelp String
m String
a = String -> Completer -> String -> p s a -> p s a
forall s a. String -> Completer -> String -> p s a -> p s a
forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> Completer -> String -> p s a -> p s a
metaCompleterHelp String
m (String -> Completer
O.bashCompleter String
a)

instance OptionsGrammar C.Parsec C.ParsecFieldGrammar

class    (C.Parsec a, C.Pretty a) => ParsecPretty a
instance (C.Parsec a, C.Pretty a) => ParsecPretty a