Skip to content

Commit

Permalink
Merge pull request #178 from jkachmar/reinterpret-log-deriving
Browse files Browse the repository at this point in the history
Uses generic derivation for reinterpret log example
  • Loading branch information
robrix committed Jun 13, 2019
2 parents 0e8df08 + 1cbe0be commit 2bf10ce
Showing 1 changed file with 2 additions and 17 deletions.
19 changes: 2 additions & 17 deletions examples/ReinterpretLog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@
-- structured log messages as strings.


{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
Expand Down Expand Up @@ -107,23 +108,7 @@ runApplication =
data Log (a :: Type) (m :: Type -> Type) (k :: Type)
= Log a k
deriving stock (Functor)

-- Log is a "first order" effect, so the Effect and HFunctor instance are
-- boilerplate. See https://github.com/fused-effects/fused-effects/issues/54
instance Effect (Log a) where
handle ::
Functor f
=> f ()
-> (forall x. f (m x) -> n (f x))
-> Log a m (m b)
-> Log a n (n (f b))
handle state handler =
coerce . fmap (handler . ((<$ state)))

instance HFunctor (Log a) where
hmap :: (forall x. m x -> n x) -> Log a m k -> Log a n k
hmap _ =
coerce
deriving anyclass (HFunctor, Effect)

-- Log an 'a'.
log ::
Expand Down

0 comments on commit 2bf10ce

Please sign in to comment.