{-# LANGUAGE DeriveGeneric        #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE StandaloneDeriving   #-}
{-# LANGUAGE UndecidableInstances #-}
module Cabal.Config (
    
    Config (..),
    Repo (..),
    RepoName,
    
    readConfig,
    findConfig,
    parseConfig,
    resolveConfig,
    
    cfgRepoIndex,
    hackageHaskellOrg,
    ) where
import Control.DeepSeq          (NFData (..))
import Control.Exception        (throwIO)
import Data.ByteString          (ByteString)
import Data.Function            ((&))
import Data.Functor.Identity    (Identity (..))
import Data.List                (foldl')
import Data.List.NonEmpty       (NonEmpty)
import Data.Map                 (Map)
import Data.Maybe               (fromMaybe)
import Distribution.Compat.Lens (LensLike', over)
import GHC.Generics             (Generic)
import Network.URI              (URI)
import System.Directory         (getAppUserDataDirectory)
import System.Environment       (lookupEnv)
import System.FilePath          ((</>))
import qualified Data.ByteString                    as BS
import qualified Data.Map.Strict                    as M
import qualified Distribution.CabalSpecVersion      as C
import qualified Distribution.FieldGrammar          as C
import qualified Distribution.Fields                as C
import qualified Distribution.Parsec                as C
import qualified Distribution.Simple.Utils          as C
import Cabal.Internal.Newtypes
import Cabal.Parse
infixl 1 <&>
(<&>) :: Functor f => f a -> (a -> b) -> f b
<&> :: f a -> (a -> b) -> f b
(<&>) = ((a -> b) -> f a -> f b) -> f a -> (a -> b) -> f b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
readConfig :: IO (Config Identity)
readConfig :: IO (Config Identity)
readConfig = do
    FilePath
fp <- IO FilePath
findConfig
    ByteString
bs <- FilePath -> IO ByteString
BS.readFile FilePath
fp
    (ParseError NonEmpty -> IO (Config Identity))
-> (Config Maybe -> IO (Config Identity))
-> Either (ParseError NonEmpty) (Config Maybe)
-> IO (Config Identity)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseError NonEmpty -> IO (Config Identity)
forall e a. Exception e => e -> IO a
throwIO Config Maybe -> IO (Config Identity)
resolveConfig (FilePath
-> ByteString -> Either (ParseError NonEmpty) (Config Maybe)
parseConfig FilePath
fp ByteString
bs)
findConfig :: IO FilePath
findConfig :: IO FilePath
findConfig = do
    Maybe FilePath
env <- FilePath -> IO (Maybe FilePath)
lookupEnv FilePath
"CABAL_CONFIG"
    case Maybe FilePath
env of
        Just FilePath
p -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
p
        Maybe FilePath
Nothing -> do
            FilePath
c <- FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"cabal"
            FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
c FilePath -> FilePath -> FilePath
</> FilePath
"config")
data Config f = Config
    { Config f -> Map FilePath Repo
cfgRepositories    :: Map RepoName Repo
    , Config f -> f FilePath
cfgRemoteRepoCache :: f FilePath
    , Config f -> f FilePath
cfgInstallDir      :: f FilePath
    , Config f -> f FilePath
cfgStoreDir        :: f FilePath
    }
  deriving ((forall x. Config f -> Rep (Config f) x)
-> (forall x. Rep (Config f) x -> Config f) -> Generic (Config f)
forall x. Rep (Config f) x -> Config f
forall x. Config f -> Rep (Config f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (Config f) x -> Config f
forall (f :: * -> *) x. Config f -> Rep (Config f) x
$cto :: forall (f :: * -> *) x. Rep (Config f) x -> Config f
$cfrom :: forall (f :: * -> *) x. Config f -> Rep (Config f) x
Generic)
deriving instance Show (f FilePath) => Show (Config f)
instance NFData (f FilePath) => NFData (Config f)
data Repo = Repo
    { Repo -> URI
repoURL    :: URI
    , Repo -> Bool
repoSecure :: Bool 
    }
  deriving (Int -> Repo -> FilePath -> FilePath
[Repo] -> FilePath -> FilePath
Repo -> FilePath
(Int -> Repo -> FilePath -> FilePath)
-> (Repo -> FilePath)
-> ([Repo] -> FilePath -> FilePath)
-> Show Repo
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [Repo] -> FilePath -> FilePath
$cshowList :: [Repo] -> FilePath -> FilePath
show :: Repo -> FilePath
$cshow :: Repo -> FilePath
showsPrec :: Int -> Repo -> FilePath -> FilePath
$cshowsPrec :: Int -> Repo -> FilePath -> FilePath
Show, (forall x. Repo -> Rep Repo x)
-> (forall x. Rep Repo x -> Repo) -> Generic Repo
forall x. Rep Repo x -> Repo
forall x. Repo -> Rep Repo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Repo x -> Repo
$cfrom :: forall x. Repo -> Rep Repo x
Generic)
type RepoName = String
instance NFData Repo
cfgRepoIndex
    :: Config Identity
    -> RepoName
    -> Maybe FilePath
cfgRepoIndex :: Config Identity -> FilePath -> Maybe FilePath
cfgRepoIndex Config Identity
cfg FilePath
repo
    | FilePath
repo FilePath -> Map FilePath Repo -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`M.member` Config Identity -> Map FilePath Repo
forall (f :: * -> *). Config f -> Map FilePath Repo
cfgRepositories Config Identity
cfg =
        FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Identity FilePath -> FilePath
forall a. Identity a -> a
runIdentity (Config Identity -> Identity FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgRemoteRepoCache Config Identity
cfg) FilePath -> FilePath -> FilePath
</> FilePath
repo FilePath -> FilePath -> FilePath
</> FilePath
"01-index.tar")
    | Bool
otherwise = Maybe FilePath
forall a. Maybe a
Nothing
hackageHaskellOrg :: RepoName
hackageHaskellOrg :: FilePath
hackageHaskellOrg = FilePath
"hackage.haskell.org"
parseConfig :: FilePath -> ByteString -> Either (ParseError NonEmpty) (Config Maybe)
parseConfig :: FilePath
-> ByteString -> Either (ParseError NonEmpty) (Config Maybe)
parseConfig = ([Field Position] -> ParseResult (Config Maybe))
-> FilePath
-> ByteString
-> Either (ParseError NonEmpty) (Config Maybe)
forall a.
([Field Position] -> ParseResult a)
-> FilePath -> ByteString -> Either (ParseError NonEmpty) a
parseWith (([Field Position] -> ParseResult (Config Maybe))
 -> FilePath
 -> ByteString
 -> Either (ParseError NonEmpty) (Config Maybe))
-> ([Field Position] -> ParseResult (Config Maybe))
-> FilePath
-> ByteString
-> Either (ParseError NonEmpty) (Config Maybe)
forall a b. (a -> b) -> a -> b
$ \[Field Position]
fields0 -> do
    let (Fields Position
fields1, [[Section Position]]
sections) = [Field Position] -> (Fields Position, [[Section Position]])
forall ann. [Field ann] -> (Fields ann, [[Section ann]])
C.partitionFields [Field Position]
fields0
    let fields2 :: Fields Position
fields2 = (ByteString -> [NamelessField Position] -> Bool)
-> Fields Position -> Fields Position
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey (\ByteString
k [NamelessField Position]
_ -> ByteString
k ByteString -> [ByteString] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ByteString]
knownFields) Fields Position
fields1
    Fields Position
-> [[Section Position]] -> ParseResult (Config Maybe)
forall (t :: * -> *).
Foldable t =>
Fields Position
-> t [Section Position] -> ParseResult (Config Maybe)
parse Fields Position
fields2 [[Section Position]]
sections
  where
    knownFields :: [ByteString]
knownFields = ParsecFieldGrammar (Config Maybe) (Config Maybe) -> [ByteString]
forall s a. ParsecFieldGrammar s a -> [ByteString]
C.fieldGrammarKnownFieldList ParsecFieldGrammar (Config Maybe) (Config Maybe)
grammar
    parse :: Fields Position
-> t [Section Position] -> ParseResult (Config Maybe)
parse Fields Position
fields t [Section Position]
sections = do
        Config Maybe
cfg <- CabalSpecVersion
-> Fields Position
-> ParsecFieldGrammar (Config Maybe) (Config Maybe)
-> ParseResult (Config Maybe)
forall s a.
CabalSpecVersion
-> Fields Position -> ParsecFieldGrammar s a -> ParseResult a
C.parseFieldGrammar CabalSpecVersion
C.cabalSpecLatest Fields Position
fields ParsecFieldGrammar (Config Maybe) (Config Maybe)
grammar
        (Config Maybe -> (Config Maybe -> Config Maybe) -> Config Maybe)
-> Config Maybe -> [Config Maybe -> Config Maybe] -> Config Maybe
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Config Maybe -> (Config Maybe -> Config Maybe) -> Config Maybe
forall a b. a -> (a -> b) -> b
(&) Config Maybe
cfg ([Config Maybe -> Config Maybe] -> Config Maybe)
-> ParseResult [Config Maybe -> Config Maybe]
-> ParseResult (Config Maybe)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Section Position -> ParseResult (Config Maybe -> Config Maybe))
-> [Section Position] -> ParseResult [Config Maybe -> Config Maybe]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Section Position -> ParseResult (Config Maybe -> Config Maybe)
forall (f :: * -> *).
Section Position -> ParseResult (Config f -> Config f)
parseSec (t [Section Position] -> [Section Position]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat t [Section Position]
sections)
    parseSec :: C.Section C.Position -> C.ParseResult (Config f -> Config f)
    parseSec :: Section Position -> ParseResult (Config f -> Config f)
parseSec (C.MkSection (C.Name Position
_pos ByteString
name) [C.SecArgName Position
_pos' ByteString
secName] [Field Position]
fields) | ByteString
name ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"repository" = do
        let repoName :: FilePath
repoName = ByteString -> FilePath
C.fromUTF8BS ByteString
secName
        let fields' :: Fields Position
fields' = (Fields Position, [[Section Position]]) -> Fields Position
forall a b. (a, b) -> a
fst ((Fields Position, [[Section Position]]) -> Fields Position)
-> (Fields Position, [[Section Position]]) -> Fields Position
forall a b. (a -> b) -> a -> b
$ [Field Position] -> (Fields Position, [[Section Position]])
forall ann. [Field ann] -> (Fields ann, [[Section ann]])
C.partitionFields [Field Position]
fields
        Repo
repo <- CabalSpecVersion
-> Fields Position
-> ParsecFieldGrammar Repo Repo
-> ParseResult Repo
forall s a.
CabalSpecVersion
-> Fields Position -> ParsecFieldGrammar s a -> ParseResult a
C.parseFieldGrammar CabalSpecVersion
C.cabalSpecLatest Fields Position
fields' ParsecFieldGrammar Repo Repo
repoGrammar
        (Config f -> Config f) -> ParseResult (Config f -> Config f)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Config f -> Config f) -> ParseResult (Config f -> Config f))
