Skip to content

Instantly share code, notes, and snippets.

@monadplus
Last active October 17, 2019 05:59
Show Gist options
  • Save monadplus/82c3ab6f788cfd885724f77bf7ad9e10 to your computer and use it in GitHub Desktop.
Save monadplus/82c3ab6f788cfd885724f77bf7ad9e10 to your computer and use it in GitHub Desktop.
Associated type families
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
-- Source: "Thinking with Types" - S.Maguire
module DIY where
import Data.Kind ( Type )
import Data.Monoid ( (<>) )
import Data.Proxy ( Proxy(..) )
import GHC.TypeLits
data (x :: k1) :<< (y :: k2)
infixr 5 :<<
-- Associates to the rigth i.e (Bool :<< (Int :<< Double))
-- The way the infix operator associates is importart, otherwise the structural recursion would have a different form
class HasPrintf a where
type Printf a :: Type
format :: String -> Proxy a -> Printf a
-- To simplify things, our base case will be always a Symbol.
-- i.e. Proxy @(Int :<< " ...") will have an isntance.
-- Proxy @(".." :<< Int) will not.
instance KnownSymbol text => HasPrintf (text :: Symbol) where
type Printf text = String
format s _ = s <> symbolVal (Proxy @text)
instance (HasPrintf a, KnownSymbol text) => HasPrintf ((text :: Symbol) :<< a) where
type Printf (text :<< a) = Printf a
format s _ = format (s <> symbolVal (Proxy @text)) (Proxy @a)
instance (HasPrintf a, Show param) => HasPrintf ((param :: Type) :<< a) where
type Printf (param :<< a) = param -> Printf a
format s _ param = format (s <> show param) (Proxy @a)
printf :: HasPrintf a => Proxy a -> Printf a
printf = format ""
showSum :: Int -> Int -> String
showSum x y = printf (Proxy @(Int :<< "+" :<< Int :<< "=" :<< Int :<< "")) x y (x+y)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment