mirror of
https://github.com/commercialhaskell/stackage-server.git
synced 2026-01-12 04:08:29 +01:00
Drop dependency on stackage-curator
This commit is contained in:
parent
856ac728b4
commit
77b0b3b396
@ -75,7 +75,6 @@ dependencies:
|
||||
- hoogle
|
||||
- deepseq
|
||||
- auto-update
|
||||
- stackage-curator
|
||||
- yesod-sitemap
|
||||
- streaming-commons
|
||||
- classy-prelude-conduit
|
||||
|
||||
@ -2,12 +2,13 @@
|
||||
module Handler.BuildPlan where
|
||||
|
||||
import Import hiding (get, PackageName (..), Version (..), DList)
|
||||
import Stackage.Types
|
||||
import Stackage.ShowBuildPlan
|
||||
--import Stackage.Types
|
||||
import Stackage.Database
|
||||
|
||||
getBuildPlanR :: SnapName -> Handler TypedContent
|
||||
getBuildPlanR slug = track "Handler.BuildPlan.getBuildPlanR" $ do
|
||||
getBuildPlanR _slug = track "Handler.BuildPlan.getBuildPlanR" $ do
|
||||
error "temporarily disabled, please open on issue on https://github.com/fpco/stackage-server/issues/ if you need it"
|
||||
{-
|
||||
fullDeps <- (== Just "true") <$> lookupGetParam "full-deps"
|
||||
spec <- parseSnapshotSpec $ toPathPiece slug
|
||||
let set = setShellCommands simpleCommands
|
||||
@ -21,3 +22,4 @@ getBuildPlanR slug = track "Handler.BuildPlan.getBuildPlanR" $ do
|
||||
provideRep $ return $ toSimpleText toInstall
|
||||
provideRep $ return $ toJSON toInstall
|
||||
provideRepType "application/x-sh" $ return $ toShellScript set toInstall
|
||||
-}
|
||||
|
||||
88
src/Stackage/Types.hs
Normal file
88
src/Stackage/Types.hs
Normal file
@ -0,0 +1,88 @@
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
module Stackage.Types
|
||||
( BuildPlan (..)
|
||||
, SystemInfo (..)
|
||||
, PackagePlan (..)
|
||||
, DocMap
|
||||
, PackageDocs (..)
|
||||
, PackageName
|
||||
, Version
|
||||
, display
|
||||
) where
|
||||
|
||||
import qualified Distribution.Text as DT
|
||||
import ClassyPrelude.Conduit
|
||||
import Data.Aeson
|
||||
import Distribution.Types.PackageName (PackageName, mkPackageName)
|
||||
import Distribution.Version (Version)
|
||||
import Control.Monad.Catch (MonadThrow, throwM)
|
||||
import Data.Typeable (TypeRep, Typeable, typeOf)
|
||||
|
||||
data BuildPlan = BuildPlan
|
||||
{ bpSystemInfo :: !SystemInfo
|
||||
, bpPackages :: !(Map PackageName PackagePlan)
|
||||
}
|
||||
instance FromJSON BuildPlan where
|
||||
parseJSON = withObject "BuildPlan" $ \o -> BuildPlan
|
||||
<$> o .: "system-info"
|
||||
<*> o .: "packages"
|
||||
|
||||
data SystemInfo = SystemInfo
|
||||
{ siGhcVersion :: !Version
|
||||
, siCorePackages :: !(Map PackageName Version)
|
||||
}
|
||||
instance FromJSON SystemInfo where
|
||||
parseJSON = withObject "SystemInfo" $ \o -> SystemInfo
|
||||
<$> o .: "ghc-version"
|
||||
<*> o .: "core-packages"
|
||||
|
||||
data PackagePlan = PackagePlan
|
||||
{ ppVersion :: Version
|
||||
}
|
||||
instance FromJSON PackagePlan where
|
||||
parseJSON = withObject "PackagePlan" $ \o -> PackagePlan
|
||||
<$> o .: "version"
|
||||
|
||||
type DocMap = Map Text PackageDocs
|
||||
|
||||
data PackageDocs = PackageDocs
|
||||
{ pdVersion :: !Text
|
||||
, pdModules :: !(Map Text [Text])
|
||||
}
|
||||
instance FromJSON PackageDocs where
|
||||
parseJSON = withObject "PackageDocs" $ \o -> PackageDocs
|
||||
<$> o .: "version"
|
||||
<*> o .: "modules"
|
||||
|
||||
display :: DT.Text a => a -> Text
|
||||
display = fromString . DT.display
|
||||
|
||||
data ParseFailedException = ParseFailedException TypeRep Text
|
||||
deriving (Show, Typeable)
|
||||
instance Exception ParseFailedException
|
||||
|
||||
simpleParse :: (MonadThrow m, DT.Text a, Typeable a) => Text -> m a
|
||||
simpleParse orig = withTypeRep $ \rep ->
|
||||
case DT.simpleParse str of
|
||||
Nothing -> throwM (ParseFailedException rep (pack str))
|
||||
Just v -> return v
|
||||
where
|
||||
str = unpack orig
|
||||
|
||||
withTypeRep :: Typeable a => (TypeRep -> m a) -> m a
|
||||
withTypeRep f =
|
||||
res
|
||||
where
|
||||
res = f (typeOf (unwrap res))
|
||||
|
||||
unwrap :: m a -> a
|
||||
unwrap _ = error "unwrap"
|
||||
|
||||
-- orphans
|
||||
|
||||
instance FromJSON Version where
|
||||
parseJSON = withText "Version" $ either (fail . show) pure . simpleParse
|
||||
instance FromJSON PackageName where
|
||||
parseJSON = withText "PackageName" $ pure . mkPackageName . unpack
|
||||
instance FromJSONKey PackageName where
|
||||
fromJSONKey = FromJSONKeyText $ mkPackageName . unpack
|
||||
@ -2,4 +2,3 @@ resolver: nightly-2018-06-20
|
||||
extra-deps:
|
||||
- archive: https://github.com/snoyberg/gitrev/archive/6a1a639f493ac08959eb5ddf540ca1937baaaaf9.tar.gz
|
||||
- archive: https://github.com/bitemyapp/esqueleto/archive/b81e0d951e510ebffca03c5a58658ad884cc6fbd.tar.gz
|
||||
- archive: https://github.com/fpco/stackage-curator/archive/7635cdc45fcc7c1b733957bce865c40ae8e22b0c.tar.gz
|
||||
|
||||
Loading…
Reference in New Issue
Block a user