[Haskell-cafe] Need help with scrap-your-boilerplate
Roman Cheplyaka
roma at ro-che.info
Mon Oct 6 19:08:16 UTC 2014
On 06/10/14 21:24, Michael Sperber wrote:
> Would using a different generic-programming framework help me do this
> without the unsafe stuff?
Yes. For example, using my traverse-with-class library:
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses,
FlexibleInstances, ConstraintKinds, UndecidableInstances,
ImplicitParams, OverlappingInstances #-}
import Data.Generics.Traversable
import Data.Generics.Traversable.TH
import Data.Proxy
data Foo a = Foo a
deriveGTraversable ''Foo
-- define a class around our generic operation
class Bar b where
bar :: b -> b
-- default case
instance Bar a where
bar x = x
-- Foo-specific case
instance Bar (Foo a) where
bar x = x
-- deep traversal
recursiveBar :: (Bar a, GTraversable (Rec Bar) a) => a -> a
recursiveBar x =
let ?c = Proxy :: Proxy Bar -- traversal with the Bar dictionary
in everywhere bar x
Roman
More information about the Haskell-Cafe
mailing list