Skip to content

Instantly share code, notes, and snippets.

@mitchellvitez
Last active July 15, 2021 13:55
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 mitchellvitez/347ec82742b5c202ce843ccc81f7e3a8 to your computer and use it in GitHub Desktop.
Save mitchellvitez/347ec82742b5c202ce843ccc81f7e3a8 to your computer and use it in GitHub Desktop.
quasiquoter for compile-time checks without TH splices
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE DeriveLift #-}
module Email where
import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Language.Haskell.TH.Syntax (Lift, lift, Q, Exp)
-- don't expose this constructor
newtype Email = Email String
deriving (Show, Lift)
-- do expose this smart constructor
mkEmail :: String -> Maybe Email
mkEmail email =
if isValidEmail email then Just (Email email) else Nothing
where
-- you'd want this to check more conditions
isValidEmail email = '@' `elem` email
email :: QuasiQuoter
email =
QuasiQuoter
{ quoteExp = \s ->
case mkEmail s of
Nothing -> fail $ "`" <> show s <> "` is not a valid email"
Just email -> lift email
, quotePat = error "email is not a pattern"
, quoteDec = error "email is not a declaration"
, quoteType = error "email is not a type"
}
-- usage:
--
-- {-# LANGUAGE QuasiQuotes #-} -- you just need QuasiQuotes
-- [email|test@test.com|] -- then use this as a compile-time-checked expression
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment