Open danclien opened 7 years ago
As in the linked issue, we cannot validate the contents of type-level strings, aka Symbol
s. We could have a run-time inspection / validation (it's possible, and not too hard), but nobody have done one yet.
We can have that runtime check at compile time with TH. On Mon, 19 Jun 2017 at 19:59, Oleg Grenrus notifications@github.com wrote:
As in the linked issue, we cannot validate the contents of type-level strings, aka Symbols. We could have a run-time inspection / validation (it's possible, and not too hard), but nobody have done one yet.
— You are receiving this because you are subscribed to this thread. Reply to this email directly, view it on GitHub https://github.com/haskell-servant/servant/issues/770#issuecomment-309502273, or mute the thread https://github.com/notifications/unsubscribe-auth/AAp59hhDsUcjND67OkzRaUxDLZ1VWWeqks5sFqj3gaJpZM4N-ZFD .
Wai issue to make a run-time check https://github.com/yesodweb/wai/issues/628
@k-bx that's too runtime :) in Servant we have static information about header names, so we can perform the check before we run the server. The only problem stopping us from performing this check at compile time is that we can't process type-level Symbol
s like we can process String
s. However with some simple TH it should be possible to perform that check at compile time.
I disagree with simple in "with some simple TH*, I'd like to see the proof to that argument ;)
@phadej the only "not simple" thing is that you have to place your check in a separate module and, well, come up with a descriptive error message 😉
Here's "complex" TH code to perform arbitrary run-time check at compile-time:
module Check where
import Language.Haskell.TH
-- | Perform a run-time check of a constant value at compile-time.
checkAtCompileTime :: Either String a -> Q [Dec]
checkAtCompileTime (Left msg) = fail msg
checkAtCompileTime _ = return []
Here's a sample type-level string check that we'd like to perform at compile time, but can't do normally:
{-# LANGUAGE DataKinds #-}
module Types where
import Data.Proxy
import GHC.TypeLits
-- | A type-level string.
-- We can't inspect it on the type-level.
type Name = "Too Many Words"
-- | A term-level value of Name.
-- We can inspect it, but normally at run-time only.
name :: String
name = symbolVal (Proxy :: Proxy Name)
-- | Check that a string consists of exactly one word.
--
-- >>> singleWord "bird"
-- Right "bird"
--
-- >>> singleWord "too many words"
-- Left "expected one word, but got `too many words'"
singleWord :: String -> Either String String
singleWord s = case words s of
[w] -> Right w
_ -> Left $ "expected one word, but got `" ++ s ++ "'"
Due to GHC stage restrictions we have to perform a compile-time check in a separate module:
{-# LANGUAGE TemplateHaskell #-}
import Check
import Types
-- performing a run-time check for a type-level string at compile-time
-- feels like dark magic :)
checkAtCompileTime (singleWord name)
And here's what you get when you try to compile this (or load in GHCi):
>>> :l test.hs
test.hs:8:1: error: expected one word, but got `Too Many Words'
I'm not sure if there's a type-safe way of enforcing valid HTTP header names, but
servant
currently allows header names to have spaces which can break break Chrome.More information can be found in a
wai
issue at https://github.com/yesodweb/wai/issues/628.Example