From a29be8315c2e6647a5878529affda84ec8036ccb Mon Sep 17 00:00:00 2001 From: stuebinm Date: Tue, 11 Oct 2022 11:28:30 +0200 Subject: update stack resolver (also got rid of the map templater, which had version problems with mustache — it's not likely anyone will need it anyways) --- cwality-config.toml | 9 ---- cwality-maps/Config.hs | 61 --------------------- cwality-maps/Main.hs | 129 --------------------------------------------- cwality-maps/Substitute.hs | 100 ----------------------------------- default.nix | 4 +- fixed.nix | 30 ----------- lib/LintConfig.hs | 4 +- package.yaml | 21 -------- src/Version.hs | 2 +- stack.yaml | 21 ++------ stack.yaml.lock | 102 ++++++----------------------------- walint.cabal | 45 ++++------------ 12 files changed, 37 insertions(+), 491 deletions(-) delete mode 100644 cwality-config.toml delete mode 100644 cwality-maps/Config.hs delete mode 100644 cwality-maps/Main.hs delete mode 100644 cwality-maps/Substitute.hs delete mode 100644 fixed.nix diff --git a/cwality-config.toml b/cwality-config.toml deleted file mode 100644 index b663476..0000000 --- a/cwality-config.toml +++ /dev/null @@ -1,9 +0,0 @@ - - -verbose = true -port = 8080 - -# directory containing template maps. -# all .json files therein will be interpreted as maps; -# other files are served statically -template = "./example-templates" diff --git a/cwality-maps/Config.hs b/cwality-maps/Config.hs deleted file mode 100644 index 38c61ed..0000000 --- a/cwality-maps/Config.hs +++ /dev/null @@ -1,61 +0,0 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE KindSignatures #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE TypeFamilies #-} - -module Config ( loadConfig - , Config, port, verbose, template - ) where - -import Universum - -import Data.List (isSuffixOf) -import qualified Data.Map.Strict as M -import Data.Tiled (Tiledmap, - loadTiledmap) -import Lens.Micro.Platform (makeLenses, traverseOf) -import System.Directory (listDirectory) -import System.FilePath (()) -import Toml (TomlCodec, (.=)) -import qualified Toml as T - -type family ConfigRes (b :: Bool) a where - ConfigRes True a = a - ConfigRes False a = FilePath - --- | the server's configuration -data Config (loaded :: Bool) = Config - { _port :: Int - , _verbose :: Bool - , _template :: ConfigRes loaded (FilePath, Map Text Tiledmap) - } deriving Generic - -makeLenses ''Config - - -configCodec :: TomlCodec (Config False) -configCodec = Config - <$> T.int "port" .= _port - <*> T.bool "verbose" .= _verbose - <*> T.string "template" .= _template - -loadConfig :: FilePath -> IO (Config True) -loadConfig path = do - T.decodeFileEither configCodec path >>= \case - Right c -> traverseOf template loadMaps c - Left err -> error (show err) - where loadMaps path = do - maps <- listDirectory path - <&> filter (".json" `isSuffixOf`) - - list <- forM maps $ \mapname -> - loadTiledmap (path mapname) >>= \case - Right tmap -> pure (toText mapname, tmap) - err -> error (show err) - - pure (path, M.fromList list) diff --git a/cwality-maps/Main.hs b/cwality-maps/Main.hs deleted file mode 100644 index 3f383cd..0000000 --- a/cwality-maps/Main.hs +++ /dev/null @@ -1,129 +0,0 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE DeriveAnyClass #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE TypeApplications #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} -{-# LANGUAGE UndecidableInstances #-} - - --- | simple server offering linting "as a service" -module Main where - -import Universum - -import Config (Config, loadConfig, port, - template, verbose) -import Data.Aeson (FromJSON) -import qualified Data.Aeson as A -import qualified Data.Map.Strict as M -import qualified Data.Text as T -import Data.Text.Encoding.Base64.URL (decodeBase64Unpadded) -import Data.Tiled (Tiledmap) -import Network.Wai.Handler.Warp (defaultSettings, - runSettings, setPort) -import Network.Wai.Middleware.Gzip (def) -import Network.Wai.Middleware.RequestLogger (OutputFormat (..), - RequestLoggerSettings (..), - mkRequestLogger) -import Servant (Application, Capture, - CaptureAll, - FromHttpApiData (parseUrlPiece), - Get, Handler, JSON, Raw, - Server, err400, err404, - serve, throwError, - type (:<|>) (..), - type (:>)) -import Servant.Server.StaticFiles (serveDirectoryWebApp) -import Substitute (Substitutable (substitute), - SubstitutionError) - -import Control.Monad.Logger - - --- | a map's filename ending in .json --- (a newtype to differentiate between maps and assets in a route) -newtype JsonFilename = JsonFilename Text - -instance FromHttpApiData JsonFilename where - parseUrlPiece url = - if ".json" `T.isSuffixOf` url - then Right (JsonFilename url) - else Left url - - -newtype Tag = Tag Text - deriving (Generic, FromJSON) - -newtype MapParams = MapParams - { substs :: Map Text Text - } deriving (Generic, FromJSON) - -instance FromHttpApiData MapParams where - parseUrlPiece urltext = - case decodeBase64Unpadded urltext of - Right text -> case A.decode (encodeUtf8 text) of - Just params -> params - Nothing -> Left "decoding params failed?" - -- for fun (and testing) also allow non-encoded json - Left _err -> case A.decode (encodeUtf8 urltext) of - Just params -> Right params - Nothing -> Left "decoding MapParams failed" - --- | actual set of routes: api for json & html + static pages from disk -type Routes = - "generate" :> Capture "params" MapParams :> - (Capture "map.json" JsonFilename :> Get '[JSON] Tiledmap - -- explicitly capture broken json to return 400 instead of looking for files - :<|> Capture "map.json" JsonFilename :> CaptureAll "rest" Text :> Get '[JSON] Void - :<|> Raw) - - - - -mkMap :: Config True -> Tiledmap -> MapParams -> ([SubstitutionError], Tiledmap) -mkMap _config basemap params = - substitute basemap (substs params) - -mapHandler :: MapParams -> Config True -> JsonFilename -> Handler Tiledmap -mapHandler params config (JsonFilename mapname) = - case M.lookup mapname (snd $ view template config) of - Just basemap -> runStdoutLoggingT $ - logWarnN (pretty errors) >> pure tiledmap - where (errors, tiledmap) = mkMap config basemap params - pretty errors = T.concat - . intersperse "\n " - $ concatMap (lines . show) errors - Nothing -> throwError err404 - --- | Complete set of routes: API + HTML sites -server :: Config True -> Server Routes -server config params = - mapHandler params config - :<|> (\_ _ -> throwError err400) - :<|> serveDirectoryWebApp (fst . view template $ config) - -app :: Config True -> Application -app = serve (Proxy @Routes) . server - - - -main :: IO () -main = do - config <- loadConfig "./cwality-config.toml" - loggerMiddleware <- mkRequestLogger - $ def { outputFormat = Detailed (view verbose config) } - - let warpsettings = - setPort (view port config) - defaultSettings - - runSettings warpsettings - . loggerMiddleware - $ app config diff --git a/cwality-maps/Substitute.hs b/cwality-maps/Substitute.hs deleted file mode 100644 index ccab272..0000000 --- a/cwality-maps/Substitute.hs +++ /dev/null @@ -1,100 +0,0 @@ -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TupleSections #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} -{-# LANGUAGE UndecidableInstances #-} - --- | Typeclasses for (generic) substitution on all strings contained in an ADT, --- failsafe, but with error reporting -module Substitute (SubstitutionError, Substitutable(..)) where - -import Universum - -import qualified Data.Aeson as A -import qualified Data.Foldable as Fold -import Data.Tiled (GlobalId, LocalId) -import GHC.Generics (Generic (Rep, from, to), K1 (K1), - M1 (M1), U1, type (:*:) ((:*:)), - type (:+:) (..)) -import qualified Text.Mustache as MU -import qualified Text.Mustache.Render as MU -import Text.Parsec.Error (ParseError) - --- | errors that might be encountered. SubstitutionErrors occur during substitution --- and a generally non-fatal (but might result e.g. in empty strings being inserted --- instead of variables), while CompileErrors may indicate that (invalid) template --- syntax got leaked into the output -data SubstitutionError = CompileError ParseError | Mustache MU.SubstitutionError - deriving Show - - -class Substitutable s where - substitute :: s -> Map Text Text -> ([SubstitutionError], s) - -instance Substitutable Text where - substitute orig substs = case MU.compileTemplate "" orig of - Right template -> first (map Mustache) $ MU.checkedSubstitute template substs - Left err -> ([CompileError err], orig) -- just ignore syntactic errors (TODO: add a log message?) - - -instance {-# OVERLAPS #-} Substitutable String where - substitute orig substs = second toString (substitute (toText orig) substs) - -instance {-# OVERLAPPING #-} (Functor a, Substitutable b, Foldable a) => Substitutable (a b) where - substitute orig substs = (Fold.fold $ map fst orig',) $ map snd orig' - where orig' = map (`substitute` substs) orig - --- | helper: don't substitute anything, don't produce errors -trivial :: t -> b -> ([a], t) -trivial = const . ([],) - -instance {-# OVERLAPS #-} Substitutable A.Value where - substitute (A.Object fields) params = - second A.Object $ traverse (`substitute` params) fields - substitute (A.String str) params = - second A.String $ substitute str params - substitute other params = ([], other) - - -instance Substitutable Int where - substitute = trivial - -instance Substitutable GlobalId where - substitute = trivial - -instance Substitutable LocalId where - substitute = trivial - -instance Substitutable Double where - substitute = trivial - -instance Substitutable Float where - substitute = trivial - -class GSubstitutable i where - gsubstitute :: i p -> Map Text Text -> ([SubstitutionError], i p) - -instance Substitutable c => GSubstitutable (K1 i c) where - gsubstitute (K1 text) = second K1 . substitute text - -instance (GSubstitutable a, GSubstitutable b) => GSubstitutable (a :*: b) where - gsubstitute (a :*: b) substs = (e1 <> e2, a' :*: b') - where (e1, a') = gsubstitute a substs - (e2, b') = gsubstitute b substs - -instance (GSubstitutable a, GSubstitutable b) => GSubstitutable (a :+: b) where - gsubstitute (L1 a) = second L1 . gsubstitute a - gsubstitute (R1 a) = second R1 . gsubstitute a - -instance (GSubstitutable a) => GSubstitutable (M1 x y a) where - gsubstitute (M1 a) = second M1 . gsubstitute a - -instance GSubstitutable U1 where - gsubstitute = trivial - -instance {-# OVERLAPPABLE #-} (GSubstitutable (Rep a), Generic a) => Substitutable a where - substitute a substs = second to (gsubstitute (from a) substs) diff --git a/default.nix b/default.nix index d86ae6c..cceeb50 100644 --- a/default.nix +++ b/default.nix @@ -7,7 +7,9 @@ let # use haskell.nix's nixpkgs, which may (?) have more substitutes available haskellNix.sources.nixpkgs-unstable # args for nixpkgs; includes the haskell.nix overlay - (haskellNix.nixpkgsArgs // { system = "x86_64-linux"; }); + (haskellNix.nixpkgsArgs // { + system = "x86_64-linux"; + }); drvs = pkgs.haskell-nix.project { # 'cleanGit' cleans a source directory based on the files known by git diff --git a/fixed.nix b/fixed.nix deleted file mode 100644 index 35c2ba9..0000000 --- a/fixed.nix +++ /dev/null @@ -1,30 +0,0 @@ -{ nixpkgs ? import {} }: -with nixpkgs; - -stdenv.mkDerivation { - name = "walint-fixed"; - - buildInputs = [ ghc stack zlib zlib.dev git openssl cacert ]; - - src = ./.; - - buildPhase = '' - cp -r $src . - mkdir /tmp/stack-home - HOME=/tmp/stack-home stack build --no-nix --system-ghc - ''; - - installPhase = '' - HOME=/tmp/stack-home stack install --local-bin-path $out --no-nix --system-ghc - mkdir -p $out/share/walint - cp -r static $out/share/walint - cp config.json $out/share/walint - cp config.toml $out/share/walint - ''; - - outputHashAlgo = "sha256"; - outputHashMode = "recursive"; - # replace this with the correct SHA256 - outputHash = "sha256-Qd7MDGslrS6zs6WWI9sjzDous0nUbrjdK2fF747KLq8="; - dontShrink = true; -} diff --git a/lib/LintConfig.hs b/lib/LintConfig.hs index 87b9fbd..a84740d 100644 --- a/lib/LintConfig.hs +++ b/lib/LintConfig.hs @@ -182,7 +182,9 @@ expandWorlds config = config { configUriSchemas = configUriSchemas' } assemblysubsts = DomainSubstitution (M.fromList generated) ["map"] where generated = configAssemblies config - <&> \slug -> (slug, "/_/general/maps.world.di.c3voc.de/assembly/"<>slug) + <&> \slug -> if slug == "lobby" + then (slug, "/_/global/raw.githubusercontent.com/c0c0bird/bridging-bubbles") + else (slug, "/_/global/maps.world.di.c3voc.de/assembly/"<>slug) instance (FromJSON (LintConfig a)) => Argument (LintConfig a) where parseArgument str = diff --git a/package.yaml b/package.yaml index 82fd537..e2f6ea6 100644 --- a/package.yaml +++ b/package.yaml @@ -60,27 +60,6 @@ executables: - aeson-pretty - template-haskell - process - cwality-maps: - main: Main.hs - source-dirs: 'cwality-maps' - ghc-options: -rtsopts -threaded - dependencies: - - tiled - - servant - - servant-server - - wai - - wai-extra - - warp - - monad-logger - - fmt - - tomland - - microlens-platform - - directory - - filepath - - containers - - base64 - - parsec - - mustache walint-mapserver: main: Main.hs source-dirs: 'server' diff --git a/src/Version.hs b/src/Version.hs index e62c9b8..1748512 100644 --- a/src/Version.hs +++ b/src/Version.hs @@ -9,7 +9,7 @@ import qualified Language.Haskell.TH as TH import System.Process (readProcess) version :: String -version = "walint divoc bb3 2022 (" <> +version = "walint generic 2022 (" <> $(do hash <- liftIO $ catchAny (readProcess "git" ["rev-parse", "HEAD"] "") (\_ -> pure "[unknown]") diff --git a/stack.yaml b/stack.yaml index 787df61..56d9597 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,4 +1,4 @@ -resolver: lts-18.25 +resolver: lts-19.28 # User packages to be built. # Various formats can be used as shown in the example below. @@ -15,22 +15,11 @@ packages: # These entries can reference officially published versions as well as # forks / in-progress versions pinned to a git hash. For example: # -extra-deps: - - aeson-2.0.2.0 - - OneTuple-0.3.1@sha256:c4c1f2971fd41c964a1bbe433adeed4cad9d0f99d67430ff5e1be5a7d7ab2ca3,2240 - - semialign-1.2.0.1@sha256:5efc30d6f53f8d2a8a26d9bf3a57c0f20f4ba3086797ccaa615f644abc21d42e,2814 - - text-short-0.1.4@sha256:4f7a76e78baf391d262883007e8f8d8fb23a2805d56d9725d6abdf1428542e11,3575 - - time-compat-1.9.6.1@sha256:381a2e8ed6e41d20ff5929d12d25c1d9337d459de5964ef1d90b06d115b31f07,5033 - - HList-0.5.1.0@sha256:3ecb2d10ad2b3d36ad28e2f08505f9c3d7143ca737ef13b3e64db503635966c2,7525 - - cli-extras-0.1.0.2@sha256:404552a3e5e844f332fcf74858999b9b9b6d5dcab6017a9d5a48868715a21468,1996 - - logging-effect-1.3.12@sha256:72d168dd09887649ba9501627219b6027cbec2d5541931555b7885b133785ce3,1679 - - which-0.2@sha256:db82ca7d83d64cce8ad579756f02d27c5bd289806ee02474726f7fafb87318e8,858 - - cli-git-0.1.0.2@sha256:4e62e6b7357e4fe698df8b58ba53919f9d4a056e9617dbc00c869a365e316387,1122 - - servant-lucid-0.9.0.4@sha256:698db96903a145fdef40cc897f8790728642af917c37b941a98b2da872b65f08,1787 - - servant-websockets-2.0.0@sha256:6e9e3600bced90fd52ed3d1bf632205cb21479075b20d6637153cc4567000234,2253 - # mustache is on stackage, but in a version that doesn't yet support aeson 2.0 - - mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 allow-newer: true +extra-deps: +- mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 +- tomland-1.3.3.1@sha256:83a8fd26a97164100541f7b26aa40ffdc6f230b21e94cbb3eae1fb7093c4356e,8924 +- validation-selective-0.1.0.1@sha256:9a5aa8b801efc6a4ffb120e1b28e80c5f7d090043be56bba11222cd20c393044,3621 # use aeson with a non-hash-floodable implementation flags: diff --git a/stack.yaml.lock b/stack.yaml.lock index 43a3319..fb1ccd1 100644 --- a/stack.yaml.lock +++ b/stack.yaml.lock @@ -5,99 +5,29 @@ packages: - completed: - hackage: aeson-2.0.2.0@sha256:5720fffb7289366029f2b7940e9f8b22a1b4c282f0cef4710685b1d14d76bdc7,6327 pantry-tree: - size: 37910 - sha256: 6de8e70acd5ed455ac33d7496e8dbf994067f1f845dd420e7256623b2a8dee8b - original: - hackage: aeson-2.0.2.0 -- completed: - hackage: OneTuple-0.3.1@sha256:c4c1f2971fd41c964a1bbe433adeed4cad9d0f99d67430ff5e1be5a7d7ab2ca3,2240 - pantry-tree: - size: 506 - sha256: 7678e4fbd592b26bb241e56171f400a62f73bc1de8a7706fcc2fbce2a5ba9c20 - original: - hackage: OneTuple-0.3.1@sha256:c4c1f2971fd41c964a1bbe433adeed4cad9d0f99d67430ff5e1be5a7d7ab2ca3,2240 -- completed: - hackage: semialign-1.2.0.1@sha256:5efc30d6f53f8d2a8a26d9bf3a57c0f20f4ba3086797ccaa615f644abc21d42e,2814 - pantry-tree: - size: 537 - sha256: 061a65f6c4355cc852cbfb0b4ad875814acf8f35edc7cefa4bf5b3e2c9b63e33 - original: - hackage: semialign-1.2.0.1@sha256:5efc30d6f53f8d2a8a26d9bf3a57c0f20f4ba3086797ccaa615f644abc21d42e,2814 -- completed: - hackage: text-short-0.1.4@sha256:4f7a76e78baf391d262883007e8f8d8fb23a2805d56d9725d6abdf1428542e11,3575 - pantry-tree: - size: 727 - sha256: aa1040a3846f49461a4345e96f1a7d8367f00657f248c52cb7b76cb162dc8b10 - original: - hackage: text-short-0.1.4@sha256:4f7a76e78baf391d262883007e8f8d8fb23a2805d56d9725d6abdf1428542e11,3575 -- completed: - hackage: time-compat-1.9.6.1@sha256:381a2e8ed6e41d20ff5929d12d25c1d9337d459de5964ef1d90b06d115b31f07,5033 - pantry-tree: - size: 4113 - sha256: dd54303f712dd2b8dc05942061921b0d06e0bd501b42c965a9ac6a0a37cd3128 - original: - hackage: time-compat-1.9.6.1@sha256:381a2e8ed6e41d20ff5929d12d25c1d9337d459de5964ef1d90b06d115b31f07,5033 -- completed: - hackage: HList-0.5.1.0@sha256:3ecb2d10ad2b3d36ad28e2f08505f9c3d7143ca737ef13b3e64db503635966c2,7525 - pantry-tree: - size: 5800 - sha256: fe9d53555847bd16ffd46e3fb6013751c23f375a95d05b4d4c8de0bb22911e72 - original: - hackage: HList-0.5.1.0@sha256:3ecb2d10ad2b3d36ad28e2f08505f9c3d7143ca737ef13b3e64db503635966c2,7525 -- completed: - hackage: cli-extras-0.1.0.2@sha256:404552a3e5e844f332fcf74858999b9b9b6d5dcab6017a9d5a48868715a21468,1996 - pantry-tree: - size: 849 - sha256: 0f78dd9ad144dd81d2567ff0c47c111e2764db1b48341b34a2026018fb7f01ff - original: - hackage: cli-extras-0.1.0.2@sha256:404552a3e5e844f332fcf74858999b9b9b6d5dcab6017a9d5a48868715a21468,1996 -- completed: - hackage: logging-effect-1.3.12@sha256:72d168dd09887649ba9501627219b6027cbec2d5541931555b7885b133785ce3,1679 - pantry-tree: - size: 330 - sha256: 3907e21147987af4f1590abce025e7439f0d338444f259791068c361d586117f - original: - hackage: logging-effect-1.3.12@sha256:72d168dd09887649ba9501627219b6027cbec2d5541931555b7885b133785ce3,1679 -- completed: - hackage: which-0.2@sha256:db82ca7d83d64cce8ad579756f02d27c5bd289806ee02474726f7fafb87318e8,858 - pantry-tree: - size: 262 - sha256: bef8458bddea924f3162e51fcef66cb3071f73c31d3dbb6d4029b0115af88a54 - original: - hackage: which-0.2@sha256:db82ca7d83d64cce8ad579756f02d27c5bd289806ee02474726f7fafb87318e8,858 -- completed: - hackage: cli-git-0.1.0.2@sha256:4e62e6b7357e4fe698df8b58ba53919f9d4a056e9617dbc00c869a365e316387,1122 - pantry-tree: - size: 269 - sha256: 1e81c51e2b60db2b1784901cf0af33c67384f5412ad8edaad8a7068135f5217f - original: - hackage: cli-git-0.1.0.2@sha256:4e62e6b7357e4fe698df8b58ba53919f9d4a056e9617dbc00c869a365e316387,1122 -- completed: - hackage: servant-lucid-0.9.0.4@sha256:698db96903a145fdef40cc897f8790728642af917c37b941a98b2da872b65f08,1787 - pantry-tree: - size: 392 - sha256: 39e0e7b2b25980bfe4df036e89959188f9ef9e8c78c85e241fa9a682d1d78cf3 + sha256: 44c4d43ecfe1fee11fb03ffd49b0580ed00eec5144067092801ef4256df77ef8 + size: 1182 + hackage: mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 original: - hackage: servant-lucid-0.9.0.4@sha256:698db96903a145fdef40cc897f8790728642af917c37b941a98b2da872b65f08,1787 + hackage: mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 - completed: - hackage: servant-websockets-2.0.0@sha256:6e9e3600bced90fd52ed3d1bf632205cb21479075b20d6637153cc4567000234,2253 pantry-tree: - size: 523 - sha256: 085c6620bff7671bef1d969652a349271c3703fbf10dd753cb63ee1cd700bca5 + sha256: 0e3bdbd32955944c3ee9ff0f47dc765d25ab6be4a336c6d735eed8eb9bc8ce27 + size: 6430 + hackage: tomland-1.3.3.1@sha256:83a8fd26a97164100541f7b26aa40ffdc6f230b21e94cbb3eae1fb7093c4356e,8924 original: - hackage: servant-websockets-2.0.0@sha256:6e9e3600bced90fd52ed3d1bf632205cb21479075b20d6637153cc4567000234,2253 + hackage: tomland-1.3.3.1@sha256:83a8fd26a97164100541f7b26aa40ffdc6f230b21e94cbb3eae1fb7093c4356e,8924 - completed: - hackage: mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 pantry-tree: - size: 1182 - sha256: 44c4d43ecfe1fee11fb03ffd49b0580ed00eec5144067092801ef4256df77ef8 + sha256: bf72fe4304690da4b5bc6e5218b0f90b5613e7d658f3ce31731816a423fcbca6 + size: 696 + hackage: validation-selective-0.1.0.1@sha256:9a5aa8b801efc6a4ffb120e1b28e80c5f7d090043be56bba11222cd20c393044,3621 original: - hackage: mustache-2.4.0@sha256:bd1cfbd027c04d8329877e95413d34dc357d4bee041dd8978cd6a23b114fbda1,3180 + hackage: validation-selective-0.1.0.1@sha256:9a5aa8b801efc6a4ffb120e1b28e80c5f7d090043be56bba11222cd20c393044,3621 snapshots: - completed: - size: 587393 - url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/18/25.yaml - sha256: 1b74fb5e970497b5aefae56703f1bd44aa648bd1a5ef95c1eb8c29775087e2bf - original: lts-18.25 + sha256: 7f4393ad659c579944d12202cffb12d8e4b8114566b015f77bbc303a24cff934 + size: 619405 + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/19/28.yaml + original: lts-19.28 diff --git a/walint.cabal b/walint.cabal index f5fe2fc..c380de3 100644 --- a/walint.cabal +++ b/walint.cabal @@ -1,6 +1,6 @@ cabal-version: 2.0 --- This file has been generated from package.yaml by hpack version 0.34.5. +-- This file has been generated from package.yaml by hpack version 0.34.7. -- -- see: https://github.com/sol/hpack @@ -29,6 +29,8 @@ library Properties Uris Paths_walint + autogen-modules: + Paths_walint hs-source-dirs: lib default-extensions: @@ -62,6 +64,8 @@ library tiled Data.Tiled.Abstract other-modules: Paths_walint + autogen-modules: + Paths_walint hs-source-dirs: tiled default-extensions: @@ -76,46 +80,13 @@ library tiled , vector default-language: Haskell2010 -executable cwality-maps - main-is: Main.hs - other-modules: - Config - Substitute - Paths_walint - hs-source-dirs: - cwality-maps - default-extensions: - NoImplicitPrelude - ghc-options: -Wall -Wno-name-shadowing -Wno-unticked-promoted-constructors -rtsopts -threaded - build-depends: - aeson - , base - , base64 - , bytestring - , containers - , directory - , filepath - , fmt - , microlens-platform - , monad-logger - , mustache - , parsec - , servant - , servant-server - , text - , tiled - , tomland - , universum - , wai - , wai-extra - , warp - default-language: Haskell2010 - executable walint main-is: Main.hs other-modules: Version Paths_walint + autogen-modules: + Paths_walint hs-source-dirs: src default-extensions: @@ -142,6 +113,8 @@ executable walint-mapserver Server Worker Paths_walint + autogen-modules: + Paths_walint hs-source-dirs: server default-extensions: -- cgit v1.2.3