module Game.LambdaHack.Client.UI.Content.Screen
( ScreenContent(..), makeData
#ifdef EXPOSE_INTERNAL
, validateSingle
#endif
) where
import Prelude ()
import Game.LambdaHack.Core.Prelude
import qualified Data.ByteString as BS
import qualified Data.EnumMap.Strict as EM
import qualified Data.Text as T
import Game.LambdaHack.Content.ItemKind (ItemKind)
import Game.LambdaHack.Definition.Defs
data ScreenContent = ScreenContent
{ ScreenContent -> X
rwidth :: X
, ScreenContent -> X
rheight :: Y
, ScreenContent -> String
rwebAddress :: String
, ScreenContent -> ([String], [[String]])
rintroScreen :: ([String], [[String]])
, ScreenContent -> EnumMap (ContentSymbol ItemKind) Text
rapplyVerbMap :: EM.EnumMap (ContentSymbol ItemKind) T.Text
, ScreenContent -> [(String, ByteString)]
rFontFiles :: [(FilePath, BS.ByteString)]
}
validateSingle :: ScreenContent -> [Text]
validateSingle :: ScreenContent -> [Text]
validateSingle ScreenContent{String
rwebAddress :: String
rwebAddress :: ScreenContent -> String
rwebAddress, ([String], [[String]])
rintroScreen :: ([String], [[String]])
rintroScreen :: ScreenContent -> ([String], [[String]])
rintroScreen} =
(let tsGt80 :: [Text]
tsGt80 = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((X -> X -> Bool
forall a. Ord a => a -> a -> Bool
> X
80) (X -> Bool) -> (Text -> X) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> X
T.length) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack [String
rwebAddress]
in case [Text]
tsGt80 of
[] -> []
Text
tGt80 : [Text]
_ -> [Text
"rwebAddress's length is over 80:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tGt80])
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (let tsGt41 :: [Text]
tsGt41 = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((X -> X -> Bool
forall a. Ord a => a -> a -> Bool
> X
41) (X -> Bool) -> (Text -> X) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> X
T.length) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack ([String] -> [Text]) -> [String] -> [Text]
forall a b. (a -> b) -> a -> b
$ ([String], [[String]]) -> [String]
forall a b. (a, b) -> a
fst ([String], [[String]])
rintroScreen
in case [Text]
tsGt41 of
[] -> []
Text
tGt41 : [Text]
_ -> [Text
"intro screen has a line with length over 41:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tGt41])
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (let tsGt80 :: [Text]
tsGt80 = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((X -> X -> Bool
forall a. Ord a => a -> a -> Bool
> X
80) (X -> Bool) -> (Text -> X) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> X
T.length) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack ([String] -> [Text]) -> [String] -> [Text]
forall a b. (a -> b) -> a -> b
$ [String] -> [[String]] -> [String]
forall a. [a] -> [[a]] -> [a]
intercalate [String
""]
([[String]] -> [String]) -> [[String]] -> [String]
forall a b. (a -> b) -> a -> b
$ ([String], [[String]]) -> [[String]]
forall a b. (a, b) -> b
snd ([String], [[String]])
rintroScreen
in case [Text]
tsGt80 of
[] -> []
Text
tGt80 : [Text]
_ -> [Text
"manual has a line with length over 80:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tGt80])
makeData :: ScreenContent -> ScreenContent
makeData :: ScreenContent -> ScreenContent
makeData ScreenContent
sc =
let singleOffenders :: [Text]
singleOffenders = ScreenContent -> [Text]
validateSingle ScreenContent
sc
in Bool -> ScreenContent -> ScreenContent
forall a. (?callStack::CallStack) => Bool -> a -> a
assert ([Text] -> Bool
forall a. [a] -> Bool
null [Text]
singleOffenders
Bool -> (String, [Text]) -> Bool
forall a. Show a => Bool -> a -> Bool
`blame` String
"Screen Content" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": some content items not valid"
String -> [Text] -> (String, [Text])
forall v. String -> v -> (String, v)
`swith` [Text]
singleOffenders)
ScreenContent
sc