Created
December 3, 2017 20:14
-
-
Save natefaubion/5856886ab7ca079a1c51e9c451d797b2 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import Prelude | |
import Data.Generic.Rep | |
import Type.Proxy | |
import Data.Symbol (SProxy(..), reflectSymbol, class IsSymbol) | |
import Type.Equality | |
import Control.Alternative | |
import Control.Monad.Eff.Console (logShow) | |
import TryPureScript | |
class ConstructorNames a where | |
names :: forall f. Alternative f => Proxy a -> f String | |
instance namesSum :: (ConstructorNames a, ConstructorNames b) => ConstructorNames (Sum a b) where | |
names _ = names (Proxy :: Proxy a) <|> names (Proxy :: Proxy b) | |
instance namesConstructor :: (TypeEquals tail (Argument a), IsSymbol name) => ConstructorNames (Constructor name tail) where | |
names _ = pure (reflectSymbol (SProxy :: SProxy name)) | |
instance namesNoConstructors :: ConstructorNames NoArguments where | |
names _ = empty | |
data Test = Bar Int | Baz String | |
derive instance genericTest :: Generic Test _ | |
toRep :: forall from to. Generic from to => Proxy from -> Proxy to | |
toRep _ = Proxy | |
testNames :: Array String | |
testNames = names (toRep (Proxy :: Proxy Test)) | |
main = render =<< withConsole (logShow testNames) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment