Skip to content

Instantly share code, notes, and snippets.

@kristoff3r
Created April 4, 2018 15:01
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 kristoff3r/bccc8b33d03631b8f193c00c6111666d to your computer and use it in GitHub Desktop.
Save kristoff3r/bccc8b33d03631b8f193c00c6111666d to your computer and use it in GitHub Desktop.
Run with stack --resolver lts-11.1 ghci --package servant servant-server servant-lucid text network-uri
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Data.Monoid ((<>))
import qualified Data.Text as T
import Data.Text (Text)
import Network.URI (uriToString)
import Servant
import Servant.HTML.Lucid
import Servant.Utils.Links (safeLink)
mkLink :: (IsElem a Routes, HasLink a) => Proxy a -> MkLink a
mkLink = safeLink (Proxy :: Proxy Routes)
routeToText :: (IsElem a Routes, HasLink a, ToHttpApiData (MkLink a))
=> Proxy a
-> Text
routeToText = toUrlPiece . routeToURI
routeToURI :: (IsElem a Routes, HasLink a) => Proxy a -> MkLink a
routeToURI = safeLink (Proxy :: Proxy Routes)
type ShowProfileR = "user" :> Capture "profileName" Text :> Get '[HTML] (Text)
type ShowProfilesR = "user" :> Get '[HTML] (Text)
type Routes = ShowProfileR :<|> ShowProfilesR
example :: Text
example = routeToText (Proxy :: Proxy ShowProfilesR)
example2 :: Text
example2 = toUrlPiece $ safeLink (Proxy :: Proxy Routes) (Proxy :: Proxy ShowProfileR) "username"
-- Does not work
--example3 :: Text
--example3 = routeToText (Proxy :: Proxy ShowProfileR) "username"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment