Skip to content

Commit

Permalink
Tease apart and rename bits of (Show algebra) instance. #71
Browse files Browse the repository at this point in the history
  • Loading branch information
epost committed Oct 15, 2018
1 parent f34f8df commit ce9abfd
Showing 1 changed file with 43 additions and 10 deletions.
53 changes: 43 additions & 10 deletions src/Language/Instance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ import Prelude hiding (EQ)
import Data.Set as Set
import Data.Map.Strict as Map
import Data.List hiding (intercalate)
import qualified Data.Foldable as Foldable
import Language.Common
import Language.Term as Term
import Language.Typeside as Typeside
Expand Down Expand Up @@ -97,21 +98,53 @@ sepBy (x:y ) sep = x ++ sep ++ (sepBy y sep)
sepBy' :: [Char] -> [[Char]] -> [Char]
sepBy' x y = sepBy y x

-- instance (Show var, Show ty, Show sym, Show en, Show fk, Show att, Show gen, Show sk, Show x, Show y, Eq en, Eq fk, Eq att)
-- => Show (Algebra var ty sym en fk att gen sk x y) where
-- show (Algebra sch en' nf''' repr'' ty' nf'''' repr''' teqs') =
-- "algebra\n" ++ l ++ "\ntype-algeba\n" ++ w ++ sepBy' "\n" (Prelude.map show $ Set.toList $ teqs')
-- where w = "nulls\n" ++ sepBy' "\n" (Prelude.map (\ty'' -> show ty'' ++ " (" ++ show (Set.size (ty' ty'')) ++ ") = " ++ show (Set.toList $ ty' ty'') ++ " ") (Set.toList $ Typeside.tys $ Schema.typeside sch))
-- h = Prelude.map (\en'' -> show en'' ++ " (" ++ show (Set.size (en' en'')) ++ ")\n-------------\n" ++ (sepBy' "\n" $ Prelude.map (\x -> show x ++ ": "
-- ++ (sepBy (Prelude.map (f x) $ fksFrom' sch en'') ",") ++ ", "
-- ++ (sepBy (Prelude.map (g x) $ attsFrom' sch en'') ",")) $ Set.toList $ en' en'')) (Set.toList $ Schema.ens sch)
-- l = sepBy' "\n" h
-- f x (fk,_) = show fk ++ " = " ++ (show $ aFk alg fk x )
-- g x (att,_) = show att ++ " = " ++ (show $ aAtt alg att x )
-- alg = Algebra sch en' nf''' repr'' ty' nf'''' repr''' teqs'

instance (Show var, Show ty, Show sym, Show en, Show fk, Show att, Show gen, Show sk, Show x, Show y, Eq en, Eq fk, Eq att)
=> Show (Algebra var ty sym en fk att gen sk x y) where
show (Algebra sch en' nf''' repr'' ty' nf'''' repr''' teqs') =
"algebra\n" ++ l ++ "\ntype-algeba\n" ++ w ++ sepBy' "\n" (Prelude.map show $ Set.toList $ teqs')
where w = "nulls\n" ++ sepBy' "\n" (Prelude.map (\ty'' -> show ty'' ++ " (" ++ show (Set.size (ty' ty'')) ++ ") = " ++ show (Set.toList $ ty' ty'') ++ " ") (Set.toList $ Typeside.tys $ Schema.typeside sch))
h = Prelude.map (\en'' -> show en'' ++ " (" ++ show (Set.size (en' en'')) ++ ")\n-------------\n" ++ (sepBy' "\n" $ Prelude.map (\x -> show x ++ ": "
++ (sepBy (Prelude.map (f x) $ fksFrom' sch en'') ",") ++ ", "
++ (sepBy (Prelude.map (g x) $ attsFrom' sch en'') ",")) $ Set.toList $ en' en'')) (Set.toList $ Schema.ens sch)
l = sepBy' "\n" h
f x (fk,_) = show fk ++ " = " ++ (show $ aFk alg fk x )
g x (att,_) = show att ++ " = " ++ (show $ aAtt alg att x )
alg = Algebra sch en' nf''' repr'' ty' nf'''' repr''' teqs'
show alg@(Algebra sch en' _ _ ty' _ _ teqs') =
"algebra" ++ "\n" ++
intercalate "\n\n" prettyEntities ++ "\n" ++
"type-algebra" ++ "\n" ++
"nulls" ++ "\n" ++
w ++
prettyTypeEqns
where w = " " ++ (intercalate "\n " . mapl w2 . Typeside.tys . Schema.typeside $ sch)
w2 ty'' = show ty'' ++ " (" ++ (show . Set.size $ ty' ty'') ++ ") = " ++ show (Foldable.toList $ ty' ty'') ++ " "

prettyEntities = prettyEntity `mapl` Schema.ens sch

prettyEntity e =
show e ++ " (" ++ show (Set.size $ en' e) ++ ")\n" ++
"-------------\n" ++
(intercalate "\n" $ prettyEntityRow e `mapl` en' e)

prettyEntityRow en'' e =
show e ++ ": " ++
intercalate "," (prettyFk e <$> fksFrom' sch en'') ++ ", " ++
intercalate "," (prettyAtt e <$> attsFrom' sch en'')

prettyAtt :: x -> (att, w) -> String
prettyAtt x (att,_) = show att ++ " = " ++ (prettyTerm $ aAtt alg att x)

prettyFk x (fk, _) = show fk ++ " = " ++ (show $ aFk alg fk x)

prettyTerm = show

prettyTypeEqns = intercalate "\n" (Set.map show teqs')

mapl fn = fmap fn . Foldable.toList

fksFrom :: Eq en => Collage var ty sym en fk att gen sk -> en -> [(fk,en)]
fksFrom sch en' = f $ Map.assocs $ cfks sch
Expand Down

0 comments on commit ce9abfd

Please sign in to comment.