-> (Config f -> Config f) -> ParseResult (Config f -> Config f)
forall a b. (a -> b) -> a -> b
$ ASetter
  (Config f) (Config f) (Map FilePath Repo) (Map FilePath Repo)
-> (Map FilePath Repo -> Map FilePath Repo) -> Config f -> Config f
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
  (Config f) (Config f) (Map FilePath Repo) (Map FilePath Repo)
forall (f :: * -> *) (g :: * -> *).
Functor f =>
LensLike' f (Config g) (Map FilePath Repo)
cfgRepositoriesL ((Map FilePath Repo -> Map FilePath Repo) -> Config f -> Config f)
-> (Map FilePath Repo -> Map FilePath Repo) -> Config f -> Config f
forall a b. (a -> b) -> a -> b
$ FilePath -> Repo -> Map FilePath Repo -> Map FilePath Repo
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert FilePath
repoName Repo
repo
    parseSec Section Position
_ = (Config f -> Config f) -> ParseResult (Config f -> Config f)
forall (m :: * -> *) a. Monad m => a -> m a
return Config f -> Config f
forall a. a -> a
id
grammar :: C.ParsecFieldGrammar (Config Maybe) (Config Maybe)
grammar :: ParsecFieldGrammar (Config Maybe) (Config Maybe)
grammar = Map FilePath Repo
-> Maybe FilePath
-> Maybe FilePath
-> Maybe FilePath
-> Config Maybe
forall (f :: * -> *).
Map FilePath Repo
-> f FilePath -> f FilePath -> f FilePath -> Config f
Config Map FilePath Repo
forall a. Monoid a => a
mempty
    (Maybe FilePath
 -> Maybe FilePath -> Maybe FilePath -> Config Maybe)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar
     (Config Maybe) (Maybe FilePath -> Maybe FilePath -> Config Maybe)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> (FilePath -> FilePathNT)
