Skip to content

Commit 2e0dbe7

Browse files
committed
Add Show/Render for Data.Comp.Multi
1 parent d13a6be commit 2e0dbe7

File tree

5 files changed

+95
-5
lines changed

5 files changed

+95
-5
lines changed

.gitignore

+1
Original file line numberDiff line numberDiff line change
@@ -10,3 +10,4 @@ dummy.cabal
1010
*.mix
1111
hpcreport
1212
*.DS_Store
13+
.stack-work

compdata.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -165,6 +165,7 @@ library
165165
Data.Comp.Multi.Generic
166166
Data.Comp.Multi.Desugar
167167
Data.Comp.Multi.Projection
168+
Data.Comp.Multi.Render
168169

169170
Other-Modules: Data.Comp.SubsumeCommon
170171
Data.Comp.Derive.Equality

src/Data/Comp/Multi/Derive/Show.hs

+51-5
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE TemplateHaskell #-}
22
{-# LANGUAGE TypeOperators #-}
3+
{-# LANGUAGE FlexibleInstances #-}
34
--------------------------------------------------------------------------------
45
-- |
56
-- Module : Data.Comp.Multi.Derive.Show
@@ -17,13 +18,17 @@ module Data.Comp.Multi.Derive.Show
1718
(
1819
ShowHF(..),
1920
KShow(..),
20-
makeShowHF
21+
makeShowHF,
22+
ShowConstr(..),
23+
makeShowConstr
2124
) where
2225

2326
import Data.Comp.Derive.Utils
2427
import Data.Comp.Multi.Algebra
2528
import Data.Comp.Multi.HFunctor
2629
import Language.Haskell.TH
30+
import Data.Tree
31+
import Data.Tree.View
2732

2833
{-| Signature printing. An instance @ShowHF f@ gives rise to an instance
2934
@KShow (HTerm f)@. -}
@@ -36,9 +41,9 @@ class ShowHF f where
3641
class KShow a where
3742
kshow :: a i -> K String i
3843

39-
showConstr :: String -> [String] -> String
40-
showConstr con [] = con
41-
showConstr con args = "(" ++ con ++ " " ++ unwords args ++ ")"
44+
showConstr' :: String -> [String] -> String
45+
showConstr' con [] = con
46+
showConstr' con args = "(" ++ con ++ " " ++ unwords args ++ ")"
4247

4348
{-| Derive an instance of 'ShowHF' for a type constructor of any higher-order
4449
kind taking at least two arguments. -}
@@ -66,5 +71,46 @@ makeShowHF fname = do
6671
allVars = zipWith (filterFarg (getBinaryFArg fArg ty)) args varNs
6772
shows = listE $ map mkShow allVars
6873
conName = nameBase constr
69-
body <- [|K $ showConstr conName $shows|]
74+
body <- [|K $ showConstr' conName $shows|]
7075
return $ Clause [pat] (NormalB body) []
76+
77+
{-| Constructor printing. -}
78+
class ShowConstr f where
79+
showConstr :: KShow a => f a i -> String
80+
81+
instance KShow (K (Tree String)) where
82+
kshow (K a) = K $ showTree a
83+
84+
showCon' :: String -> [String] -> String
85+
showCon' con args = unwords $ con : filter (not.null) args
86+
87+
{-| Derive an instance of 'showConstr' for a type constructor of any first-order kind
88+
taking at least one argument. -}
89+
makeShowConstr :: Name -> Q [Dec]
90+
makeShowConstr fname = do
91+
Just (DataInfo _cxt name args' constrs _deriving) <- abstractNewtypeQ $ reify fname
92+
let args = init args'
93+
fArg = VarT . tyVarBndrName $ last args
94+
argNames = map (VarT . tyVarBndrName) (init args)
95+
complType = foldl AppT (ConT name) argNames
96+
preCond = map (mkClassP ''KShow . (: [])) argNames
97+
classType = AppT (ConT ''ShowConstr) complType
98+
constrs' <- mapM normalConExp constrs
99+
showConstrDecl <- funD 'showConstr (showConstrClauses fArg constrs')
100+
return [InstanceD Nothing preCond classType [showConstrDecl]]
101+
where showConstrClauses fArg = map (genShowConstrClause fArg)
102+
filterFarg fArg ty@(AppT ty' _) x = (fArg == ty', varE x)
103+
filterFarg fArg ty@(_) x = (fArg == ty, varE x)
104+
mkShow :: (Bool, ExpQ) -> ExpQ
105+
mkShow (isFArg, var)
106+
| isFArg = [| "" |]
107+
| otherwise = [| unK $ kshow $var |]
108+
genShowConstrClause fArg (constr, args, ty) = do
109+
let n = length args
110+
varNs <- newNames n "x"
111+
let pat = ConP constr $ map VarP varNs
112+
allVars = zipWith (filterFarg (getBinaryFArg fArg ty)) args varNs
113+
shows = listE $ map mkShow allVars
114+
conName = nameBase constr
115+
body <- [| showCon' conName $shows|]
116+
return $ Clause [pat] (NormalB body) []

src/Data/Comp/Multi/Render.hs

+36
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
{-# LANGUAGE TypeSynonymInstances #-}
3+
{-# LANGUAGE TypeOperators #-}
4+
{-# LANGUAGE RankNTypes #-}
5+
module Data.Comp.Multi.Render where
6+
7+
import Data.Comp.Multi
8+
import Data.Comp.Multi.Derive
9+
import Data.Comp.Multi.HFoldable
10+
import Data.Comp.Multi.Show()
11+
import Data.Tree (Tree (..))
12+
import Data.Tree.View
13+
14+
-- | The 'stringTree' algebra of a functor. The default instance creates a tree
15+
-- with the same structure as the term.
16+
class (HFunctor f, HFoldable f,ShowHF f,ShowConstr f) => Render f where
17+
stringTreeAlg :: Alg f (K (Tree String))
18+
stringTreeAlg f = K $ Node (showConstr f) $ fmap (\(E (K a)) -> a) $ htoList f
19+
20+
-- | Convert a term to a 'Tree'
21+
stringTree :: Render f => Term f :-> K (Tree String)
22+
stringTree = cata stringTreeAlg
23+
24+
-- | Show a term using ASCII art
25+
showTerm :: Render f => Term f :=> String
26+
showTerm = showTree . unK . stringTree
27+
28+
-- | Print a term using ASCII art
29+
drawTerm :: Render f => Term f :=> IO ()
30+
drawTerm = putStrLn . showTerm
31+
32+
-- | Write a term to an HTML file with foldable nodes
33+
writeHtmlTerm :: Render f => FilePath -> Term f :=> IO ()
34+
writeHtmlTerm file = writeHtmlTree file . fmap (\n -> NodeInfo n "") . unK . stringTree
35+
36+
$(derive [liftSum] [''Render])

src/Data/Comp/Multi/Show.hs

+6
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ module Data.Comp.Multi.Show
2626
import Data.Comp.Multi.Algebra
2727
import Data.Comp.Multi.Annotation
2828
import Data.Comp.Multi.Derive
29+
import Data.Comp.Derive.Utils (derive)
2930
import Data.Comp.Multi.HFunctor
3031
import Data.Comp.Multi.Term
3132

@@ -49,3 +50,8 @@ instance (ShowHF f, Show p) => ShowHF (f :&: p) where
4950
showHF (v :&: p) = K $ unK (showHF v) ++ " :&: " ++ show p
5051

5152
$(derive [liftSum] [''ShowHF])
53+
54+
instance (ShowConstr f, Show p) => ShowConstr (f :&: p) where
55+
showConstr (v :&: p) = showConstr v ++ " :&: " ++ show p
56+
57+
$(derive [liftSum] [''ShowConstr])

0 commit comments

Comments
 (0)