Use http-client-openssl for internal downloader
This commit is contained in:
@@ -1,8 +1,12 @@
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveLift #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
@@ -13,8 +17,10 @@ module GHCup.Utils.Prelude where
|
||||
import Control.Applicative
|
||||
import Control.Exception.Safe
|
||||
import Control.Monad
|
||||
import Control.Monad.Base
|
||||
import Control.Monad.IO.Class
|
||||
import Control.Monad.Trans.Class ( lift )
|
||||
import Control.Monad.Trans.Control
|
||||
import Data.Bifunctor
|
||||
import Data.ByteString ( ByteString )
|
||||
import Data.String
|
||||
@@ -264,3 +270,40 @@ decUTF8Safe = E.decodeUtf8With E.lenientDecode
|
||||
|
||||
decUTF8Safe' :: L.ByteString -> Text
|
||||
decUTF8Safe' = TL.toStrict . TLE.decodeUtf8With E.lenientDecode
|
||||
|
||||
|
||||
instance MonadBaseControl b m => MonadBaseControl b (Excepts e m) where
|
||||
type StM (Excepts e m) a = ComposeSt (Excepts e) m a
|
||||
liftBaseWith = defaultLiftBaseWith
|
||||
restoreM = defaultRestoreM
|
||||
{-# INLINABLE liftBaseWith #-}
|
||||
{-# INLINABLE restoreM #-}
|
||||
|
||||
instance MonadTransControl (Excepts e) where
|
||||
type StT (Excepts e) a = VEither e a
|
||||
liftWith f = veitherMToExcepts <$> liftM return $ f $ runE
|
||||
restoreT = veitherMToExcepts
|
||||
{-# INLINABLE liftWith #-}
|
||||
{-# INLINABLE restoreT #-}
|
||||
|
||||
instance MonadBase b m => MonadBase b (Excepts e m) where
|
||||
liftBase = liftBaseDefault
|
||||
{-# INLINABLE liftBase #-}
|
||||
|
||||
instance MonadBaseControl (VEither e) (VEither e) where
|
||||
type StM (VEither e) a = a
|
||||
liftBaseWith f = f id
|
||||
restoreM = return
|
||||
{-# INLINABLE liftBaseWith #-}
|
||||
{-# INLINABLE restoreM #-}
|
||||
|
||||
instance MonadBase (VEither e) (VEither e) where
|
||||
liftBase = id
|
||||
{-# INLINABLE liftBase #-}
|
||||
|
||||
|
||||
veitherMToExcepts :: Monad m => m (VEither es a) -> Excepts es m a
|
||||
veitherMToExcepts ma = do
|
||||
ve <- lift ma
|
||||
veitherToExcepts ve
|
||||
|
||||
|
||||
Reference in New Issue
Block a user