{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}

-- | Copyright: (c) 2021-2022 berberman
-- SPDX-License-Identifier: MIT
-- Maintainer: berberman <berberman@yandex.com>
-- Stability: experimental
-- Portability: portable
--
-- 'NixFetcher' is used to describe how to fetch package sources.
--
-- There are three types of fetchers overall:
--
-- 1. 'FetchGit' -- nix-prefetch fetchgit
-- 2. 'FetchGitHub' -- nix-prefetch fetchFromGitHub
-- 3. 'FetchUrl' -- nix-prefetch fetchurl
--
-- As you can see the type signature of 'prefetch':
-- a fetcher will be filled with the fetch result (hash) after the prefetch.
module NvFetcher.NixFetcher
  ( -- * Types
    NixFetcher (..),
    FetchStatus (..),
    FetchResult,

    -- * Rules
    prefetchRule,
    prefetch,

    -- * Functions
    gitHubFetcher,
    pypiFetcher,
    gitHubReleaseFetcher,
    gitFetcher,
    urlFetcher,
    openVsxFetcher,
    vscodeMarketplaceFetcher,
    tarballFetcher,
  )
where

import Control.Monad (void)
import Data.Coerce (coerce)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Development.Shake
import NeatInterpolation (trimming)
import NvFetcher.Types
import NvFetcher.Types.ShakeExtras
import Prettyprinter (pretty, (<+>))

--------------------------------------------------------------------------------

runFetcher :: NixFetcher Fresh -> Action Checksum
runFetcher :: NixFetcher 'Fresh -> Action Checksum
runFetcher = \case
  FetchGit {Bool
Maybe Text
Text
FetchResult 'Fresh
Version
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: FetchResult 'Fresh
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_furl :: Text
..} -> do
    (CmdTime Double
t, Stdout (ByteString -> Text
T.decodeUtf8 -> Text
out), CmdLine String
c) <-
      Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a. Action a -> Action a
quietly (Action (CmdTime, Stdout ByteString, CmdLine)
 -> Action (CmdTime, Stdout ByteString, CmdLine))
-> Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
        [CmdOption]
-> String
-> [String]
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall r.
(Partial, CmdResult r) =>
[CmdOption] -> String -> [String] -> Action r
command [Bool -> CmdOption
EchoStderr Bool
False] String
"nix-prefetch" ([String] -> Action (CmdTime, Stdout ByteString, CmdLine))
-> [String] -> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
          [String
"fetchgit"]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--url", Text -> String
T.unpack Text
_furl]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--rev", Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Version -> Text
coerce Version
_rev]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--fetchSubmodules" | Bool
_fetchSubmodules]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--deepClone" | Bool
_deepClone]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--leaveDotGit" | Bool
_leaveDotGit]
    String -> Action ()
putVerbose (String -> Action ()) -> String -> Action ()
forall a b. (a -> b) -> a -> b
$ String
"Finishing running " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
c String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", took " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Double -> String
forall a. Show a => a -> String
show Double
t String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"s"
    case (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
out of
      [Text
x] -> Checksum -> Action Checksum
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Checksum -> Action Checksum) -> Checksum -> Action Checksum
forall a b. (a -> b) -> a -> b
$ Text -> Checksum
coerce Text
x
      [Text]
_ -> String -> Action Checksum
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action Checksum) -> String -> Action Checksum
forall a b. (a -> b) -> a -> b
$ String
"Failed to parse output from nix-prefetch: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
out
  FetchGitHub {Bool
Maybe Text
Text
FetchResult 'Fresh
Version
_frepo :: forall (k :: FetchStatus). NixFetcher k -> Text
_fowner :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: FetchResult 'Fresh
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_frepo :: Text
_fowner :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
..} -> do
    (CmdTime Double
t, Stdout (ByteString -> Text
T.decodeUtf8 -> Text
out), CmdLine String
c) <-
      Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a. Action a -> Action a
quietly (Action (CmdTime, Stdout ByteString, CmdLine)
 -> Action (CmdTime, Stdout ByteString, CmdLine))
-> Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
        [CmdOption]
-> String
-> [String]
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall r.
(Partial, CmdResult r) =>
[CmdOption] -> String -> [String] -> Action r
command [Bool -> CmdOption
EchoStderr Bool
False] String
"nix-prefetch" ([String] -> Action (CmdTime, Stdout ByteString, CmdLine))
-> [String] -> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
          [String
"fetchFromGitHub"]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--owner", Text -> String
T.unpack Text
_fowner]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--repo", Text -> String
T.unpack Text
_frepo]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--rev", Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Version -> Text
coerce Version
_rev]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--fetchSubmodules" | Bool
_fetchSubmodules]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--deepClone" | Bool
_deepClone]
            [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
"--leaveDotGit" | Bool
_leaveDotGit]
    String -> Action ()
putVerbose (String -> Action ()) -> String -> Action ()
forall a b. (a -> b) -> a -> b
$ String
"Finishing running " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
c String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", took " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Double -> String
forall a. Show a => a -> String
show Double
t String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"s"
    case (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
out of
      [Text
x] -> Checksum -> Action Checksum
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Checksum -> Action Checksum) -> Checksum -> Action Checksum
forall a b. (a -> b) -> a -> b
$ Text -> Checksum
coerce Text
x
      [Text]
_ -> String -> Action Checksum
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action Checksum) -> String -> Action Checksum
forall a b. (a -> b) -> a -> b
$ String
"Failed to parse output from nix-prefetch: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
out
  FetchUrl {Maybe Text
Text
FetchResult 'Fresh
_sha256 :: FetchResult 'Fresh
_name :: Maybe Text
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} -> do
    (CmdTime Double
t, Stdout (ByteString -> Text
T.decodeUtf8 -> Text
out), CmdLine String
c) <-
      Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a. Action a -> Action a
quietly (Action (CmdTime, Stdout ByteString, CmdLine)
 -> Action (CmdTime, Stdout ByteString, CmdLine))
-> Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
        [CmdOption]
-> String
-> [String]
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall r.
(Partial, CmdResult r) =>
[CmdOption] -> String -> [String] -> Action r
command [Bool -> CmdOption
EchoStderr Bool
False] String
"nix-prefetch" [String
"fetchurl", String
"--url", Text -> String
T.unpack Text
_furl]
    String -> Action ()
putVerbose (String -> Action ()) -> String -> Action ()
forall a b. (a -> b) -> a -> b
$ String
"Finishing running " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
c String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", took " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Double -> String
forall a. Show a => a -> String
show Double
t String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"s"
    case (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
out of
      [Text
x] -> Checksum -> Action Checksum
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Checksum -> Action Checksum) -> Checksum -> Action Checksum
forall a b. (a -> b) -> a -> b
$ Text -> Checksum
coerce Text
x
      [Text]
_ -> String -> Action Checksum
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action Checksum) -> String -> Action Checksum
forall a b. (a -> b) -> a -> b
$ String
"Failed to parse output from nix-prefetch: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
out
  FetchTarball {Text
FetchResult 'Fresh
_sha256 :: FetchResult 'Fresh
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult k
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} -> do
    (CmdTime Double
t, Stdout (ByteString -> Text
T.decodeUtf8 -> Text
out), CmdLine String
c) <-
      Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a. Action a -> Action a
quietly (Action (CmdTime, Stdout ByteString, CmdLine)
 -> Action (CmdTime, Stdout ByteString, CmdLine))
-> Action (CmdTime, Stdout ByteString, CmdLine)
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall a b. (a -> b) -> a -> b
$
        [CmdOption]
-> String
-> [String]
-> Action (CmdTime, Stdout ByteString, CmdLine)
forall r.
(Partial, CmdResult r) =>
[CmdOption] -> String -> [String] -> Action r
command [Bool -> CmdOption
EchoStderr Bool
False] String
"nix-prefetch" [String
"fetchTarball", String
"--url", Text -> String
T.unpack Text
_furl]
    String -> Action ()
putVerbose (String -> Action ()) -> String -> Action ()
forall a b. (a -> b) -> a -> b
$ String
"Finishing running " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
c String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", took " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Double -> String
forall a. Show a => a -> String
show Double
t String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"s"
    case (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
out of
      [Text
x] -> Checksum -> Action Checksum
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Checksum -> Action Checksum) -> Checksum -> Action Checksum
forall a b. (a -> b) -> a -> b
$ Text -> Checksum
coerce Text
x
      [Text]
_ -> String -> Action Checksum
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action Checksum) -> String -> Action Checksum
forall a b. (a -> b) -> a -> b
$ String
"Failed to parse output from nix-prefetch: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
out

pypiUrl :: Text -> Version -> Text
pypiUrl :: Text -> Version -> Text
pypiUrl Text
pypi (Version -> Text
coerce -> Text
ver) =
  let h :: Text
h = Char -> Text -> Text
T.cons (Text -> Char
T.head Text
pypi) Text
""
   in [trimming|https://pypi.io/packages/source/$h/$pypi/$pypi-$ver.tar.gz|]

--------------------------------------------------------------------------------

-- | Rules of nix fetcher
prefetchRule :: Rules ()
prefetchRule :: Rules ()
prefetchRule = Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
-> Rules ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
 -> Rules ())
-> Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
-> Rules ()
forall a b. (a -> b) -> a -> b
$
  (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
-> Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
forall q a.
(RuleResult q ~ a, ShakeValue q, ShakeValue a, Partial) =>
(q -> Action a) -> Rules (q -> Action a)
addOracleCache ((NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
 -> Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched)))
-> (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
-> Rules (NixFetcher 'Fresh -> Action (NixFetcher 'Fetched))
forall a b. (a -> b) -> a -> b
$ \(NixFetcher 'Fresh
f :: NixFetcher Fresh) -> do
    String -> Action ()
putInfo (String -> Action ())
-> (Doc Any -> String) -> Doc Any -> Action ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Any -> String
forall a. Show a => a -> String
show (Doc Any -> Action ()) -> Doc Any -> Action ()
forall a b. (a -> b) -> a -> b
$ Doc Any
"#" Doc Any -> Doc Any -> Doc Any
forall ann. Doc ann -> Doc ann -> Doc ann
<+> NixFetcher 'Fresh -> Doc Any
forall a ann. Pretty a => a -> Doc ann
pretty NixFetcher 'Fresh
f
    Checksum
sha256 <- Action Checksum -> Action Checksum
forall a. Action a -> Action a
withRetry (Action Checksum -> Action Checksum)
-> Action Checksum -> Action Checksum
forall a b. (a -> b) -> a -> b
$ NixFetcher 'Fresh -> Action Checksum
runFetcher NixFetcher 'Fresh
f
    NixFetcher 'Fetched -> Action (NixFetcher 'Fetched)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NixFetcher 'Fetched -> Action (NixFetcher 'Fetched))
-> NixFetcher 'Fetched -> Action (NixFetcher 'Fetched)
forall a b. (a -> b) -> a -> b
$ NixFetcher 'Fresh
f {_sha256 :: FetchResult 'Fetched
_sha256 = FetchResult 'Fetched
Checksum
sha256}

-- | Run nix fetcher
prefetch :: NixFetcher Fresh -> Action (NixFetcher Fetched)
prefetch :: NixFetcher 'Fresh -> Action (NixFetcher 'Fetched)
prefetch = NixFetcher 'Fresh -> Action (NixFetcher 'Fetched)
forall q a.
(RuleResult q ~ a, ShakeValue q, ShakeValue a) =>
q -> Action a
askOracle

--------------------------------------------------------------------------------

-- | Create a fetcher from git url
gitFetcher :: Text -> PackageFetcher
gitFetcher :: Text -> PackageFetcher
gitFetcher Text
furl Version
rev = Text
-> Version
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> FetchResult 'Fresh
-> NixFetcher 'Fresh
forall (k :: FetchStatus).
Text
-> Version
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> FetchResult k
-> NixFetcher k
FetchGit Text
furl Version
rev Bool
False Bool
False Bool
False Maybe Text
forall a. Maybe a
Nothing ()

-- | Create a fetcher from github repo
gitHubFetcher ::
  -- | owner and repo
  (Text, Text) ->
  PackageFetcher
