Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Created August 1, 2014 13:10
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save snoyberg/8d85d41c5b4d0da002ae to your computer and use it in GitHub Desktop.
Save snoyberg/8d85d41c5b4d0da002ae to your computer and use it in GitHub Desktop.
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
import Yesod
import Yesod.OptionalSubsite
import Yesod.Static
data HelloWorld = HelloWorld
getStatic _ = OptionalSubsite Nothing
mkYesod "HelloWorld" [parseRoutes|
/ HomeR GET
/static StaticR OptionalSubsite-Static getStatic
|]
instance Yesod HelloWorld
getHomeR :: Handler Html
getHomeR = defaultLayout [whamlet|Hello World!|]
main :: IO ()
main = warp 3000 HelloWorld
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Yesod.OptionalSubsite where
import Yesod.Core
import Yesod.Core.Types
newtype OptionalSubsite a = OptionalSubsite (Maybe a)
instance RenderRoute a => RenderRoute (OptionalSubsite a) where
newtype Route (OptionalSubsite a) = OptionalRoute (Route a)
renderRoute (OptionalRoute x) = renderRoute x
deriving instance Eq (Route a) => Eq (Route (OptionalSubsite a))
deriving instance Show (Route a) => Show (Route (OptionalSubsite a))
deriving instance Read (Route a) => Read (Route (OptionalSubsite a))
instance ParseRoute a => ParseRoute (OptionalSubsite a) where
parseRoute = fmap OptionalRoute . parseRoute
instance (MonadHandler m, YesodSubDispatch a m) => YesodSubDispatch (OptionalSubsite a) m where
yesodSubDispatch subEnv req =
case msub of
Nothing -> ysreParentRunner subEnv notFound (ysreParentEnv subEnv) Nothing req
Just sub -> flip yesodSubDispatch req subEnv
{ ysreGetSub = const sub
, ysreToParentRoute = ysreToParentRoute subEnv . OptionalRoute
}
where
OptionalSubsite msub = ysreGetSub subEnv $ yreSite $ ysreParentEnv subEnv
@m1-s
Copy link

m1-s commented Feb 17, 2022

I have stumbled upon this gist after 8 years. How can I specify the route to my OptionalSubsite in hamlet? I need the route to some file but I can not depend on template Haskell functions such as staticFiles to generate the routes because the served folder is optional.

$if servingOptionalSite
    <a href="@{StaticR (routeToSomeFile)}">Docs

@snoyberg
Copy link
Author

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment