Skip to content

Commit dd066a2

Browse files
committed
Add redirect from Haskell Platform to Downloads
1 parent 89d38e8 commit dd066a2

File tree

1 file changed

+14
-1
lines changed

1 file changed

+14
-1
lines changed

builder/site.hs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
--------------------------------------------------------------------------------
2-
{-# LANGUAGE TypeApplications #-}
32
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE TupleSections #-}
4+
{-# LANGUAGE TypeApplications #-}
45
import Data.Aeson
56
import qualified Data.ByteString.Lazy as BL
67
import Data.Monoid ((<>))
@@ -64,6 +65,7 @@ main = mkContext >>= \ctx -> hakyll $ do
6465
match "templates/*" $
6566
compile templateCompiler
6667

68+
version "redirects" $ createRedirects haskellPlatformRedirects
6769

6870
parseTestimonialCompiler :: Compiler (Item Testimonial)
6971
parseTestimonialCompiler = do
@@ -111,3 +113,14 @@ testimonialContext =
111113
, field "shortTestimonial" (pure . shortTestimonial . itemBody)
112114
, field "companyURL" (pure . companyURL . itemBody)
113115
]
116+
117+
haskellPlatformRedirects :: [(Identifier, String)]
118+
haskellPlatformRedirects = (, "/downloads") <$>
119+
[ "platform/index.html"
120+
, "platform/mac.html"
121+
, "platform/linux.html"
122+
, "platform/windows.html"
123+
, "platform/prior.html"
124+
, "platform/contents.html"
125+
, "platform/download.html"
126+
]

0 commit comments

Comments
 (0)