This commit is contained in:
Adam Bergmark 2023-12-23 19:27:17 +01:00 committed by Jens Petersen
parent 821abc97ef
commit b2a81b7260
7 changed files with 35 additions and 19 deletions

View File

@ -0,0 +1,2 @@
package *
ghc-options: -fwrite-ide-info

View File

@ -30,6 +30,7 @@ executable lts-constraints
, Cabal
, containers
, mtl
, optparse-generic
, pantry
, parsec
, rio

View File

@ -1,4 +1,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS -Wno-name-shadowing #-}
@ -8,12 +11,12 @@ import Control.Monad
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.State (MonadState (..), runStateT)
import Data.Text (Text)
import Options.Generic (getRecord, ParseRecord)
import Data.Text qualified as T
import Data.Text.IO qualified as T
import GHC.Generics (Generic)
import RIO.Map (Map)
import System.IO (openFile, IOMode (..), hFlush, hClose)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Safe (at)
import System.Environment (getArgs)
import BuildConstraints (parsePackageDecl, handlePackage)
import Snapshot (snapshotMap, loadSnapshot)
@ -23,7 +26,14 @@ src :: String
src = "../../build-constraints.yaml"
target :: Int -> String
target major = "../../lts-" <> show major <> "-build-constraints.yaml"
target major = "lts-" <> show major <> "-build-constraints.yaml"
data Args = Args
{ major :: Int
, baseSnapshotPath :: FilePath
} deriving Generic
instance ParseRecord Args
data State
= LookingForLibBounds
@ -32,10 +42,8 @@ data State
main :: IO ()
main = do
args :: [String] <- getArgs
print args
let major :: Int = read . (`at` 0) $ args
map <- snapshotMap <$> loadSnapshot ("../../../stackage-snapshots/lts/" <> show major <> "/0.yaml")
Args { major, baseSnapshotPath } <- getRecord "lts-constraints"
map <- snapshotMap <$> loadSnapshot baseSnapshotPath
output <- openFile (target major) WriteMode
let putLine = liftIO . T.hPutStrLn output
lines <- T.lines <$> T.readFile src
@ -43,7 +51,7 @@ main = do
forM_ lines $ putLine <=< processLine map
hFlush output
hClose output
putStrLn $ "Done. Wrote to " <> (target major)
putStrLn $ "Done. Wrote to " <> target major
processLine :: MonadState State m => Map PackageName Version -> Text -> m Text
processLine map line = do

View File

@ -1,6 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# OPTIONS -Wno-name-shadowing #-}
module Types where
@ -9,13 +8,12 @@ import Data.Aeson
import Data.String.Conversions.Monomorphic
import Distribution.Text (simpleParse)
import Distribution.Types.VersionRange (VersionRange)
import GHC.Generics
import RIO.Text (Text)
import qualified Distribution.Types.PackageName as C (PackageName, mkPackageName)
import qualified Distribution.Types.Version as C (Version)
newtype PackageName = PackageName { unPackageName :: C.PackageName }
deriving (Eq, Generic, Ord, FromJSONKey, Show)
deriving (Eq, Ord, FromJSONKey, Show)
mkPackageName :: Text -> PackageName
mkPackageName = PackageName . C.mkPackageName . fromStrictText
@ -24,7 +22,7 @@ instance FromJSON PackageName where
parseJSON = fmap (PackageName . C.mkPackageName) . parseJSON
newtype Version = Version { unVersion :: C.Version }
deriving (Generic, Show)
deriving Show
instance FromJSON Version where
parseJSON =

View File

@ -1,4 +1,4 @@
resolver:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/21/24.yaml
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/22/0.yaml
packages:
- .

View File

@ -6,8 +6,8 @@
packages: []
snapshots:
- completed:
sha256: abcc4a65c15c7c2313f1a87f01bfd4d910516e1930b99653eef1d2d006515916
size: 640074
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/21/24.yaml
sha256: e176944bc843f740e05242fa7a66ca1f440c127e425254f7f1257f9b19add23f
size: 712153
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/22/0.yaml
original:
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/21/24.yaml
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/22/0.yaml

View File

@ -0,0 +1,7 @@
roots = ["Main.main","^Paths_.*"]
type-class-roots = false
root-instances = [{ class = "\\.IsString$" },{ class = "\\.IsList$" }]
unused-types = false