{- |
Copyright:  (c) 2015-2019 Aelve
            (c) 2019-2021 Kowainik
SPDX-License-Identifier: MPL-2.0
Maintainer: Kowainik <xrom.xkov@gmail.com>
-}

module ShortcutLinks
    ( Result(..)
    , Shortcut
    , allShortcuts
    , useShortcut
    , useShortcutFrom
    ) where

import Data.Text (Text)

import ShortcutLinks.All (Result (..), Shortcut, allShortcuts)
import ShortcutLinks.Utils (format)


{- | Use a shortcut from 'allShortcuts'.

This is the main function you should use.
-}
useShortcut
  :: Text                   -- ^ Shortcut name
  -> Maybe Text             -- ^ Option
  -> Text                   -- ^ Link text
  -> Result Text            -- ^ Resulting URL
useShortcut :: Text -> Maybe Text -> Text -> Result Text
useShortcut = [([Text], Maybe Text -> Text -> Result Text)]
-> Text -> Maybe Text -> Text -> Result Text
useShortcutFrom [([Text], Maybe Text -> Text -> Result Text)]
allShortcuts

{- | Use a shortcut from a list.

For instance, if you want to add @hk@ as a synonym for @hackage@, you'd
write:

@
useShortcutFrom ((["hk"], hackage) : allShortcuts)
@
-}
useShortcutFrom
  :: [([Text], Shortcut)]
  -> Text                   -- ^ Shortcut name
  -> Maybe Text             -- ^ Option
  -> Text                   -- ^ Link text
  -> Result Text            -- ^ Resulting URL
useShortcutFrom :: [([Text], Maybe Text -> Text -> Result Text)]
-> Text -> Maybe Text -> Text -> Result Text
useShortcutFrom [([Text], Maybe Text -> Text -> Result Text)]
shortcuts Text
name Maybe Text
option Text
link =
    case (([Text], Maybe Text -> Text -> Result Text) -> Bool)
-> [([Text], Maybe Text -> Text -> Result Text)]
-> [([Text], Maybe Text -> Text -> Result Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter ([Text], Maybe Text -> Text -> Result Text) -> Bool
givenShortcut [([Text], Maybe Text -> Text -> Result Text)]
shortcuts of
        []   -> String -> Result Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Text -> Text -> String
forall r. FormatType r => Text -> r
format Text
"there's no shortcut named '{}'" Text
name)
        [([Text], Maybe Text -> Text -> Result Text)
sh] -> ([Text], Maybe Text -> Text -> Result Text)
-> Maybe Text -> Text -> Result Text
forall a b. (a, b) -> b
snd ([Text], Maybe Text -> Text -> Result Text)
sh Maybe Text
option Text
link
        [([Text], Maybe Text -> Text -> Result Text)]
_    -> String -> Result Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Text -> Text -> String
forall r. FormatType r => Text -> r
format Text
"there's more than one shortcut named '{}'" Text
name)
  where
    givenShortcut :: ([Text], Shortcut) -> Bool
    givenShortcut :: ([Text], Maybe Text -> Text -> Result Text) -> Bool
givenShortcut ([Text]
names, Maybe Text -> Text -> Result Text
_) = Text
name Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
names