gitHubFetcher :: (Text, Text) -> PackageFetcher
gitHubFetcher (Text
owner, Text
repo) Version
rev = Text
-> Text
-> Version
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> FetchResult 'Fresh
-> NixFetcher 'Fresh
forall (k :: FetchStatus).
Text
-> Text
-> Version
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> FetchResult k
-> NixFetcher k
FetchGitHub Text
owner Text
repo Version
rev Bool
False Bool
False Bool
False Maybe Text
forall a. Maybe a
Nothing ()

-- | Create a fetcher from pypi
pypiFetcher :: Text -> PackageFetcher
pypiFetcher :: Text -> PackageFetcher
pypiFetcher Text
p Version
v = Text -> NixFetcher 'Fresh
urlFetcher (Text -> NixFetcher 'Fresh) -> Text -> NixFetcher 'Fresh
forall a b. (a -> b) -> a -> b
$ Text -> Version -> Text
pypiUrl Text
p Version
v

-- | Create a fetcher from github release
gitHubReleaseFetcher ::
  -- | owner and repo
  (Text, Text) ->
  -- | file name
  Text ->
  PackageFetcher
gitHubReleaseFetcher :: (Text, Text) -> Text -> PackageFetcher
gitHubReleaseFetcher (Text
owner, Text
repo) Text
fp (Version -> Text
coerce -> Text
ver) =
  Text -> NixFetcher 'Fresh
urlFetcher
    [trimming|https://github.com/$owner/$repo/releases/download/$ver/$fp|]

-- | Create a fetcher from url
urlFetcher :: Text -> NixFetcher Fresh
urlFetcher :: Text -> NixFetcher 'Fresh
urlFetcher Text
url = Text -> Maybe Text -> FetchResult 'Fresh -> NixFetcher 'Fresh
forall (k :: FetchStatus).
Text -> Maybe Text -> FetchResult k -> NixFetcher k
FetchUrl Text
url Maybe Text
forall a. Maybe a
Nothing ()

-- | Create a fetcher from openvsx
openVsxFetcher ::
  -- | publisher and extension name
  (Text, Text) ->
  PackageFetcher
openVsxFetcher :: (Text, Text) -> PackageFetcher
openVsxFetcher (Text
publisher, Text
extName) (Version -> Text
coerce -> Text
ver) =
  Text -> Maybe Text -> FetchResult 'Fresh -> NixFetcher 'Fresh
forall (k :: FetchStatus).
Text -> Maybe Text -> FetchResult k -> NixFetcher k
FetchUrl
    [trimming|https://open-vsx.org/api/$publisher/$extName/$ver/file/$publisher.$extName-$ver.vsix|]
    (Text -> Maybe Text
forall a. a -> Maybe a
Just [trimming|$extName-$ver.zip|])
    ()

-- | Create a fetcher from vscode marketplace
vscodeMarketplaceFetcher ::
  -- | publisher and extension name
  (Text, Text) ->
  PackageFetcher
vscodeMarketplaceFetcher :: (Text, Text) -> PackageFetcher
vscodeMarketplaceFetcher (Text
publisher, Text
extName) (Version -> Text
coerce -> Text
ver) =
  Text -> Maybe Text -> FetchResult 'Fresh -> NixFetcher 'Fresh
forall (k :: FetchStatus).
Text -> Maybe Text -> FetchResult k -> NixFetcher k
FetchUrl
    [trimming|https://$publisher.gallery.vsassets.io/_apis/public/gallery/publisher/$publisher/extension/$extName/$ver/assetbyname/Microsoft.VisualStudio.Services.VSIXPackage|]
    (Text -> Maybe Text
forall a. a -> Maybe a
Just [trimming|$extName-$ver.zip|])
    ()

-- | Create a fetcher from url, using fetchTarball
tarballFetcher :: Text -> NixFetcher Fresh
tarballFetcher :: Text -> NixFetcher 'Fresh
tarballFetcher Text
url = Text -> FetchResult 'Fresh -> NixFetcher 'Fresh
forall (k :: FetchStatus). Text -> FetchResult k -> NixFetcher k
FetchTarball Text
url ()