{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} module Generics.Regular.Transformations.RewriteRules ( Transform, Transformation, apply ) where import Generics.Regular import Generics.Regular.Rewriting import Generics.Regular.Zipper import Control.Monad ( foldM ) -------------------------------------------------------------------------------- -- Patch -------------------------------------------------------------------------------- -- Basically, a class synonym class (Regular a, Rewrite a, Zipper (PF a)) => Transform a instance Transform a => Rewrite a -- An edit is a list of: type Transformation a = [ ( Loc a -> Maybe (Loc a) -- A path to the location to edit , Rule a) ] -- The rewrite rule to apply there -- Patching is terribly simple: at the given locations, apply all the rules, -- then exit the zipper. apply :: forall a. (Transform a) => Transformation a -> a -> Maybe a apply rs = fmap leave . flip (foldM appRule) rs . enter where appRule a (l,r) = l a >>= updateM (rewriteM r)