Skip to content

Instantly share code, notes, and snippets.

@teh
Last active September 29, 2016 12:14
Show Gist options
  • Save teh/829aa08fd67d0f0ce4e0494b70981791 to your computer and use it in GitHub Desktop.
Save teh/829aa08fd67d0f0ce4e0494b70981791 to your computer and use it in GitHub Desktop.
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds, PolyKinds, TypeOperators #-}
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
-- When do I need TypeApplication?
-- When I need some intermediate types that change how
-- the internal function behaves.
-- Could maybe have sth like "runAPI @MyAPI input"
import GHC.TypeLits (Symbol, KnownSymbol, symbolVal)
import Data.Proxy (Proxy(..))
-- The canonical example: `a` isn't exported so f doesn't
-- know which read instance to pick. f "True" @Bool works,
-- f "1" @Bool fails.
f :: forall a. (Read a, Show a) => String -> String
f = (show :: a -> String) . read
data a :<|> b = a :<|> b
infixr 8 :<|>
data (a :: k) :> (b :: *)
infixr 9 :>
data Const (s :: Symbol)
class PrintThing layout where
pt :: String
instance forall s a. (KnownSymbol s) => PrintThing (Const s) where
pt = symbolVal (Proxy :: Proxy s)
instance forall a b. (PrintThing a, PrintThing b) => PrintThing (a :<|> b) where
pt = (pt @a) ++ (pt @b)
-- Tests
type Test = (Const "1") :<|> (Const "2")
type Test2 = (Const "hello") :<|> (Const " yous")
hello = do
print (pt @Test)
print (pt @Test2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment