{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
module ShortcutLinks.All
( Result(..)
, Shortcut
, allShortcuts
, wikipedia
, tvtropes
, facebook
, vk
, googleplus
, telegram
, twitter
, juick
, google
, duckduckgo
, yandex
, baidu
, haskell
, hackage
, stackage
, cabal
, npm
, jam
, rubygems
, pypi
, metacpanPod
, metacpanRelease
, cargo
, pub
, hex
, cran
, swiprolog
, dub
, bpkg
, pear
, github
, gitlab
, bitbucket
, googleplay
, chocolatey
, brew
, debian
, aur
, mint
, fedora
, gentoo
, opensuse
, marmalade
, melpa
, elpa
, packagecontrol
, atomPackage
, atomTheme
, jedit
, vim
, operaExt
, operaTheme
, firefox
, chrome
, ghcExt
, rfc
, ecma
, cve
) where
import Control.Monad (unless, when)
import Data.Char (isAlphaNum, isDigit, isPunctuation, isSpace)
import Data.Maybe (fromMaybe, isNothing)
import Data.Text (Text)
import ShortcutLinks.Utils (format, formatSlash, orElse, replaceSpaces, stripPrefixCI, titleFirst,
tryStripPrefixCI)
import qualified Control.Monad.Fail as Fail
import qualified Data.Text as T
data Result a
= Failure String
| Warning [String] a
| Success a
deriving stock (Int -> Result a -> ShowS
[Result a] -> ShowS
Result a -> String
(Int -> Result a -> ShowS)
-> (Result a -> String) -> ([Result a] -> ShowS) -> Show (Result a)
forall a. Show a => Int -> Result a -> ShowS
forall a. Show a => [Result a] -> ShowS
forall a. Show a => Result a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result a] -> ShowS
$cshowList :: forall a. Show a => [Result a] -> ShowS
show :: Result a -> String
$cshow :: forall a. Show a => Result a -> String
showsPrec :: Int -> Result a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Result a -> ShowS
Show, a -> Result b -> Result a
(a -> b) -> Result a -> Result b
(forall a b. (a -> b) -> Result a -> Result b)
-> (forall a b. a -> Result b -> Result a) -> Functor Result
forall a b. a -> Result b -> Result a
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Result b -> Result a
$c<$ :: forall a b. a -> Result b -> Result a
fmap :: (a -> b) -> Result a -> Result b
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
Functor)
instance Applicative Result where
pure :: a -> Result a
pure :: a -> Result a
pure = a -> Result a
forall a. a -> Result a
Success
(<*>) :: Result (a -> b) -> Result a -> Result b
Failure String
x <*> :: Result (a -> b) -> Result a -> Result b
<*> Result a
_ = String -> Result b
forall a. String -> Result a
Failure String
x
Warning [String]
wf a -> b
f <*> Result a
s = case Result a
s of
Success a
a -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning [String]
wf (a -> b
f a
a)
Warning [String]
wa a
a -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning ([String]
wf [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
wa) (a -> b
f a
a)
Failure String
x -> String -> Result b
forall a. String -> Result a
Failure String
x
Success a -> b
f <*> Result a
a = a -> b
f (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Result a
a
instance Monad Result where
#if !(MIN_VERSION_base(4,13,0))
fail :: String -> Result a
fail = Fail.fail
#endif
return :: a -> Result a
return :: a -> Result a
return = a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(>>=) :: Result a -> (a -> Result b) -> Result b
Failure String
x >>= :: Result a -> (a -> Result b) -> Result b
>>= a -> Result b
_ = String -> Result b
forall a. String -> Result a
Failure String
x
Warning [String]
wa a
a >>= a -> Result b
f = case a -> Result b
f a
a of
Success b
b -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning [String]
wa b
b
Warning [String]
wb b
b -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning ([String]
wa [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
wb) b
b
Failure String
x -> String -> Result b
forall a. String -> Result a
Failure String
x
Success a
a >>= a -> Result b
f = a -> Result b
f a
a
instance Fail.MonadFail Result where
fail :: String -> Result a
fail :: String -> Result a
fail = String -> Result a
forall a. String -> Result a
Failure
warn :: String -> Result ()
warn :: String -> Result ()
warn String
s = [String] -> () -> Result ()
forall a. [String] -> a -> Result a
Warning [String
s] ()
type Shortcut = Maybe Text -> Text -> Result Text
allShortcuts :: [([Text], Shortcut)]
allShortcuts :: [([Text], Shortcut)]
allShortcuts =
let .= :: Text -> b -> ([Text], b)
(.=) Text
names b
func = (Text -> [Text]
T.words Text
names, b
func)
in
[
Text
"w wikipedia" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
wikipedia
, Text
"tvtropes" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
tvtropes
, Text
"fb facebook" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
facebook
, Text
"vk vkontakte" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
vk
, Text
"gp gplus googleplus" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
googleplus
, Text
"tg tme telegram" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
telegram
, Text
"t twitter" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
twitter
, Text
"juick" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
juick
, Text
"google" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
google
, Text
"ddg duckduckgo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
duckduckgo
, Text
"yandex" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
yandex
, Text
"baidu" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
baidu
, Text
"hackage hk" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
hackage
, Text
"stackage" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
stackage
, Text
"haskell hs" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
haskell
, Text
"cabal" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cabal
, Text
"npm" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
npm
, Text
"jam" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
jam
, Text
"gem" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
rubygems
, Text
"pypi" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pypi
, Text
"cpan" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
metacpanPod
, Text
"cpan-r" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
metacpanRelease
, Text
"cargo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cargo
, Text
"pub" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pub
, Text
"hex" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
hex
, Text
"cran" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cran
, Text
"swiprolog" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
swiprolog
, Text
"dub" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
dub
, Text
"bpkg" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
bpkg
, Text
"pear" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pear
, Text
"gh github" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
github
, Text
"gitlab" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
gitlab
, Text
"bitbucket" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
bitbucket
, Text
"gplay googleplay" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
googleplay
, Text
"chocolatey" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
chocolatey
, Text
"brew" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
brew
, Text
"debian" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
debian
, Text
"aur" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
aur
, Text
"mint" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
mint
, Text
"fedora" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
fedora
, Text
"gentoo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
gentoo
, Text
"opensuse" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
opensuse
, Text
"marmalade" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
marmalade
, Text
"melpa" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
melpa
, Text
"elpa" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
elpa
, Text
"sublimepc" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
packagecontrol
, Text
"atom" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
atomPackage
, Text
"atom-theme" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
atomTheme
, Text
"jedit" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
jedit
, Text
"vim" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
vim
, Text
"opera" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
operaExt
, Text
"opera-theme" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
operaTheme
, Text
"firefox" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
firefox
, Text
"chrome" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
chrome
, Text
"ghc-ext" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
ghcExt
, Text
"rfc" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
rfc
, Text
"ecma" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
ecma
, Text
"cve" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cve
]
facebook :: Shortcut
facebook :: Shortcut
facebook Maybe Text
_ Text
q
| (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://facebook.com/profile.php?id=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
| Bool
otherwise = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://facebook.com/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
vk :: Shortcut
vk :: Shortcut
vk Maybe Text
_ Text
q
| (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://vk.com/id" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
| Bool
otherwise = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://vk.com/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
googleplus :: Shortcut
googleplus :: Shortcut
googleplus Maybe Text
_ Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
url
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/explore/{}" Text
url (Text -> Text
T.tail Text
q)
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
q
| (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
q
| Bool
otherwise = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/+{}" Text
url ([Text] -> Text
T.concat (Text -> [Text]
T.words Text
q))
where
url :: Text
url = Text
"https://plus.google.com"
telegram :: Shortcut
telegram :: Shortcut
telegram Maybe Text
_ Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
url
| Just (Char
'@', Text
username) <- Text -> Maybe (Char, Text)
T.uncons Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
username
| Bool
otherwise = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
q
where
url :: Text
url :: Text
url = Text
"https://t.me"
twitter :: Shortcut
Maybe Text
_ Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
url
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/hashtag/{}" Text
url (Text -> Text
T.tail Text
q)
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'@' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url (Text -> Text
T.tail Text
q)
| Bool
otherwise = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
q
where url :: Text
url = Text
"https://twitter.com"
juick :: Shortcut
juick :: Shortcut
juick Maybe Text
_ Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
url
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'*' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/tag/{}" Text
url (Text -> Text
T.tail Text
q)
| Text -> Char
T.head Text
q Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'@' = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url (Text -> Text
T.tail Text
q)
| Bool
otherwise = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => r
formatSlash Text
url Text
q
where url :: Text
url = Text
"https://juick.com"
google :: Shortcut
google :: Shortcut
google Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$
Text
"https://google.com/search?nfpr=1&q=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces Char
'+' Text
q
duckduckgo :: Shortcut
duckduckgo :: Shortcut
duckduckgo Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://duckduckgo.com/?q=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces Char
'+' Text
q
yandex :: Shortcut
yandex :: Shortcut
yandex Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$
Text
"http://yandex.ru/search/?noreask=1&text=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces Char
'+' Text
q
baidu :: Shortcut
baidu :: Shortcut
baidu Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://baidu.com/s?nojc=1&wd=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces Char
'+' Text
q
haskell :: Shortcut
haskell :: Shortcut
haskell Maybe Text
_ Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://haskell.org/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces Char
'_' Text
q
hackage :: Shortcut
hackage :: Shortcut
hackage Maybe Text
_ Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
hkUrl
| Bool
otherwise = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/package/{}" Text
hkUrl (Char -> Text -> Text
replaceSpaces Char
'-' Text
q)
where
hkUrl :: Text
hkUrl :: Text
hkUrl = Text
"https://hackage.haskell.org"
stackage :: Shortcut
stackage :: Shortcut
stackage Maybe Text
ltsNightly Text
q
| Text -> Bool
T.null Text
q Bool -> Bool -> Bool
&& Maybe Text -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Text
ltsNightly = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
url
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/{}" Text
url Text
lts
| Bool
otherwise = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/{}/package/{}" Text
url Text
lts (Char -> Text -> Text
replaceSpaces Char
'-' Text
q)
where
url :: Text
url :: Text
url = Text
"https://stackage.org"
lts :: Text
lts :: Text
lts = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"lts" Maybe Text
ltsNightly
cabal :: Shortcut
cabal :: Shortcut
cabal Maybe Text
_ Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/{}" Text
url (Char -> Text -> Text
replaceSpaces Char
'-' Text
q)
where
url :: Text
url :: Text
url = Text
"https://haskell.org/cabal/users-guide"
npm :: Shortcut
npm :: Shortcut
npm Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://npmjs.com/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
jam :: Shortcut
jam :: Shortcut
jam Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://jamjs.org/packages/#/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
rubygems :: Shortcut
rubygems :: Shortcut
rubygems Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://rubygems.org/gems/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pypi :: Shortcut
pypi :: Shortcut
pypi Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://pypi.python.org/pypi/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
metacpanPod :: Shortcut
metacpanPod :: Shortcut
metacpanPod Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://metacpan.org/pod/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
metacpanRelease :: Shortcut
metacpanRelease :: Shortcut
metacpanRelease Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://metacpan.org/release/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
cargo :: Shortcut
cargo :: Shortcut
cargo Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://crates.io/crates/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pear :: Shortcut
pear :: Shortcut
pear Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://pear.php.net/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pub :: Shortcut
pub :: Shortcut
pub Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://pub.dartlang.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
cran :: Shortcut
cran :: Shortcut
cran Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://cran.r-project.org/web/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
hex :: Shortcut
hex :: Shortcut
hex Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://hex.pm/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
swiprolog :: Shortcut
swiprolog :: Shortcut
swiprolog Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://www.swi-prolog.org/pack/list?p=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
dub :: Shortcut
dub :: Shortcut
dub Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://code.dlang.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
bpkg :: Shortcut
bpkg :: Shortcut
bpkg Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://bpkg.io/pkg/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
github :: Shortcut
github :: Shortcut
github Maybe Text
mbOwner Text
q = case Maybe Text
mbOwner of
Maybe Text
Nothing -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://github.com/{}" (Text -> Text
stripAt Text
q)
Just Text
owner -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://github.com/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'@' then Text -> Text
T.tail Text
x else Text
x
bitbucket :: Shortcut
bitbucket :: Shortcut
bitbucket Maybe Text
mbOwner Text
q = case Maybe Text
mbOwner of
Maybe Text
Nothing -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://bitbucket.org/{}" (Text -> Text
stripAt Text
q)
Just Text
owner -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://bitbucket.org/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'@' then Text -> Text
T.tail Text
x else Text
x
gitlab :: Shortcut
gitlab :: Shortcut
gitlab Maybe Text
mbOwner Text
q = case Maybe Text
mbOwner of
Maybe Text
Nothing -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://gitlab.com/{}" (Text -> Text
stripAt Text
q)
Just Text
owner -> Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://gitlab.com/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'@' then Text -> Text
T.tail Text
x else Text
x
googleplay :: Shortcut
googleplay :: Shortcut
googleplay Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://play.google.com/store/apps/details?id=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
brew :: Shortcut
brew :: Shortcut
brew Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://braumeister.org/formula/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
chocolatey :: Shortcut
chocolatey :: Shortcut
chocolatey Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://chocolatey.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
debian :: Shortcut
debian :: Shortcut
debian Maybe Text
mbDist Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://packages.debian.org/{}/{}" Text
dist Text
q
where
dist :: Text
dist = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"stable" Maybe Text
mbDist
aur :: Shortcut
aur :: Shortcut
aur Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://aur.archlinux.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
gentoo :: Shortcut
gentoo :: Shortcut
gentoo Maybe Text
mbCat Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://packages.gentoo.org/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
pkg
where
pkg :: Text
pkg = case Maybe Text
mbCat of
Maybe Text
Nothing -> Text
q
Just Text
cat -> Text
cat Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
opensuse :: Shortcut
opensuse :: Shortcut
opensuse Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://software.opensuse.org/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
mint :: Shortcut
mint :: Shortcut
mint Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://community.linuxmint.com/software/view/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
fedora :: Shortcut
fedora :: Shortcut
fedora Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://admin.fedoraproject.org/pkgdb/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
marmalade :: Shortcut
marmalade :: Shortcut
marmalade Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://marmalade-repo.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
melpa :: Shortcut
melpa :: Shortcut
melpa Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://melpa.org/#/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
elpa :: Shortcut
elpa :: Shortcut
elpa Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://elpa.gnu.org/packages/{}.html" Text
q
packagecontrol :: Shortcut
packagecontrol :: Shortcut
packagecontrol Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://packagecontrol.io/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
atomPackage :: Shortcut
atomPackage :: Shortcut
atomPackage Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://atom.io/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
atomTheme :: Shortcut
atomTheme :: Shortcut
atomTheme Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://atom.io/themes/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
jedit :: Shortcut
jedit :: Shortcut
jedit Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://plugins.jedit.org/plugins/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
vim :: Shortcut
vim :: Shortcut
vim Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"http://www.vim.org/scripts/script.php?script_id=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
operaExt :: Shortcut
operaExt :: Shortcut
operaExt Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://addons.opera.com/extensions/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
operaTheme :: Shortcut
operaTheme :: Shortcut
operaTheme Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://addons.opera.com/themes/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
firefox :: Shortcut
firefox :: Shortcut
firefox Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://addons.mozilla.org/firefox/addon/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
chrome :: Shortcut
chrome :: Shortcut
chrome Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://chrome.google.com/webstore/detail/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
ghcExt :: Shortcut
ghcExt :: Shortcut
ghcExt Maybe Text
_ Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ Text
"https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#extension-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
rfc :: Shortcut
rfc :: Shortcut
rfc Maybe Text
_ Text
x = do
let n :: Text
n = (Char -> Bool) -> Text -> Text
T.dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isAlphaNum) (Text -> Text -> Text
tryStripPrefixCI Text
"rfc" Text
x)
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
n) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"non-digits in RFC number"
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Bool
T.null Text
n) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"no RFC number"
let n' :: Text
n' = (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0') Text
n Text -> Text -> Text
forall a. (Eq a, Monoid a) => a -> a -> a
`orElse` Text
"0"
Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
"https://tools.ietf.org/html/rfc" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n')
ecma :: Shortcut
ecma :: Shortcut
ecma Maybe Text
_ Text
q = do
let dropSeparators :: Text -> Text
dropSeparators = (Char -> Bool) -> Text -> Text
T.dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isAlphaNum)
let (Text -> Text
dropSeparators -> Text
mbNum, Bool
isTR) = case Text -> Text -> Maybe Text
stripPrefixCI Text
"tr" Text
q of
Maybe Text
Nothing -> (Text -> Text -> Text
tryStripPrefixCI Text
"ecma" Text
q, Bool
False)
Just Text
q' -> (Text
q', Bool
True)
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
mbNum) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"non-digits in ECMA standard number"
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Bool
T.null Text
mbNum) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"no ECMA standard number"
let num :: Text
num = Int -> Char -> Text -> Text
T.justifyRight Int
3 Char
'0' Text
mbNum
url :: Text
url = Text
"http://ecma-international.org/publications" :: Text
Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$ if Bool
isTR
then Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/techreports/E-TR-{}.htm" Text
url Text
num
else Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"{}/standards/Ecma-{}.htm" Text
url Text
num
cve :: Shortcut
cve :: Shortcut
cve Maybe Text
_ Text
x = do
let n :: Text
n = (Char -> Bool) -> Text -> Text
T.dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isAlphaNum) (Text -> Text -> Text
tryStripPrefixCI Text
"cve" Text
x)
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Int
T.length Text
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
9) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"CVE-ID is too short"
let isValid :: Bool
isValid = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [
Text -> Int
T.length Text
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
9,
(Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit (Int -> Text -> Text
T.take Int
4 Text
n),
Text -> Int -> Char
T.index Text
n Int
4 Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-',
(Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit (Int -> Text -> Text
T.drop Int
5 Text
n) ]
Bool -> Result () -> Result ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
isValid (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn String
"CVE-ID doesn't follow the <year>-<digits> format"
Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
"http://cve.mitre.org/cgi-bin/cvename.cgi?name=CVE-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n)
wikipedia :: Shortcut
wikipedia :: Shortcut
wikipedia (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"en" -> Text
lang) Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$
Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"https://{}.wikipedia.org/wiki/{}" Text
lang Text
replacedQ
where
replacedQ :: Text
replacedQ :: Text
replacedQ = Text -> Text
titleFirst (Char -> Text -> Text
replaceSpaces Char
'_' Text
q)
tvtropes :: Shortcut
tvtropes :: Shortcut
tvtropes Maybe Text
mbCat Text
q = Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Result Text) -> Text -> Result Text
forall a b. (a -> b) -> a -> b
$
Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format Text
"http://tvtropes.org/pmwiki/pmwiki.php/{}/{}" Text
cat (Text -> Text
camel Text
q)
where
isSep :: Char -> Bool
isSep Char
c = (Char -> Bool
isSpace Char
c Bool -> Bool -> Bool
|| Char -> Bool
isPunctuation Char
c) Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\''
camel :: Text -> Text
camel = [Text] -> Text
T.concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
titleFirst (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.filter Char -> Bool
isAlphaNum) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
isSep
cat :: Text
cat = Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"Main" Text -> Text
camel Maybe Text
mbCat