Skip to content

Instantly share code, notes, and snippets.

@aavogt
Last active February 9, 2016 07:40
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save aavogt/f7d875abaf504dc3bf12 to your computer and use it in GitHub Desktop.
Save aavogt/f7d875abaf504dc3bf12 to your computer and use it in GitHub Desktop.
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds, FlexibleContexts, TemplateHaskell, TypeFamilies, TypeOperators #-}
import Data.Extensible
import Data.Monoid
import Control.Monad.Identity
mkField "a b"
nilR :: Comp First (Field Identity) :* '[]
nilR = Nil
r1 = a <@=> First (Just 1)
<: b <@=> mempty
<: nilR
r2 = a <@=> First (Just 5)
<: b <@=> First (Just "x")
<: nilR
{-
>>> r1r2
Just (a @= 1 <: b @= "x" <: Nil)
-}
r1r2 = getFirst
$ hsequence
$ hzipWith (\ (Comp x) (Comp y) -> Comp (x <> y))
r1 r2
{-# LANGUAGE DataKinds, FlexibleContexts, QuasiQuotes #-}
import Data.HList.CommonMain
import Data.Monoid
-- inferred
-- r1,r2 :: Record '[Tagged "a" (First Integer), Tagged "b" (First [Char])]
r1 = hBuild (First (Just 1)) mempty
r2 = [pun| a b |] -- could use hBuild here too, but this specifies the
-- field label with their ordering
where a = First (Just 5)
b = First (Just "x")
-- inferred:
-- r12 :: Maybe (Record '[Tagged "a" Integer, Tagged "b" [Char]])
r12 = getFirst $ unlabeled hSequence $ mconcat [r1, r2]
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.TypeLits
import Data.Monoid
import Data.Proxy
import Data.Vinyl hiding ((=:))
import Data.Vinyl.Derived hiding ((=:))
-- | ideally there'd be a way to use data type like Data.Functor.Compose,
-- just like in the extensible example?
newtype ElFieldF f sa = ElFieldF { unElFieldF :: f (ElField sa) }
deriving instance Monoid (f (ElField sa)) => Monoid (ElFieldF f sa)
(=:) :: (Functor f, KnownSymbol s) => Proxy s -> f a -> Rec (ElFieldF f) '[ '(s, a) ]
_ =: v = ElFieldF (Field <$> v) :& RNil
a = Proxy :: Proxy "a"
b = Proxy :: Proxy "b"
r1 = a =: First (Just 2)
<+> mempty
r2 = a =: First (Just 5)
<+> b =: First (Just "x")
r12 = getFirst $ rtraverse unElFieldF (mconcat [r1,r2])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment