{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Data.Generics.PlateTypeable
{-# DEPRECATED "Use Data.Generics.Uniplate.Typeable instead" #-}
(
module Data.Generics.Biplate,
module Data.Typeable,
PlateAll(..), uniplateAll,
plate, (|+), (|-)
) where
import Data.Generics.Biplate
import Data.Generics.Uniplate.Internal.Utils
import Data.Typeable
instance (Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b where
biplate :: BiplateType a b
biplate = BiplateType a b
forall from to.
(Typeable from, Typeable to, PlateAll from to) =>
from -> Type from to
plateMore
uniplateAll :: PlateAll a b => a -> (Str b, Str b -> a)
uniplateAll :: a -> (Str b, Str b -> a)
uniplateAll = a -> (Str b, Str b -> a)
forall from to. PlateAll from to => from -> Type from to
plateAll
type Type from to = (Str to, Str to -> from)
plateMore :: (Typeable from, Typeable to, PlateAll from to) => from -> Type from to
plateMore :: from -> Type from to
plateMore from
x = Type from to
res
where
res :: Type from to
res = case Maybe to -> Maybe to -> Maybe to
forall a. a -> a -> a
asTypeOf (from -> Maybe to
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast from
x) (to -> Maybe to
forall a. a -> Maybe a
Just (to -> Maybe to) -> to -> Maybe to
forall a b. (a -> b) -> a -> b
$ Str to -> to
forall a. Str a -> a
strType (Str to -> to) -> Str to -> to
forall a b. (a -> b) -> a -> b
$ Type from to -> Str to
forall a b. (a, b) -> a
fst Type from to
res) of
Maybe to
Nothing -> from -> Type from to
forall from to. PlateAll from to => from -> Type from to
plateAll from
x
Just to
y -> (to -> Str to
forall a. a -> Str a
One to
y, \(One to
y) -> to -> from
forall a b. a -> b
unsafeCoerce to
y)
class PlateAll from to where
plateAll :: from -> Type from to
plate :: from -> Type from to
plate :: from -> Type from to
plate from
x = (Str to
forall a. Str a
Zero, \Str to
_ -> from
x)
(|+) :: (Typeable item, Typeable to, PlateAll 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 from to.
(Typeable from, Typeable to, PlateAll from to) =>
from -> Type from to
plateMore 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)
instance PlateAll Int to where plateAll :: Int -> Type Int to
plateAll Int
x = Int -> Type Int to
forall from to. from -> Type from to
plate Int
x
instance Uniplate Int where uniplate :: UniplateType Int
uniplate = UniplateType Int
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll Bool to where plateAll :: Bool -> Type Bool to
plateAll Bool
x = Bool -> Type Bool to
forall from to. from -> Type from to
plate Bool
x
instance Uniplate Bool where uniplate :: UniplateType Bool
uniplate = UniplateType Bool
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll Char to where plateAll :: Char -> Type Char to
plateAll Char
x = Char -> Type Char to
forall from to. from -> Type from to
plate Char
x
instance Uniplate Char where uniplate :: UniplateType Char
uniplate = UniplateType Char
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll Integer to where plateAll :: Integer -> Type Integer to
plateAll Integer
x = Integer -> Type Integer to
forall from to. from -> Type from to
plate Integer
x
instance Uniplate Integer where uniplate :: UniplateType Integer
uniplate = UniplateType Integer
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll Double to where plateAll :: Double -> Type Double to
plateAll Double
x = Double -> Type Double to
forall from to. from -> Type from to
plate Double
x
instance Uniplate Double where uniplate :: UniplateType Double
uniplate = UniplateType Double
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll Float to where plateAll :: Float -> Type Float to
plateAll Float
x = Float -> Type Float to
forall from to. from -> Type from to
plate Float
x
instance Uniplate Float where uniplate :: UniplateType Float
uniplate = UniplateType Float
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance PlateAll () to where plateAll :: () -> Type () to
plateAll ()
x = () -> Type () to
forall from to. from -> Type from to
plate ()
x
instance Uniplate () where uniplate :: UniplateType ()
uniplate = UniplateType ()
forall from to. PlateAll from to => from -> Type from to
uniplateAll
instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll [from] to where
plateAll :: [from] -> Type [from] to
plateAll [] = [from] -> Type [from] to
forall from to. from -> Type from to
plate []
plateAll (from
x:[from]
xs) = (from -> [from] -> [from]) -> Type (from -> [from] -> [from]) to
forall from to. from -> Type from to
plate (:) Type (from -> [from] -> [from]) to
-> from -> Type ([from] -> [from]) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ from
x Type ([from] -> [from]) to -> [from] -> Type [from] to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ [from]
xs
instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll (Maybe from) to where
plateAll :: Maybe from -> Type (Maybe from) to
plateAll Maybe from
Nothing = Maybe from -> Type (Maybe from) to
forall from to. from -> Type from to
plate Maybe from
forall a. Maybe a
Nothing
plateAll (Just from
x) = (from -> Maybe from) -> Type (from -> Maybe from) to
forall from to. from -> Type from to
plate from -> Maybe from
forall a. a -> Maybe a
Just Type (from -> Maybe from) to -> from -> Type (Maybe from) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ from
x
instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) =>
PlateAll (Either a b) to where
plateAll :: Either a b -> Type (Either a b) to
plateAll (Left a
x) = (a -> Either a b) -> Type (a -> Either a b) to
forall from to. from -> Type from to
plate a -> Either a b
forall a b. a -> Either a b
Left Type (a -> Either a b) to -> a -> Type (Either a b) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ a
x
plateAll (Right b
x) = (b -> Either a b) -> Type (b -> Either a b) to
forall from to. from -> Type from to
plate b -> Either a b
forall a b. b -> Either a b
Right Type (b -> Either a b) to -> b -> Type (Either a b) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ b
x
instance (PlateAll a to, Typeable a
,PlateAll b to, Typeable b
,Typeable to, Uniplate to) =>
PlateAll (a,b) to where
plateAll :: (a, b) -> Type (a, b) to
plateAll (a
a,b
b) = (a -> b -> (a, b)) -> Type (a -> b -> (a, b)) to
forall from to. from -> Type from to
plate (,) Type (a -> b -> (a, b)) to -> a -> Type (b -> (a, b)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ a
a Type (b -> (a, b)) to -> b -> Type (a, b) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ b
b
instance (PlateAll a to, Typeable a
,PlateAll b to, Typeable b
,PlateAll c to, Typeable c
,Typeable to, Uniplate to) =>
PlateAll (a,b,c) to where
plateAll :: (a, b, c) -> Type (a, b, c) to
plateAll (a
a,b
b,c
c) = (a -> b -> c -> (a, b, c)) -> Type (a -> b -> c -> (a, b, c)) to
forall from to. from -> Type from to
plate (,,) Type (a -> b -> c -> (a, b, c)) to
-> a -> Type (b -> c -> (a, b, c)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ a
a Type (b -> c -> (a, b, c)) to -> b -> Type (c -> (a, b, c)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ b
b Type (c -> (a, b, c)) to -> c -> Type (a, b, c) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ c
c
instance (PlateAll a to, Typeable a
,PlateAll b to, Typeable b
,PlateAll c to, Typeable c
,PlateAll d to, Typeable d
,Typeable to, Uniplate to) =>
PlateAll (a,b,c,d) to where
plateAll :: (a, b, c, d) -> Type (a, b, c, d) to
plateAll (a
a,b
b,c
c,d
d) = (a -> b -> c -> d -> (a, b, c, d))
-> Type (a -> b -> c -> d -> (a, b, c, d)) to
forall from to. from -> Type from to
plate (,,,) Type (a -> b -> c -> d -> (a, b, c, d)) to
-> a -> Type (b -> c -> d -> (a, b, c, d)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ a
a Type (b -> c -> d -> (a, b, c, d)) to
-> b -> Type (c -> d -> (a, b, c, d)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ b
b Type (c -> d -> (a, b, c, d)) to
-> c -> Type (d -> (a, b, c, d)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ c
c Type (d -> (a, b, c, d)) to -> d -> Type (a, b, c, d) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ d
d
instance (PlateAll a to, Typeable a
,PlateAll b to, Typeable b
,PlateAll c to, Typeable c
,PlateAll d to, Typeable d
,PlateAll e to, Typeable e
,Typeable to, Uniplate to) =>
PlateAll (a,b,c,d,e) to where
plateAll :: (a, b, c, d, e) -> Type (a, b, c, d, e) to
plateAll (a
a,b
b,c
c,d
d,e
e) = (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Type (a -> b -> c -> d -> e -> (a, b, c, d, e)) to
forall from to. from -> Type from to
plate (,,,,) Type (a -> b -> c -> d -> e -> (a, b, c, d, e)) to
-> a -> Type (b -> c -> d -> e -> (a, b, c, d, e)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ a
a Type (b -> c -> d -> e -> (a, b, c, d, e)) to
-> b -> Type (c -> d -> e -> (a, b, c, d, e)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ b
b Type (c -> d -> e -> (a, b, c, d, e)) to
-> c -> Type (d -> e -> (a, b, c, d, e)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ c
c Type (d -> e -> (a, b, c, d, e)) to
-> d -> Type (e -> (a, b, c, d, e)) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ d
d Type (e -> (a, b, c, d, e)) to -> e -> Type (a, b, c, d, e) to
forall item to from.
(Typeable item, Typeable to, PlateAll item to) =>
Type (item -> from) to -> item -> Type from to
|+ e
e