module SAI.Data.Generics.Shape.SYB (
Homo ,
Hetero ,
Bi ,
Shape ,
HomoM ,
BiM ,
#if USE_DATA_TREE
Rose ,
#else
Rose(..) ,
#endif
ghom ,
ghomK ,
ghomDyn ,
ghomBi ,
unGhomDyn ,
unGhomBi ,
#if 1
biToHomo ,
biToHetero ,
#else
biToHomo_forgetful ,
biToHetero_faithful ,
#endif
heteroToBi ,
liftHomoM ,
liftBiM ,
unliftHomoM ,
unliftBiM ,
gempty ,
grefine ,
gaccum ,
#if 0
#endif
shapeOf ,
sizeOf ,
symmorphic ,
(~~) ,
weightedShapeOf ,
weightedRose ,
weightedRoseJust ,
sizeOfRose ,
zipRose ,
unzipRose ,
zipBi ,
unzipBi ,
zip ,
unzip ,
showHomo ,
showHomoM ,
showAsParens ,
showAsParensBool ,
showAsParensEnriched ,
showAsParensEnrichedM ,
showDyn ,
showHetero ,
showBi ,
#if USE_DATA_TREE
Tree(Node) , Forest ,
#else
toDataTree ,
fromDataTree ,
#endif
) where
import Data.Generics.Aliases ( GenericQ )
import Data.Generics.Aliases ( mkQ )
import Data.Data ( Data, gmapQ )
import Data.Dynamic
import Data.Maybe
#if USE_DATA_TREE
import Data.Tree ( Tree(Node), Forest )
#else
import qualified Data.Tree ( Tree(Node) )
#endif
import Prelude hiding ( zip, unzip, zipWith )
import qualified Prelude as P ( zip, unzip, zipWith )
import Control.Applicative ( (<*>) )
import Control.Applicative ( Applicative )
import Debug.Trace ( trace )
type Homo r = Rose r
type Hetero = Homo Dynamic
type Bi r = Homo (Dynamic, r)
type Shape = Homo ()
type HomoM r = Homo (Maybe r)
type BiM r = Bi (Maybe r)
#if USE_DATA_TREE
type Rose = Data.Tree.Tree
#else
data Rose r = Node r [Rose r] deriving Functor
type Tree = Rose
instance Show r => Show (Rose r) where
show = show' 0
where show' n (Node r chs) =
indent n ++ show r ++ "\n"
++ concatMap (show' (1+n)) chs
where indent n = replicate (2*n) ' '
instance Eq r => Eq (Rose r) where
(==) = eq
where
eq (Node r []) (Node r' []) = r == r'
eq (Node _ []) (Node _ _) = False
eq (Node _ _) (Node _ []) = False
eq (Node r chs) (Node r' chs')
= r == r' && and (zipWith eq chs chs')
#endif
showHomo :: Show r => Rose r -> String
showHomo = show' 0
where show' n (Node r chs) =
indent n ++ show r ++ "\n"
++ concatMap (show' (1+n)) chs
where indent n = concat $ replicate n "| "
showHomoM :: Show r => Rose (Maybe r) -> String
showHomoM = show' 0
where show' n (Node mr chs) =
( case mr of
Nothing -> indent n ++ "\n"
Just r -> indent n ++ show r ++ "\n"
) ++ concatMap (show' (1+n)) chs
where indent n = concat $ replicate n "| "
ghom :: forall r d. Data d => GenericQ r -> d -> Homo r
ghom f x = foldl k b (gmapQ (ghom f) x)
where
b = Node (f x) []
k (Node r chs) nod = Node r (chs++[nod])
ghomK :: forall r d. Data d =>
(r -> r -> r)
-> GenericQ r
-> d
-> Homo r
ghomK k f x = foldl k' b (gmapQ (ghomK k f) x)
where
b = Node (f x) []
k' (Node r chs) nod@(Node r' _) = Node (r `k` r') (chs++[nod])
#if 1
ghomDyn :: forall d. Data d => d -> Hetero
ghomDyn x = foldl k b (gmapQ ghomDyn x)
where
b = Node (toDyn x) []
k (Node r chs) nod = Node r (chs++[nod])
#else
ghomDyn :: forall r d. (Typeable r, Data d) => GenericQ r -> d -> Hetero
ghomDyn f x = foldl k b (gmapQ (ghomDyn f) x)
where
b = Node (toDyn (x, f x)) []
k (Node r chs) nod = Node r (chs++[nod])
#endif
ghomBi :: forall r d. Data d => GenericQ r -> d -> Bi r
#if 1
ghomBi f x = zipRose (ghomDyn x) $ ghom f x
#else
ghomBi f x = foldl k b (gmapQ (ghomBi f) x)
where
b = Node (toDyn x, f x) []
k (Node r chs) nod = Node r (chs++[nod])
#endif
unGhomDyn :: Typeable a => Hetero -> a
unGhomDyn (Node xd chs) = fromJust $ fromDynamic xd
unGhomBi :: Typeable a => Bi r -> a
unGhomBi (Node (xd,r) chs) = fromJust $ fromDynamic xd
#if 1
biToHomo :: Bi r -> Homo r
biToHomo (Node (_,r) chs) = Node r (map biToHomo chs)
biToHetero :: Bi r -> Hetero
biToHetero (Node (d,_) chs) = Node d (map biToHetero chs)
#else
biToHomo_forgetful :: Bi r -> Homo r
biToHomo_forgetful (Node (_,r) chs) = Node r (map biToHomo_forgetful chs)
biToHetero_faithful :: Bi r -> Hetero
biToHetero_faithful (Node (d,_) chs) = Node d (map biToHetero_faithful chs)
#endif
heteroToBi :: forall r d.(Data d,Typeable d,Typeable r) =>
r
-> (d -> r)
-> Hetero -> Bi r
heteroToBi z f (Node dc chs) = Node (dc, fx) chs'
where
chs' = map (heteroToBi z f) chs
fg = mkQ z f :: GenericQ r
fx | isNothing mrc = z
| otherwise = fg rc
mrc = fromDynamic dc :: Maybe d
rc = fromJust mrc
liftHomoM :: Homo r -> HomoM r
liftHomoM = fmap Just
liftBiM :: Bi r -> BiM r
liftBiM (Node (d,r) chs) = Node (d,Just r) $ map liftBiM chs
unliftHomoM :: r -> HomoM r -> Homo r
unliftHomoM = fmap . flip maybe id
unliftBiM :: r -> BiM r -> Bi r
unliftBiM z (Node (d,mr) chs) = Node (d,r) $ map (unliftBiM z) chs
where
r | isNothing mr = z
| otherwise = fromJust mr
shapeOf :: forall d. Data d => d -> Shape
shapeOf = ghom (const ())
sizeOf :: forall d. Data d => d -> Int
sizeOf = sizeOfRose . shapeOf
symmorphic :: forall d1 d2. (Data d1,Data d2) => d1 -> d2 -> Bool
#if 1
symmorphic x y = shapeOf x == shapeOf y
#else
symmorphic (Node v1 []) (Node v2 []) = True
symmorphic (Node v1 []) (Node v2 _) = False
symmorphic (Node v1 _) (Node v2 []) = False
symmorphic (Node v1 chs1) (Node v2 chs2)
= and $ P.zipWith symmorphic chs1 chs2
#endif
(~~) :: forall d1 d2. (Data d1,Data d2) => d1 -> d2 -> Bool
(~~) = symmorphic
sizeOfRose :: Rose a -> Int
sizeOfRose (Node _ chs) = 1 + sum (map sizeOfRose chs)
zipRose :: Rose r -> Rose s -> Rose (r,s)
#if 0
zipRose = zip
#else
zipRose (Node v1 []) (Node v2 []) = Node (v1,v2) []
zipRose (Node v1 []) (Node v2 _) = error "zipRose: differently shaped arguments"
zipRose (Node v1 _) (Node v2 []) = error "zipRose: differently shaped arguments"
zipRose (Node v1 chs1) (Node v2 chs2) = Node (v1,v2) $ P.zipWith zipRose chs1 chs2
#endif
#if 1
#if 1
zip :: (Applicative f, Functor f) => (f a, f b) -> f (a,b)
zip (fa, fb) = fmap (\x -> (\y -> (x,y))) fa <*> fb
#else
zip :: (Applicative f, Functor f) => f a -> f b -> f (a,b)
zip fa fb = fmap (\x -> (\y -> (x,y))) fa <*> fb
#endif
#if 0
zipWith :: Functor f => (a->b->c) -> f a -> f b -> f c
zipWith f fa fb = (fmap (\x -> f x) fa) ...
#else
zipWith :: (Applicative f, Functor f) => (a->b->c) -> f a -> f b -> f c
zipWith f fa fb = fmap (\x -> (\y -> f x y)) fa <*> fb
#endif
unzip :: Functor f => f (a,b) -> (f a, f b)
unzip fab = (fmap (\ (x,y) -> x) fab, fmap (\ (x,y) -> y) fab)
#endif
#if 0
#elif 0
unzipRose :: Rose (r, s) -> (Rose r, Rose s)
unzipRose rtree = (left,right)
where
left = fmap (\(x,y) -> x) rtree
right = fmap (\(x,y) -> y) rtree
#elif 1
unzipRose :: Rose (r, s) -> (Rose r, Rose s)
unzipRose (Node (x,y) ns) = (Node x xns, Node y yns)
where
(xns,yns) = unzip $ map unzipRose ns
#elif 0
unzipRose :: Rose (r, s) -> (Rose r, Rose s)
unzipRose (Node (v1,v2) []) = (Node v1 [], Node v2 [])
unzipRose (Node (v1,v2) chs) = Node (v1,v2) $ map unzipRose chs
unzipRose' :: Rose (r, s) -> Rose r -> Rose s -> (Rose r, Rose s)
unzipRose' (Node (v1,v2) []) acc_r acc_s = (acc_r,acc_s)
unzipRose' (Node (v1,v2) chs) acc_r acc_s = map unzipRose chs
#endif
zipBi :: Bi r -> Bi s -> Bi (r,s)
zipBi (Node (d,v1) []) (Node (_,v2) []) = Node (d,(v1,v2)) []
zipBi (Node (d,v1) []) (Node (_,v2) _) = error "zipBi: differently shaped arguments"
zipBi (Node (d,v1) _) (Node (_,v2) []) = error "zipBi: differently shaped arguments"
zipBi (Node (d,v1) chs1) (Node (_,v2) chs2) = Node (d,(v1,v2)) $ zipWith zipBi chs1 chs2
unzipBi :: Bi (r, s) -> (Bi r, Bi s)
unzipBi (Node (d,(x,y)) ns) = (Node (d,x) xns, Node (d,y) yns)
where
(xns,yns) = unzip $ map unzipBi ns
weightedRoseJust :: Rose (Maybe r) -> Rose (Maybe r, Int)
weightedRoseJust (Node Nothing []) = Node (Nothing,0) []
weightedRoseJust (Node (Just v) []) = Node (Just v,1) []
weightedRoseJust (Node v chs) = Node (v,n) chs'
where
chs' = map weightedRoseJust chs
n = sum $ map (\ (Node (_,m) _) -> m) chs'
weightedShapeOf :: forall d. Data d => d -> Homo Int
weightedShapeOf = ghomK (+) (const 1)
weightedRose :: Rose r -> Rose (r, Int)
weightedRose (Node r chs) = foldl k' b (map weightedRose chs)
where
k = (\ (r,w) (r',w') -> (r,w+w'))
f = (\ r -> (r,1))
b = Node (r,1) []
k' (Node rw chs) nod@(Node rw' _) = Node (rw `k` rw') (chs++[nod])
showAsParens :: Homo r -> String
showAsParens (Node _ chs) = "(" ++ concatMap showAsParens chs ++ ")"
showAsParensBool :: Homo Bool -> String
showAsParensBool (Node r chs) = "(" ++ (if r then "*" else ".") ++ concatMap showAsParensBool chs ++ ")"
showAsParensEnriched :: Show r => Homo r -> String
showAsParensEnriched (Node r chs) = "(" ++ show r ++ concatMap showAsParensEnriched chs ++ ")"
showAsParensEnrichedM :: Show r => HomoM r -> String
showAsParensEnrichedM (Node Nothing chs) = "(" ++ concatMap showAsParensEnrichedM chs ++ ")"
showAsParensEnrichedM (Node (Just r) chs) = "(" ++ show r ++ concatMap showAsParensEnrichedM chs ++ ")"
#if 0
#elif 0
showDyn :: Dynamic -> String
showDyn xd
| test mx (undefined::Int) = show (fromJust mx::Int)
| test mx (undefined::[Int]) = show (fromJust mx::[Int])
| test mx (undefined::[[Int]]) = show (fromJust mx::[[Int]])
| otherwise = show xd
where
test m val = isJust m && typeOf (fromJust m) == typeOf val
mx = fromDynamic xd
#elif 1
showDyn :: Dynamic -> String
showDyn xd
| test mx_Int (undefined::Int) = show (fromJust mx_Int::Int)
| test mx_LInt (undefined::[Int]) = show (fromJust mx_LInt::[Int])
| test mx_LLInt (undefined::[[Int]]) = show (fromJust mx_LLInt::[[Int]])
| otherwise = show xd
where
test mx val = isJust mx && typeOf (fromJust mx) == typeOf val
mx_Int = fromDynamic xd
mx_LInt = fromDynamic xd
mx_LLInt = fromDynamic xd
#else
showDyn :: Dynamic -> String
showDyn xd
| isNothing mx = show xd
| otherwise = show x
where
mx = fromDynamic xd :: (Show a,Typeable a) => Maybe a
x = fromJust mx
#endif
showHetero :: Hetero -> String
showHetero = showHetero' 0
where
showHetero' n (Node d chs)
= indent n ++ showDyn d ++ "\n"
++ concatMap (showHetero' (1+n)) chs
where
indent n = replicate (2*n) ' '
showBi :: Show r => Bi r -> String
showBi = showBi' 0
where
showBi' n (Node (d,r) chs)
= indent n ++ "(" ++ showDyn d ++ ", " ++ show r ++ ")" ++ "\n"
++ concatMap (showBi' (1+n)) chs
where
indent n = replicate (2*n) ' '
#if ! USE_DATA_TREE
#if 1
toDataTree :: Rose a -> Data.Tree.Tree a
toDataTree (Node v chs) = Data.Tree.Node v $ map toDataTree chs
#else
toDataTree :: forall a. (Typeable a, Rose a) => Rose a -> Data.Tree.Tree a
toDataTree = fmap (\v -> fromJust $ cast v :: Data.Tree.Tree a)
#endif
fromDataTree :: Data.Tree.Tree a -> Rose a
fromDataTree (Data.Tree.Node v chs) = Node v $ map fromDataTree chs
#endif
gempty :: forall r d. (Typeable r,Data d) => d -> BiM r
gempty = ghomBi (mkQ Nothing id)
grefine :: forall r d. (Typeable r,Data d,Typeable d) => (d -> Maybe r) -> BiM r -> BiM r
grefine f x = x'
where
f' = f
fg = mkQ Nothing f' :: d -> Maybe r
x' = grefine' x
where
grefine' (Node (xd,mr) chs) = x'
where
x' = Node (xd,r') $ map grefine' chs
md = fromDynamic xd :: Maybe d
r' | isNothing md = Nothing
| isNothing mr = fg $ fromJust md
| otherwise = error "grefine: multiple updates attempted at a node"
#if 0
Node (xd,mr) chs = x
x' = Node (xd,r') $ map grefine chs
r' | isNothing mr = fg $ fromJust $ (fromDynamic xd :: Maybe d)
| otherwise = error "grefine: multiple updates attempted at a node"
#endif
#if 0
grefineG :: forall r d. (Typeable r,Data d,Typeable d) => (d -> Maybe r) -> BiM r -> BiM r
grefineG fg x = x'
where
x' = grefine' x
where
grefine' (Node (xd,mr) chs) = x'
where
x' = Node (xd,r') $ map grefine' chs
md = fromDynamic xd :: Maybe d
r' | isNothing md = Nothing
| isNothing mr = fg $ fromJust md
| otherwise = error "grefine: multiple updates attempted at a node"
#endif
gaccum :: forall r d. (Typeable r,Data d,Typeable d) =>
(r -> r -> r) -> (d -> Maybe r) -> BiM r -> BiM r
gaccum k f x = x'
where
fg = mkQ Nothing f :: d -> Maybe r
x' = gaccum' x
where
gaccum' (Node (xd,mr) chs) = x'
where
md = fromDynamic xd :: Maybe d
r = fromJust mr
mr_ = fg $ fromJust md
r_ = fromJust mr_
#if 0
#elif 1
mr' | isNothing md = mr
| isNothing mr_ = mr
| isNothing mr = mr_
| otherwise = Just $ r `k` r_
#elif 0
mr' | isNothing md = trace "*1*" $ mr
| isNothing mr_ = trace "*2*" $ mr
| isNothing mr = trace "*3*" $ mr_
| otherwise = trace "*4*" $ Just $ r `k` r_
#elif 0
mr' | isNothing md = Nothing
| isNothing mr_ = Nothing
| isNothing mr = mr_
| otherwise = Just $ r `k` r_
#endif
x' = Node (xd,mr') $ map gaccum' chs