Cleaned up Links, sorted parameters

This commit is contained in:
Shaun Kerr 2018-07-02 10:41:33 +12:00
parent 9cf0f6ebbd
commit 2611f8a8e2
6 changed files with 30 additions and 16 deletions

19
Main.hs
View File

@ -2,8 +2,7 @@
module Main where module Main where
import Data.Time.Clock import Data.Time
import Data.Time.Calendar
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import Packs import Packs
@ -33,19 +32,29 @@ instance Yesod ProtocolSeven
getHomeR :: Handler Html getHomeR :: Handler Html
getHomeR = defaultLayout $ do getHomeR = defaultLayout $ do
(year, month, day) <- io $ getCurrentTime >>= return . toGregorian . utctDay -- Date / Time stuff
sTimeDate <- io $ getZonedTime >>= return . (formatTime defaultTimeLocale "%y %m %d")
let (year, month, day) = (\[a,b,c] -> (a,b,c)) $ map (\x -> read x :: Integer) $ words sTimeDate
let nextMonth = (month + 1) `mod` 12 let nextMonth = (month + 1) `mod` 12
let ts = toTS (year, month, day) let ts = toTS (year, month, day)
-- Release Order Big Boxes
let (_,ib,_) = initialRotation
-- Current Format
let ((i,o),b,r) = currentFormat ts let ((i,o),b,r) = currentFormat ts
let bx = (\(Bq x) -> x) let bx = (\(Bq x) -> x)
let (_,ib,_) = initialRotation
let bbout = map show $ catMaybes $ inBoth (bx ib) (tail $ bx b) let bbout = map show $ catMaybes $ inBoth (bx ib) (tail $ bx b)
let dpout = sort $ map show $ map (\(Ir n) -> n) i let dpout = sort $ map show $ map (\(Ir n) -> n) i
-- Preview
let pr = getPreview ts let pr = getPreview ts
let (pdi,pdo,bbi,bbo) = extractPreview pr let (pdi,pdo,bbi,bbo) = extractPreview pr
let nrdbFormat = nrdbSearch (((map (\(Ir n) -> n) i) ++ (map (\(Or n _) -> n) o)),(catMaybes (bx b))) let nrdbFormat = nrdbSearch (((map (\(Ir n) -> n) i) ++ (map (\(Or n _) -> n) o)),(catMaybes (bx b)))
let nrdbIn = nrdbSearch (pdi,catMaybes [bbi]) let nrdbIn = nrdbSearch (pdi,catMaybes [bbi])
let nrdbOut = nrdbSearch (pdo,catMaybes [bbo]) let nrdbOut = nrdbSearch (pdo,catMaybes [bbo])
-- Build Site
setTitle "Protocol Seven" setTitle "Protocol Seven"
addScriptRemote "https://fonts.googleapis.com/css?family=Inconsolata" addScriptRemote "https://fonts.googleapis.com/css?family=Inconsolata"
toWidget $(whamletFile "header.hamlet") toWidget $(whamletFile "header.hamlet")

View File

@ -7,8 +7,8 @@ nrdbSearch :: ([DataPack], [BigBox]) -> String
nrdbSearch (d, b) = nrdbSearch (d, b) =
"https://netrunnerdb.com/find/?q=e%3A" ++ "https://netrunnerdb.com/find/?q=e%3A" ++
intercalate "%7C" ( intercalate "%7C" (
(map nrdbPackCodes d) ++ sort ((map nrdbPackCodes d) ++
(map nrdbBoxCodes b) (map nrdbBoxCodes b))
) )
nrdbPackCodes :: DataPack -> String nrdbPackCodes :: DataPack -> String

View File

@ -20,5 +20,5 @@ monthsSince (Ts d1 m1 y1) (Ts d2 m2 y2)
t1 = Ts d1 m1 y1 t1 = Ts d1 m1 y1
t2 = Ts d2 m2 y2 t2 = Ts d2 m2 y2
toTS :: (Integer, Int, Int) -> Timestamp toTS :: (Integer, Integer, Integer) -> Timestamp
toTS (y,m,d) = Ts (fromIntegral d) (fromIntegral m) y toTS (y,m,d) = Ts d m y

View File

@ -3,7 +3,7 @@ module Utils where
inBoth :: (Eq a) => [a] -> [a] -> [a] inBoth :: (Eq a) => [a] -> [a] -> [a]
inBoth x y = filter (\n -> n `elem` y) x inBoth x y = filter (\n -> n `elem` y) x
showMonth :: Int -> String showMonth :: Integer -> String
showMonth 1 = "January" showMonth 1 = "January"
showMonth 2 = "February" showMonth 2 = "February"
showMonth 3 = "March" showMonth 3 = "March"

View File

@ -1,6 +1,5 @@
<section class="rotation"> <section class="rotation">
<h2>Format for #{showMonth month} #{year}: <h2>Format for #{showMonth month} #{year}: <a href=#{nrdbFormat}>NRDB</a>
<a href=#{nrdbFormat}>Click Here for NetrunnerDB
<div class="flexboxcontainer"> <div class="flexboxcontainer">
<div class="rotationLeft"> <div class="rotationLeft">
<h3>Evergreen: <h3>Evergreen:
@ -19,16 +18,14 @@
<div class="flexboxcontainer"> <div class="flexboxcontainer">
$maybe (pin, pout, pbin, pbout) <- pr $maybe (pin, pout, pbin, pbout) <- pr
<div class="upcomingIn"> <div class="upcomingIn">
<h3>In: <h3>In: <a href=#{nrdbIn}>NRDB</a>
<a href=#{nrdbIn}>Click Here for NetrunnerDB
<ul> <ul>
$maybe pbbin <- pbin $maybe pbbin <- pbin
<li>+ #{show pbbin} <li>+ #{show pbbin}
$forall indp <- pin $forall indp <- pin
<li>+ #{show indp} <li>+ #{show indp}
<div class="upcomingOut"> <div class="upcomingOut">
<h3>Out: <h3>Out: <a href=#{nrdbOut}>NRDB</a>
<a href=#{nrdbOut}>Click Here for NetrunnerDB
<ul> <ul>
$maybe pbbout <- pbout $maybe pbbout <- pbout
<li>- #{show pbbout} <li>- #{show pbbout}

View File

@ -51,6 +51,14 @@ p,h2,h3 {
padding: 10px; padding: 10px;
} }
a:link {
color: cornflowerblue
}
a:visited {
color: mediumpurple
}
ul { ul {
text-align: initial; text-align: initial;
margin: 10px; margin: 10px;