{-# LANGUAGE DataKinds #-} module Distribution.Types.Executable.Lens ( Executable , module Distribution.Types.Executable.Lens ) where import Distribution.Compat.Lens import Distribution.Compat.Prelude import Prelude () import Distribution.Types.BuildInfo (BuildInfo) import Distribution.Types.Executable (Executable) import Distribution.Types.ExecutableScope (ExecutableScope) import Distribution.Types.UnqualComponentName (UnqualComponentName) import Distribution.Utils.Path import qualified Distribution.Types.Executable as T exeName :: Lens' Executable UnqualComponentName exeName :: Lens' Executable UnqualComponentName exeName UnqualComponentName -> f UnqualComponentName f Executable s = (UnqualComponentName -> Executable) -> f UnqualComponentName -> f Executable forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\UnqualComponentName x -> Executable s{T.exeName = x}) (UnqualComponentName -> f UnqualComponentName f (Executable -> UnqualComponentName T.exeName Executable s)) {-# INLINE exeName #-} modulePath :: Lens' Executable (RelativePath Source File) modulePath :: Lens' Executable (RelativePath Source 'File) modulePath RelativePath Source 'File -> f (RelativePath Source 'File) f Executable s = (RelativePath Source 'File -> Executable) -> f (RelativePath Source 'File) -> f Executable forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\RelativePath Source 'File x -> Executable s{T.modulePath = x}) (RelativePath Source 'File -> f (RelativePath Source 'File) f (Executable -> RelativePath Source 'File T.modulePath Executable s)) {-# INLINE modulePath #-} exeScope :: Lens' Executable ExecutableScope exeScope :: Lens' Executable ExecutableScope exeScope ExecutableScope -> f ExecutableScope f Executable s = (ExecutableScope -> Executable) -> f ExecutableScope -> f Executable forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\ExecutableScope x -> Executable s{T.exeScope = x}) (ExecutableScope -> f ExecutableScope f (Executable -> ExecutableScope T.exeScope Executable s)) {-# INLINE exeScope #-} exeBuildInfo :: Lens' Executable BuildInfo exeBuildInfo :: Lens' Executable BuildInfo exeBuildInfo BuildInfo -> f BuildInfo f Executable s = (BuildInfo -> Executable) -> f BuildInfo -> f Executable forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\BuildInfo x -> Executable s{T.buildInfo = x}) (BuildInfo -> f BuildInfo f (Executable -> BuildInfo T.buildInfo Executable s)) {-# INLINE exeBuildInfo #-}