-- | This program generates Cartel's own Cabal file. It's included -- here in the library to provide a live, type-checked, compilable -- example. You will want to look at the source code itself, as the -- Haddocks won't show you much. module Cartel.GenCartelCabal where import Cartel import qualified Cartel.Version -- Dependencies base :: Package base = closedOpen "base" [4,8,0,0] [5] directory :: Package directory = atLeast "directory" [1,1,0,2] filepath :: Package filepath = atLeast "filepath" [1,3,0,0] time :: Package time = atLeast "time" [1,4] quickcheck :: Package quickcheck = atLeast "QuickCheck" [2,7] tasty :: Package tasty = atLeast "tasty" [0,10] tastyQuickcheck :: Package tastyQuickcheck = atLeast "tasty-quickcheck" [0,8] tastyTh :: Package tastyTh = atLeast "tasty-th" [0,1] random :: Package random = atLeast "random" [1,0,1,1] transformers :: Package transformers = atLeast "transformers" [0,3,0,0] multiarg :: Package multiarg = atLeast "multiarg" [0,30,0,0] libDepends :: [Package] libDepends = [ base, directory, filepath, time, transformers ] testDepends :: [Package] testDepends = [ multiarg, quickcheck, random, tasty, tastyTh, tastyQuickcheck ] commonOptions :: HasBuildInfo a => [a] commonOptions = [ ghcOptions ["-Wall"] , hsSourceDirs ["lib"] , buildDepends libDepends ] testOptions :: HasBuildInfo a => [a] testOptions = hsSourceDirs ["tests"] : buildDepends testDepends : commonOptions main :: IO () main = defaultMain $ do libModules <- modules "lib" flagVisual <- makeFlag "visual" (FlagOpts { flagDescription = "Build cartel-visual-test executable." , flagDefault = False , flagManual = True }) testMods <- modules "tests" return ( mempty { name = "cartel" , version = Cartel.Version.version , buildType = Just simple , category = "Distribution" , maintainer = "omari@smileystation.com" , synopsis = "Specify Cabal files in Haskell" , description = [ "By specifying your Cabal files in Haskell, you have the power" , "of Haskell at your disposal to reduce redundancy. You can" , "also read in trees of module names dynamically, which saves" , "you from manually maintaining lists of module names." , "" , "See the documentation in the \"Cartel\" module for details." ] , license = Just bsd3 , licenseFile = "LICENSE" , copyright = "Copyright 2014-2016 Omari Norman" , author = "Omari Norman" , stability = "Experimental" , cabalVersion = Just (1,10) , homepage = "http://www.github.com/massysett/cartel" , bugReports = "http://www.github.com/massysett/cartel/issues" , extraSourceFiles = ["README.md"] } , exposedModules libModules : haskell2010 : commonOptions , [ githubHead "massysett" "cartel" , executable "cartel-visual-test" [ condBlock (flag flagVisual) ( buildable True , otherModules (testMods ++ libModules) : testOptions ) [ buildable False ] , haskell2010 , mainIs "cartel-visual-test.hs" ] , testSuite "cartel-properties" $ haskell2010 : otherModules (testMods ++ libModules) : otherExtensions ["TemplateHaskell"] : testOptions ++ exitcodeFields "cartel-properties.hs" ] )