{-# 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.Semigroup ((<>))
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 x :: String
x <*> :: Result (a -> b) -> Result a -> Result b
<*> _ = String -> Result b
forall a. String -> Result a
Failure String
x
Warning wf :: [String]
wf f :: a -> b
f <*> s :: Result a
s = case Result a
s of
Success a :: a
a -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning [String]
wf (a -> b
f a
a)
Warning wa :: [String]
wa a :: 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 x :: String
x -> String -> Result b
forall a. String -> Result a
Failure String
x
Success f :: a -> b
f <*> a :: 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 x :: String
x >>= :: Result a -> (a -> Result b) -> Result b
>>= _ = String -> Result b
forall a. String -> Result a
Failure String
x
Warning wa :: [String]
wa a :: a
a >>= f :: a -> Result b
f = case a -> Result b
f a
a of
Success b :: b
b -> [String] -> b -> Result b
forall a. [String] -> a -> Result a
Warning [String]
wa b
b
Warning wb :: [String]
wb b :: 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 x :: String
x -> String -> Result b
forall a. String -> Result a
Failure String
x
Success a :: a
a >>= f :: 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 s :: 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)
(.=) names :: Text
names func :: b
func = (Text -> [Text]
T.words Text
names, b
func)
in
[
"w wikipedia" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
wikipedia
, "tvtropes" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
tvtropes
, "fb facebook" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
facebook
, "vk vkontakte" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
vk
, "gp gplus googleplus" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
googleplus
, "tg tme telegram" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
telegram
, "t twitter" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
twitter
, "juick" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
juick
, "google" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
google
, "ddg duckduckgo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
duckduckgo
, "yandex" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
yandex
, "baidu" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
baidu
, "hackage hk" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
hackage
, "stackage" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
stackage
, "haskell hs" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
haskell
, "cabal" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cabal
, "npm" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
npm
, "jam" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
jam
, "gem" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
rubygems
, "pypi" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pypi
, "cpan" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
metacpanPod
, "cpan-r" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
metacpanRelease
, "cargo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cargo
, "pub" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pub
, "hex" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
hex
, "cran" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cran
, "swiprolog" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
swiprolog
, "dub" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
dub
, "bpkg" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
bpkg
, "pear" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
pear
, "gh github" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
github
, "gitlab" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
gitlab
, "bitbucket" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
bitbucket
, "gplay googleplay" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
googleplay
, "chocolatey" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
chocolatey
, "brew" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
brew
, "debian" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
debian
, "aur" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
aur
, "mint" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
mint
, "fedora" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
fedora
, "gentoo" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
gentoo
, "opensuse" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
opensuse
, "marmalade" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
marmalade
, "melpa" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
melpa
, "elpa" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
elpa
, "sublimepc" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
packagecontrol
, "atom" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
atomPackage
, "atom-theme" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
atomTheme
, "jedit" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
jedit
, "vim" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
vim
, "opera" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
operaExt
, "opera-theme" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
operaTheme
, "firefox" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
firefox
, "chrome" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
chrome
, "ghc-ext" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
ghcExt
, "rfc" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
rfc
, "ecma" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
ecma
, "cve" Text -> Shortcut -> ([Text], Shortcut)
forall b. Text -> b -> ([Text], b)
.= Shortcut
cve
]
facebook :: Shortcut
facebook :: Shortcut
facebook _ q :: 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
$ "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
$ "https://facebook.com/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
vk :: Shortcut
vk :: Shortcut
vk _ q :: 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
$ "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
$ "https://vk.com/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
googleplus :: Shortcut
googleplus :: Shortcut
googleplus _ q :: 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
== '#' = 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 "{}/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
== '+' = 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
url ([Text] -> Text
T.concat (Text -> [Text]
T.words Text
q))
where
url :: Text
url = "https://plus.google.com"
telegram :: Shortcut
telegram :: Shortcut
telegram _ q :: Text
q
| Text -> Bool
T.null Text
q = Text -> Result Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
url
| Just ('@', username :: 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 = "https://t.me"
twitter :: Shortcut
_ q :: 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
== '#' = 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 "{}/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
== '@' = 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 = "https://twitter.com"
juick :: Shortcut
juick :: Shortcut
juick _ q :: 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
== '*' = 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 "{}/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
== '@' = 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 = "https://juick.com"
google :: Shortcut
google :: Shortcut
google _ q :: 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
$
"https://google.com/search?nfpr=1&q=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces '+' Text
q
duckduckgo :: Shortcut
duckduckgo :: Shortcut
duckduckgo _ q :: 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
$ "https://duckduckgo.com/?q=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces '+' Text
q
yandex :: Shortcut
yandex :: Shortcut
yandex _ q :: 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
$
"http://yandex.ru/search/?noreask=1&text=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces '+' Text
q
baidu :: Shortcut
baidu :: Shortcut
baidu _ q :: 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
$ "http://baidu.com/s?nojc=1&wd=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces '+' Text
q
haskell :: Shortcut
haskell :: Shortcut
haskell _ q :: 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
$ "https://haskell.org/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
replaceSpaces '_' Text
q
hackage :: Shortcut
hackage :: Shortcut
hackage _ q :: 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 "{}/package/{}" Text
hkUrl (Char -> Text -> Text
replaceSpaces '-' Text
q)
where
hkUrl :: Text
hkUrl :: Text
hkUrl = "https://hackage.haskell.org"
stackage :: Shortcut
stackage :: Shortcut
stackage ltsNightly :: Maybe Text
ltsNightly q :: 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
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 "{}/{}/package/{}" Text
url Text
lts (Char -> Text -> Text
replaceSpaces '-' Text
q)
where
url :: Text
url :: Text
url = "https://stackage.org"
lts :: Text
lts :: Text
lts = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe "lts" Maybe Text
ltsNightly
cabal :: Shortcut
cabal :: Shortcut
cabal _ q :: 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
url (Char -> Text -> Text
replaceSpaces '-' Text
q)
where
url :: Text
url :: Text
url = "https://haskell.org/cabal/users-guide"
npm :: Shortcut
npm :: Shortcut
npm _ q :: 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
$ "https://npmjs.com/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
jam :: Shortcut
jam :: Shortcut
jam _ q :: 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
$ "http://jamjs.org/packages/#/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
rubygems :: Shortcut
rubygems :: Shortcut
rubygems _ q :: 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
$ "https://rubygems.org/gems/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pypi :: Shortcut
pypi :: Shortcut
pypi _ q :: 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
$ "https://pypi.python.org/pypi/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
metacpanPod :: Shortcut
metacpanPod :: Shortcut
metacpanPod _ q :: 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
$ "https://metacpan.org/pod/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
metacpanRelease :: Shortcut
metacpanRelease :: Shortcut
metacpanRelease _ q :: 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
$ "https://metacpan.org/release/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
cargo :: Shortcut
cargo :: Shortcut
cargo _ q :: 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
$ "https://crates.io/crates/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pear :: Shortcut
pear :: Shortcut
pear _ q :: 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
$ "http://pear.php.net/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
pub :: Shortcut
pub :: Shortcut
pub _ q :: 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
$ "https://pub.dartlang.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
cran :: Shortcut
cran :: Shortcut
cran _ q :: 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
$ "http://cran.r-project.org/web/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
hex :: Shortcut
hex :: Shortcut
hex _ q :: 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
$ "https://hex.pm/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
swiprolog :: Shortcut
swiprolog :: Shortcut
swiprolog _ q :: 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
$ "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 _ q :: 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
$ "http://code.dlang.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
bpkg :: Shortcut
bpkg :: Shortcut
bpkg _ q :: 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
$ "http://bpkg.io/pkg/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
github :: Shortcut
github :: Shortcut
github mbOwner :: Maybe Text
mbOwner q :: Text
q = case Maybe Text
mbOwner of
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 "https://github.com/{}" (Text -> Text
stripAt Text
q)
Just owner :: 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 "https://github.com/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt x :: Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '@' then Text -> Text
T.tail Text
x else Text
x
bitbucket :: Shortcut
bitbucket :: Shortcut
bitbucket mbOwner :: Maybe Text
mbOwner q :: Text
q = case Maybe Text
mbOwner of
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 "https://bitbucket.org/{}" (Text -> Text
stripAt Text
q)
Just owner :: 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 "https://bitbucket.org/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt x :: Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '@' then Text -> Text
T.tail Text
x else Text
x
gitlab :: Shortcut
gitlab :: Shortcut
gitlab mbOwner :: Maybe Text
mbOwner q :: Text
q = case Maybe Text
mbOwner of
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 "https://gitlab.com/{}" (Text -> Text
stripAt Text
q)
Just owner :: 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 "https://gitlab.com/{}/{}" (Text -> Text
stripAt Text
owner) Text
q
where
stripAt :: Text -> Text
stripAt x :: Text
x = if Text -> Char
T.head Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '@' then Text -> Text
T.tail Text
x else Text
x
googleplay :: Shortcut
googleplay :: Shortcut
googleplay _ q :: 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
$ "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 _ q :: 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
$ "http://braumeister.org/formula/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
chocolatey :: Shortcut
chocolatey :: Shortcut
chocolatey _ q :: 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
$ "https://chocolatey.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
debian :: Shortcut
debian :: Shortcut
debian mbDist :: Maybe Text
mbDist q :: 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 "https://packages.debian.org/{}/{}" Text
dist Text
q
where
dist :: Text
dist = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe "stable" Maybe Text
mbDist
aur :: Shortcut
aur :: Shortcut
aur _ q :: 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
$ "https://aur.archlinux.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
gentoo :: Shortcut
gentoo :: Shortcut
gentoo mbCat :: Maybe Text
mbCat q :: 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
$ "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
Nothing -> Text
q
Just cat :: Text
cat -> Text
cat Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
opensuse :: Shortcut
opensuse :: Shortcut
opensuse _ q :: 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
$ "http://software.opensuse.org/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
mint :: Shortcut
mint :: Shortcut
mint _ q :: 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
$ "http://community.linuxmint.com/software/view/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
fedora :: Shortcut
fedora :: Shortcut
fedora _ q :: 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
$ "https://admin.fedoraproject.org/pkgdb/package/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
marmalade :: Shortcut
marmalade :: Shortcut
marmalade _ q :: 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
$ "https://marmalade-repo.org/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
melpa :: Shortcut
melpa :: Shortcut
melpa _ q :: 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
$ "http://melpa.org/#/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
elpa :: Shortcut
elpa :: Shortcut
elpa _ q :: 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 "https://elpa.gnu.org/packages/{}.html" Text
q
packagecontrol :: Shortcut
packagecontrol :: Shortcut
packagecontrol _ q :: 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
$ "https://packagecontrol.io/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
atomPackage :: Shortcut
atomPackage :: Shortcut
atomPackage _ q :: 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
$ "https://atom.io/packages/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
atomTheme :: Shortcut
atomTheme :: Shortcut
atomTheme _ q :: 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
$ "https://atom.io/themes/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
jedit :: Shortcut
jedit :: Shortcut
jedit _ q :: 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
$ "http://plugins.jedit.org/plugins/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
vim :: Shortcut
vim :: Shortcut
vim _ q :: 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
$ "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 _ q :: 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
$ "https://addons.opera.com/extensions/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
operaTheme :: Shortcut
operaTheme :: Shortcut
operaTheme _ q :: 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
$ "https://addons.opera.com/themes/details/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
firefox :: Shortcut
firefox :: Shortcut
firefox _ q :: 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
$ "https://addons.mozilla.org/firefox/addon/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
chrome :: Shortcut
chrome :: Shortcut
chrome _ q :: 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
$ "https://chrome.google.com/webstore/detail/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
q
ghcExt :: Shortcut
ghcExt :: Shortcut
ghcExt _ q :: 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
$ "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 _ x :: 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 "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 "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 "no RFC number"
let n' :: Text
n' = (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '0') Text
n Text -> Text -> Text
forall a. (Eq a, Monoid a) => a -> a -> a
`orElse` "0"
Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return ("https://tools.ietf.org/html/rfc" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n')
ecma :: Shortcut
ecma :: Shortcut
ecma _ q :: 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, isTR :: Bool
isTR) = case Text -> Text -> Maybe Text
stripPrefixCI "tr" Text
q of
Nothing -> (Text -> Text -> Text
tryStripPrefixCI "ecma" Text
q, Bool
False)
Just q' :: 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 "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 "no ECMA standard number"
let num :: Text
num = Int -> Char -> Text -> Text
T.justifyRight 3 '0' Text
mbNum
url :: Text
url = "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 "{}/techreports/E-TR-{}.htm" Text
url Text
num
else Text -> Text -> Text -> Text
forall r. FormatType r => Text -> r
format "{}/standards/Ecma-{}.htm" Text
url Text
num
cve :: Shortcut
cve :: Shortcut
cve _ x :: 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 "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
>= 9) (Result () -> Result ()) -> Result () -> Result ()
forall a b. (a -> b) -> a -> b
$
String -> Result ()
warn "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
>= 9,
(Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit (Int -> Text -> Text
T.take 4 Text
n),
Text -> Int -> Char
T.index Text
n 4 Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '-',
(Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit (Int -> Text -> Text
T.drop 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 "CVE-ID doesn't follow the <year>-<digits> format"
Text -> Result Text
forall (m :: * -> *) a. Monad m => a -> m a
return ("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 "en" -> Text
lang) q :: 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 "https://{}.wikipedia.org/wiki/{}" Text
lang Text
replacedQ
where
replacedQ :: Text
replacedQ :: Text
replacedQ = Text -> Text
titleFirst (Char -> Text -> Text
replaceSpaces '_' Text
q)
tvtropes :: Shortcut
tvtropes :: Shortcut
tvtropes mbCat :: Maybe Text
mbCat q :: 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 "http://tvtropes.org/pmwiki/pmwiki.php/{}/{}" Text
cat (Text -> Text
camel Text
q)
where
isSep :: Char -> Bool
isSep c :: 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
/= '\''
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 "Main" Text -> Text
camel Maybe Text
mbCat