| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
HsDev.Project.Types
Contents
Synopsis
- data BuildTool
- data Sandbox = Sandbox {}
- sandboxType :: Lens' Sandbox BuildTool
- sandbox :: Lens' Sandbox Path
- data Project = Project {}
- projectName :: Lens' Project Text
- projectPath :: Lens' Project Path
- projectCabal :: Lens' Project Path
- projectDescription :: Lens' Project (Maybe ProjectDescription)
- projectBuildTool :: Lens' Project BuildTool
- projectPackageDbStack :: Lens' Project (Maybe PackageDbStack)
- project :: FilePath -> Project
- data ProjectDescription = ProjectDescription {}
- projectVersion :: Lens' ProjectDescription Text
- projectLibrary :: Lens' ProjectDescription (Maybe Library)
- projectExecutables :: Lens' ProjectDescription [Executable]
- projectTests :: Lens' ProjectDescription [Test]
- infos :: Traversal' ProjectDescription Info
- targetInfos :: ProjectDescription -> [TargetInfo]
- class Target a where
- targetName :: Traversal' a Text
- buildInfo :: Lens' a Info
- targetMain :: a -> Maybe Path
- targetModules :: a -> [[Text]]
- data TargetInfo = TargetInfo {}
- targetInfoName :: Lens' TargetInfo (Maybe Text)
- targetBuildInfo :: Lens' TargetInfo Info
- targetInfoMain :: Lens' TargetInfo (Maybe Path)
- targetInfoModules :: Lens' TargetInfo [[Text]]
- targetInfo :: Target a => a -> TargetInfo
- data Library = Library {
- _libraryModules :: [[Text]]
- _libraryBuildInfo :: Info
- libraryModules :: Lens' Library [[Text]]
- libraryBuildInfo :: Lens' Library Info
- data Executable = Executable {}
- executableName :: Lens' Executable Text
- executablePath :: Lens' Executable Path
- executableBuildInfo :: Lens' Executable Info
- data Test = Test {
- _testName :: Text
- _testEnabled :: Bool
- _testMain :: Maybe Path
- _testBuildInfo :: Info
- testName :: Lens' Test Text
- testEnabled :: Lens' Test Bool
- testBuildInfo :: Lens' Test Info
- testMain :: Lens' Test (Maybe Path)
- data Info = Info {
- _infoDepends :: [Text]
- _infoLanguage :: Maybe Language
- _infoExtensions :: [Extension]
- _infoGHCOptions :: [Text]
- _infoSourceDirs :: [Path]
- _infoOtherModules :: [[Text]]
- infoDepends :: Lens' Info [Text]
- infoLanguage :: Lens' Info (Maybe Language)
- infoExtensions :: Lens' Info [Extension]
- infoGHCOptions :: Lens' Info [Text]
- infoSourceDirs :: Lens' Info [Path]
- infoOtherModules :: Lens' Info [[Text]]
- data Extensions a = Extensions {
- _extensions :: [Extension]
- _ghcOptions :: [Text]
- _entity :: a
- extensions :: forall a. Lens' (Extensions a) [Extension]
- ghcOptions :: forall a. Lens' (Extensions a) [Text]
- entity :: forall a a. Lens (Extensions a) (Extensions a) a a
Documentation
Project build tool
Instances
| Bounded BuildTool Source # | |
| Enum BuildTool Source # | |
Defined in HsDev.Project.Types Methods succ :: BuildTool -> BuildTool # pred :: BuildTool -> BuildTool # fromEnum :: BuildTool -> Int # enumFrom :: BuildTool -> [BuildTool] # enumFromThen :: BuildTool -> BuildTool -> [BuildTool] # enumFromTo :: BuildTool -> BuildTool -> [BuildTool] # enumFromThenTo :: BuildTool -> BuildTool -> BuildTool -> [BuildTool] # | |
| Eq BuildTool Source # | |
| Ord BuildTool Source # | |
| Read BuildTool Source # | |
| Show BuildTool Source # | |
| NFData BuildTool Source # | |
Defined in HsDev.Project.Types | |
| ToJSON BuildTool Source # | |
Defined in HsDev.Project.Types | |
| FromJSON BuildTool Source # | |
| Formattable BuildTool Source # | |
Defined in HsDev.Project.Types Methods formattable :: BuildTool -> FormatFlags -> Formatted # | |
| FromField BuildTool Source # | |
Defined in HsDev.Database.SQLite.Instances Methods | |
| ToField BuildTool Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| Display BuildTool Source # | |
Constructors
| Sandbox | |
Fields
| |
Instances
| Eq Sandbox Source # | |
| Ord Sandbox Source # | |
| Show Sandbox Source # | |
| NFData Sandbox Source # | |
Defined in HsDev.Project.Types | |
| ToJSON Sandbox Source # | |
Defined in HsDev.Project.Types | |
| FromJSON Sandbox Source # | |
| Formattable Sandbox Source # | |
Defined in HsDev.Project.Types Methods formattable :: Sandbox -> FormatFlags -> Formatted # | |
| FromRow Sandbox Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| ToRow Sandbox Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| Paths Sandbox Source # | |
Defined in HsDev.Project.Types | |
| Display Sandbox Source # | |
| EnumContents Sandbox Source # | |
Defined in HsDev.Scan Methods enumContents :: CommandMonad m => Sandbox -> m ScanContents Source # | |
Cabal project
Constructors
| Project | |
Instances
| Eq Project Source # | |
| Ord Project Source # | |
| Show Project Source # | |
| NFData Project Source # | |
Defined in HsDev.Project.Types | |
| ToJSON Project Source # | |
Defined in HsDev.Project.Types | |
| FromJSON Project Source # | |
| Formattable Project Source # | |
Defined in HsDev.Project.Types Methods formattable :: Project -> FormatFlags -> Formatted # | |
| FromRow Project Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| ToRow Project Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| Paths Project Source # | |
Defined in HsDev.Project.Types | |
| Display Project Source # | |
| Documented Project Source # | |
| EnumContents Project Source # | |
Defined in HsDev.Scan Methods enumContents :: CommandMonad m => Project -> m ScanContents Source # | |
data ProjectDescription Source #
Constructors
| ProjectDescription | |
Fields
| |
Instances
infos :: Traversal' ProjectDescription Info Source #
Build target infos
targetInfos :: ProjectDescription -> [TargetInfo] Source #
Build target infos, more detailed
Methods
targetName :: Traversal' a Text Source #
buildInfo :: Lens' a Info Source #
targetMain :: a -> Maybe Path Source #
targetModules :: a -> [[Text]] Source #
Instances
| Target Test Source # | |
Defined in HsDev.Project.Types | |
| Target Executable Source # | |
Defined in HsDev.Project.Types Methods targetName :: Traversal' Executable Text Source # buildInfo :: Lens' Executable Info Source # targetMain :: Executable -> Maybe Path Source # targetModules :: Executable -> [[Text]] Source # | |
| Target Library Source # | |
Defined in HsDev.Project.Types | |
| Target TargetInfo Source # | |
Defined in HsDev.Project.Types Methods targetName :: Traversal' TargetInfo Text Source # buildInfo :: Lens' TargetInfo Info Source # targetMain :: TargetInfo -> Maybe Path Source # targetModules :: TargetInfo -> [[Text]] Source # | |
data TargetInfo Source #
Constructors
| TargetInfo | |
Fields
| |
Instances
| Eq TargetInfo Source # | |
Defined in HsDev.Project.Types | |
| Ord TargetInfo Source # | |
Defined in HsDev.Project.Types Methods compare :: TargetInfo -> TargetInfo -> Ordering # (<) :: TargetInfo -> TargetInfo -> Bool # (<=) :: TargetInfo -> TargetInfo -> Bool # (>) :: TargetInfo -> TargetInfo -> Bool # (>=) :: TargetInfo -> TargetInfo -> Bool # max :: TargetInfo -> TargetInfo -> TargetInfo # min :: TargetInfo -> TargetInfo -> TargetInfo # | |
| Show TargetInfo Source # | |
Defined in HsDev.Project.Types Methods showsPrec :: Int -> TargetInfo -> ShowS # show :: TargetInfo -> String # showList :: [TargetInfo] -> ShowS # | |
| Paths TargetInfo Source # | |
Defined in HsDev.Project.Types Methods | |
| Target TargetInfo Source # | |
Defined in HsDev.Project.Types Methods targetName :: Traversal' TargetInfo Text Source # buildInfo :: Lens' TargetInfo Info Source # targetMain :: TargetInfo -> Maybe Path Source # targetModules :: TargetInfo -> [[Text]] Source # | |
targetInfoModules :: Lens' TargetInfo [[Text]] Source #
targetInfo :: Target a => a -> TargetInfo Source #
Library in project
Constructors
| Library | |
Fields
| |
Instances
| Eq Library Source # | |
| Read Library Source # | |
| Show Library Source # | |
| ToJSON Library Source # | |
Defined in HsDev.Project.Types | |
| FromJSON Library Source # | |
| FromRow Library Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| Paths Library Source # | |
Defined in HsDev.Project.Types | |
| Target Library Source # | |
Defined in HsDev.Project.Types | |
data Executable Source #
Executable
Constructors
| Executable | |
Fields | |
Instances
Test
Constructors
| Test | |
Fields
| |
Instances
Build info
Constructors
| Info | |
Fields
| |
Instances
| Eq Info Source # | |
| Ord Info Source # | |
| Read Info Source # | |
| Show Info Source # | |
| Semigroup Info Source # | |
| Monoid Info Source # | |
| ToJSON Info Source # | |
Defined in HsDev.Project.Types | |
| FromJSON Info Source # | |
| FromRow Info Source # | |
Defined in HsDev.Database.SQLite.Instances | |
| Paths Info Source # | |
Defined in HsDev.Project.Types | |
data Extensions a Source #
Entity with project extensions
Constructors
| Extensions | |
Fields
| |
Instances
extensions :: forall a. Lens' (Extensions a) [Extension] Source #
ghcOptions :: forall a. Lens' (Extensions a) [Text] Source #
entity :: forall a a. Lens (Extensions a) (Extensions a) a a Source #