Skip to content

Instantly share code, notes, and snippets.

@myuon
Created July 17, 2015 05:07
Show Gist options
  • Save myuon/dba69af28eba338c620f to your computer and use it in GitHub Desktop.
Save myuon/dba69af28eba338c620f to your computer and use it in GitHub Desktop.
Recordを剥がして連結しただけ
{-# LANGUAGE TypeFamilies, DataKinds, TypeOperators, PolyKinds, UndecidableInstances, TemplateHaskell, FlexibleContexts, AllowAmbiguousTypes #-}
import Control.Lens
import Data.Extensible
import Data.Extensible.Internal
import GHC.TypeLits
type family GetList r :: [Assoc Symbol *] where
GetList (h :* xs) = xs
type family UnionRecord xs ys :: * where
UnionRecord xs ys = Record (GetList xs ++ GetList ys)
mkField "name weight price description featured quantity"
type Stock0 = Record '[
"name" :> String
, "weight" :> Float]
type Stock1 c = Record '[
"price" :> c
, "featured" :> Bool
, "description" :> String
, "quantity" :> Int]
type Stock c = UnionRecord Stock0 (Stock1 c)
s0 :: Num c => Stock c
s0 = name @= "DA-192H"
<: weight @= 260
<: price @= 120
<: featured @= True
<: description @= "High-quality (24bit 192kHz), lightweight portable DAC"
<: quantity @= 20
<: Nil
s1 :: Num c => Stock c
s1 = shrinkAssoc
$ name @= "HHP-150"
<: featured @= False
<: description @= "Premium wooden headphone"
<: price @= 330
<: quantity @= 55
<: weight @= 200
<: Nil
s2 :: Record '["name" :> Int, "name" :> String]
s2 = name @= 100 <: name @= "hogehoge" <: Nil
printSummary :: (Associate "name" String s, Associate "description" String s) => Record s -> IO ()
printSummary s = putStrLn $ view name s ++ ": " ++ view description s
main = do
printSummary s0
printSummary s1
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment