{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Data.ASTPath
( type HalfPath
, type ASTPath
, toList
, astPath
, AST(..)
, treePath
, terminalPath
, nullPath
, AST'(..)
) where
import GHC.Generics
type HalfPath = [String]
type ASTPath = (String, HalfPath, HalfPath)
toList :: ASTPath -> [String]
toList (t, ls, rs) = revApp ls $ t : rs
where
revApp [] ys = ys
revApp (x:xs) ys = revApp xs $ x : ys
class AST a where
{-# MINIMAL astPathWithHalf #-}
astPathWithHalf
:: a
-> String
-> ([ASTPath], [HalfPath])
default astPathWithHalf :: (Generic a, AST' (Rep a)) => a -> String -> ([ASTPath], [HalfPath])
astPathWithHalf = treePath
treePath :: forall a. (Generic a, AST' (Rep a)) => a -> String -> ([ASTPath], [HalfPath])
treePath a c = astPathWithHalf' (from a :: Rep a a) c
terminalPath :: (a -> String) -> a -> String -> ([ASTPath], [HalfPath])
terminalPath f x _ = ([], [[f x]])
nullPath :: a -> String -> ([ASTPath], [HalfPath])
nullPath _ _ = ([], [])
astPath :: AST a => a -> [ASTPath]
astPath a = fst $ astPathWithHalf a undefined
class AST' f where
astPathWithHalf' :: f a -> String -> ([ASTPath], [HalfPath])
instance AST' V1 where
astPathWithHalf' _ _ = undefined
instance AST' U1 where
astPathWithHalf' _ _ = ([], [])
instance (AST' f, AST' g) => AST' (f :+: g) where
astPathWithHalf' (L1 a) = astPathWithHalf' a
astPathWithHalf' (R1 a) = astPathWithHalf' a
instance (AST' f, AST' g) => AST' (f :*: g) where
astPathWithHalf' (a :*: b) c = (ps, hs)
where
(psa, hsa) = astPathWithHalf' a c
(psb, hsb) = astPathWithHalf' b c
ps = psa ++ psb ++ [ (c, p1, p2) | p1 <- hsa, p2 <- hsb ]
hs = hsa ++ hsb
instance (AST a) => AST' (K1 i a) where
astPathWithHalf' (K1 a) = astPathWithHalf (a :: a)
instance (AST' f, Datatype d) => AST' (D1 d f) where
astPathWithHalf' (M1 a) = astPathWithHalf' a
instance (AST' f, Constructor c) => AST' (C1 c f) where
astPathWithHalf' (M1 a) _ = (ps, map (c:) hs)
where
(ps, hs) = astPathWithHalf' a c
c = conName (undefined :: t c f a)
instance (AST' f, Selector s) => AST' (S1 s f) where
astPathWithHalf' (M1 a) = astPathWithHalf' a
instance AST a => AST [a] where
astPathWithHalf [] _ = ([], [])
astPathWithHalf (x:xs) c = (ps, hs)
where
(psh, hsh) = astPathWithHalf x c
(pst, hst) = astPathWithHalf xs c
ps = psh ++ pst ++ [ (c, p1, p2) | p1 <- hsh, p2 <- hst ]
hs = hsh ++ hst