2

I've learnt that I can define my API with servant and Lucid in the following way:

type ClientAPI = 
    "users" :> Get '[HTML] (Html ()) 
    :<|> "userdata" :> Get '[HTML] (Html ())

Then if I want to add a link to one of the endpoints in my HTML, I can use "a_" function provided by Lucid, e.g.

a_ [href_ "users"] "Show users"

The problem I have with this approach is that I need to repeat the endpoint's name twice. "users" occurs both in API definition and a_ tag. As a result if I change it in one place, the other one stops working immediately.

Is there a way to define a single symbol that could be used in both places instead ? Something like:

data MySites = UserSite | UserDataSite -- potentially more

type ClientAPI' =
    UserSite :> Get '[HTML] (Html ())
    -- ......

let html =
...
   a_ [href_ UserSite] "Show users"
...
LA.27
  • 1,888
  • 19
  • 35
  • 2
    Perhaps the `safeLink` function could help. http://hackage.haskell.org/package/servant-0.16.2/docs/Servant-Links.html#v:safeLink Code that uses `safeLink` will only compile if the endpoint is an actual part of the api. This SO answer contains an example https://stackoverflow.com/a/41566105/1364288 – danidiaz Nov 24 '19 at 23:20

1 Answers1

2

If you just want to abstract over the string "user", you can do this with a type alias, and then use GHC.TypeLits.symbolVal to get the string at the value level:

{-# LANGUAGE DataKinds #-}

import Data.Proxy
import GHC.TypeLits

type UserSite = "user"

html = ... href_ (symbolVal (Proxy :: Proxy UserSite)) ...

You can also make the symbolVal call a bit shorter by defining a helper with AllowAmbiguousTypes:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

urlpath :: forall s . KnownSymbol s => String
urlpath = symbolVal (Proxy :: Proxy s)

html = ... href_ (urlpath @UserSite) ...

(I actually thought something like it was in the standard library somewhere but I can't find it.)

Ganesh Sittampalam
  • 28,821
  • 4
  • 79
  • 98