-> ALens' (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalFieldAla ByteString
"remote-repo-cache" FilePath -> FilePathNT
C.FilePathNT ALens' (Config Maybe) (Maybe FilePath)
forall (f :: * -> *) (g :: * -> *).
Functor f =>
LensLike' f (Config g) (g FilePath)
cfgRemoteRepoCacheL
    ParsecFieldGrammar
  (Config Maybe) (Maybe FilePath -> Maybe FilePath -> Config Maybe)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar
     (Config Maybe) (Maybe FilePath -> Config Maybe)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteString
-> (FilePath -> FilePathNT)
-> ALens' (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalFieldAla ByteString
"installdir"        FilePath -> FilePathNT
C.FilePathNT ALens' (Config Maybe) (Maybe FilePath)
forall (f :: * -> *) (g :: * -> *).
Functor f =>
LensLike' f (Config g) (g FilePath)
cfgInstallDirL
    ParsecFieldGrammar (Config Maybe) (Maybe FilePath -> Config Maybe)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar (Config Maybe) (Config Maybe)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteString
-> (FilePath -> FilePathNT)
-> ALens' (Config Maybe) (Maybe FilePath)
-> ParsecFieldGrammar (Config Maybe) (Maybe FilePath)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalFieldAla ByteString
"store-dir"         FilePath -> FilePathNT
C.FilePathNT ALens' (Config Maybe) (Maybe FilePath)
forall (f :: * -> *) (g :: * -> *).
Functor f =>
LensLike' f (Config g) (g FilePath)
cfgStoreDirL
repoGrammar :: C.ParsecFieldGrammar Repo Repo
repoGrammar :: ParsecFieldGrammar Repo Repo
repoGrammar = URI -> Bool -> Repo
Repo
    (URI -> Bool -> Repo)
-> ParsecFieldGrammar Repo URI
-> ParsecFieldGrammar Repo (Bool -> Repo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> (URI -> WrappedURI)
-> ALens' Repo URI
-> ParsecFieldGrammar Repo URI
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.uniqueFieldAla  ByteString
"url"    URI -> WrappedURI
WrapURI ALens' Repo URI
forall (f :: * -> *). Functor f => LensLike' f Repo URI
repoURLL
    ParsecFieldGrammar Repo (Bool -> Repo)
-> ParsecFieldGrammar Repo Bool -> ParsecFieldGrammar Repo Repo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteString
-> ALens' Repo Bool -> Bool -> ParsecFieldGrammar Repo Bool
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"secure"         ALens' Repo Bool
forall (f :: * -> *). Functor f => LensLike' f Repo Bool
repoSecureL Bool
False
resolveConfig :: Config Maybe -> IO (Config Identity)
resolveConfig :: Config Maybe -> IO (Config Identity)
resolveConfig Config Maybe
cfg = do
    FilePath
c <- FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"cabal"
    Config Identity -> IO (Config Identity)
forall (m :: * -> *) a. Monad m => a -> m a
return Config Maybe
cfg
        { cfgRemoteRepoCache :: Identity FilePath
cfgRemoteRepoCache = FilePath -> Identity FilePath
forall a. a -> Identity a
Identity (FilePath -> Identity FilePath) -> FilePath -> Identity FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe (FilePath
c FilePath -> FilePath -> FilePath
</> FilePath
"packages") (Config Maybe -> Maybe FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgRemoteRepoCache Config Maybe
cfg)
        , cfgInstallDir :: Identity FilePath
cfgInstallDir      = FilePath -> Identity FilePath
forall a. a -> Identity a
Identity (FilePath -> Identity FilePath) -> FilePath -> Identity FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe (FilePath
c FilePath -> FilePath -> FilePath
</> FilePath
"bin")      (Config Maybe -> Maybe FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgInstallDir Config Maybe
cfg)
        , cfgStoreDir :: Identity FilePath
cfgStoreDir        = FilePath -> Identity FilePath
forall a. a -> Identity a
Identity (FilePath -> Identity FilePath) -> FilePath -> Identity FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe (FilePath
c FilePath -> FilePath -> FilePath
</> FilePath
"store")    (Config Maybe -> Maybe FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgStoreDir Config Maybe
cfg)
        }
cfgRepositoriesL :: Functor f => LensLike' f (Config g) (Map String Repo)
cfgRepositoriesL :: LensLike' f (Config g) (Map FilePath Repo)
cfgRepositoriesL Map FilePath Repo -> f (Map FilePath Repo)
f Config g
cfg = Map FilePath Repo -> f (Map FilePath Repo)
f (Config g -> Map FilePath Repo
forall (f :: * -> *). Config f -> Map FilePath Repo
cfgRepositories Config g
cfg) f (Map FilePath Repo)
-> (Map FilePath Repo -> Config g) -> f (Config g)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Map FilePath Repo
x -> Config g
cfg { cfgRepositories :: Map FilePath Repo
cfgRepositories = Map FilePath Repo
x }
cfgRemoteRepoCacheL :: Functor f => LensLike' f (Config g) (g FilePath)
cfgRemoteRepoCacheL :: LensLike' f (Config g) (g FilePath)
cfgRemoteRepoCacheL g FilePath -> f (g FilePath)
f Config g
cfg = g FilePath -> f (g FilePath)
f (Config g -> g FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgRemoteRepoCache Config g
cfg) f (g FilePath) -> (g FilePath -> Config g) -> f (Config g)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \g FilePath
x -> Config g
cfg { cfgRemoteRepoCache :: g FilePath
cfgRemoteRepoCache = g FilePath
x }
cfgInstallDirL :: Functor f => LensLike' f (Config g) (g FilePath)
cfgInstallDirL :: LensLike' f (Config g) (g FilePath)
cfgInstallDirL g FilePath -> f (g FilePath)
f Config g
cfg = g FilePath -> f (g FilePath)
f (Config g -> g FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgInstallDir Config g
cfg) f (g FilePath) -> (g FilePath -> Config g) -> f (Config g)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \g FilePath
x -> Config g
cfg { cfgInstallDir :: g FilePath
cfgInstallDir = g FilePath
x }
cfgStoreDirL :: Functor f => LensLike' f (Config g) (g FilePath)
cfgStoreDirL :: LensLike' f (Config g) (g FilePath)
cfgStoreDirL g FilePath -> f (g FilePath)
f Config g
cfg = g FilePath -> f (g FilePath)
f (Config g -> g FilePath
forall (f :: * -> *). Config f -> f FilePath
cfgStoreDir Config g
cfg) f (g FilePath) -> (g FilePath -> Config g) -> f (Config g)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \g FilePath
x -> Config g
cfg { cfgStoreDir :: g FilePath
cfgStoreDir = g FilePath
x }
repoURLL :: Functor f => LensLike' f Repo URI
repoURLL :: LensLike' f Repo URI
repoURLL URI -> f URI
f Repo
s = URI -> f URI
f (Repo -> URI
repoURL Repo
s) f URI -> (URI -> Repo) -> f Repo
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \URI
x -> Repo
s { repoURL :: URI
repoURL = URI
x }
repoSecureL :: Functor f => LensLike' f Repo Bool
repoSecureL :: LensLike' f Repo Bool
repoSecureL Bool -> f Bool
f Repo
s = Bool -> f Bool
f (Repo -> Bool
repoSecure Repo
s) f Bool -> (Bool -> Repo) -> f Repo
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Bool
x -> Repo
s { repoSecure :: Bool
repoSecure = Bool
x }