Skip to content

Instantly share code, notes, and snippets.

@aaronlevin
Created February 17, 2015 17:36
Show Gist options
  • Select an option

  • Save aaronlevin/58c09801b60eea32db71 to your computer and use it in GitHub Desktop.

Select an option

Save aaronlevin/58c09801b60eea32db71 to your computer and use it in GitHub Desktop.
Use `Data.Reflection` to deserialized type-encoded json strings into `Proxy`
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Main where
import Control.Monad
import Data.Aeson
import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as B
import Data.Proxy (Proxy(Proxy))
import Data.Reflection
import Data.Text
import GHC.TypeLits
instance KnownSymbol n => ToJSON (Proxy n) where
toJSON p = object [ "type" .= symbolVal p ]
instance KnownSymbol n => FromJSON (Proxy n) where
parseJSON (Object v) = v .: "type" >>= handleType
where
handleType (A.String s) | s == pack (reflect (Proxy :: Proxy n)) = return Proxy
handleType _ = mzero
parseJSON _ = mzero
-- | bring stringly-typed programming to the masses: encode the "foo" type in a string.
jsonString :: B.ByteString
jsonString = "{\"type\":\"foo\"}"
foo :: Maybe (Proxy "foo")
foo = decode jsonString
bar :: Maybe (Proxy "bar")
bar = decode jsonString
main :: IO ()
main = do
print foo -- prints "Just Proxy"
print bar -- prints "Nothing"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment