{-# LANGUAGE MultiParamTypeClasses #-}
module Data.Generics.PlateDirect
{-# DEPRECATED "Use Data.Generics.Uniplate.Direct instead" #-}
(
module Data.Generics.Biplate,
plate, plateSelf,
(|+), (|-), (|*), (||+), (||*)
) where
import Data.Generics.Biplate
type Type from to = (Str to, Str to -> from)
plate :: from -> Type from to
plate :: from -> Type from to
plate from
f = (Str to
forall a. Str a
Zero, \Str to
_ -> from
f)
(|*) :: Type (to -> from) to -> to -> Type from to
|* :: Type (to -> from) to -> to -> Type from to
(|*) (Str to
xs,Str to -> to -> from
x_) to
y = (Str to -> Str to -> Str to
forall a. Str a -> Str a -> Str a
Two Str to
xs (to -> Str to
forall a. a -> Str a
One to
y),\(Two Str to
xs (One to
y)) -> Str to -> to -> from
x_ Str to
xs to
y)
(|+) :: Biplate item to => Type (item -> from) to -> item -> Type from to
|+ :: Type (item -> from) to -> item -> Type from to
(|+) (Str to
xs,Str to -> item -> from
x_) item
y = case BiplateType item to
forall from to. Biplate from to => BiplateType from to
biplate item
y of
(Str to
ys,Str to -> item
y_) -> (Str to -> Str to -> Str to
forall a. Str a -> Str a -> Str a
Two Str to
xs Str to
ys, \(Two Str to
xs Str to
ys) -> Str to -> item -> from
x_ Str to
xs (Str to -> item
y_ Str to
ys))
(|-) :: Type (item -> from) to -> item -> Type from to
|- :: Type (item -> from) to -> item -> Type from to
(|-) (Str to
xs,Str to -> item -> from
x_) item
y = (Str to
xs,\Str to
xs -> Str to -> item -> from
x_ Str to
xs item
y)
(||*) :: Type ([to] -> from) to -> [to] -> Type from to
||* :: Type ([to] -> from) to -> [to] -> Type from to
(||*) (Str to
xs,Str to -> [to] -> from
x_) [to]
y = (Str to -> Str to -> Str to
forall a. Str a -> Str a -> Str a
Two Str to
xs ([to] -> Str to
forall a. [a] -> Str a
listStr [to]
y), \(Two Str to
xs Str to
ys) -> Str to -> [to] -> from
x_ Str to
xs (Str to -> [to]
forall a. Str a -> [a]
strList Str to
ys))
(||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from to
||+ :: Type ([item] -> from) to -> [item] -> Type from to
(||+) (Str to
xs,Str to -> [item] -> from
x_) [item]
y = case [item] -> Type [item] to
forall a to. Biplate a to => [a] -> Type [a] to
plateListDiff [item]
y of
(Str to
ys,Str to -> [item]
y_) -> (Str to -> Str to -> Str to
forall a. Str a -> Str a -> Str a
Two Str to
xs Str to
ys, \(Two Str to
xs Str to
ys) -> Str to -> [item] -> from
x_ Str to
xs (Str to -> [item]
y_ Str to
ys))
where
plateListDiff :: [a] -> Type [a] to
plateListDiff [] = [a] -> Type [a] to
forall from to. from -> Type from to
plate []
plateListDiff (a
x:[a]
xs) = (a -> [a] -> [a]) -> Type (a -> [a] -> [a]) to
forall from to. from -> Type from to
plate (:) Type (a -> [a] -> [a]) to -> a -> Type ([a] -> [a]) to
forall item to from.
Biplate item to =>
Type (item -> from) to -> item -> Type from to
|+ a
x Type ([a] -> [a]) to -> [a] -> Type [a] to
forall item to from.
Biplate item to =>
Type ([item] -> from) to -> [item] -> Type from to
||+ [a]
xs
plateSelf :: to -> Type to to
plateSelf :: to -> Type to to
plateSelf to
x = (to -> Str to
forall a. a -> Str a
One to
x, \(One to
x) -> to
x)