Skip to content

Commit

Permalink
Move assembleGens from Instance into Collage. #148
Browse files Browse the repository at this point in the history
  • Loading branch information
epost committed Aug 21, 2019
1 parent d911bab commit 468409e
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 12 deletions.
15 changes: 15 additions & 0 deletions src/Language/CQL/Collage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
Expand Down Expand Up @@ -101,6 +102,20 @@ attsFrom sch en' = f $ Map.assocs $ catts sch
where f [] = []
f ((fk,(en1,t)):l) = if en1 == en' then (fk,t) : (f l) else f l

type Carrier en fk gen = Term Void Void Void en fk Void gen Void

assembleGens
:: (MultiTyMap '[Show, Ord, NFData] '[var, ty, sym, en, fk, att, gen, sk])
=> Collage var ty sym en fk att gen sk
-> [Carrier en fk gen]
-> Map en (Set (Carrier en fk gen))
assembleGens col [] = Map.fromList $ fmap (, Set.empty) $ Set.toList $ cens col
assembleGens col (e:tl) = Map.insert t (Set.insert e s) m
where
m = assembleGens col tl
t = typeOf col e
s = m ! t

-- | Gets the type of a term that is already known to be well-typed.
typeOf
:: (MultiTyMap '[Show, Ord, NFData] '[var, ty, sym, en, fk, att, gen, sk])
Expand Down
13 changes: 1 addition & 12 deletions src/Language/CQL/Instance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ import qualified Data.Set as Set
import Data.Typeable hiding (typeOf)
import Data.Void
import Language.CQL.Collage (Collage(..), attsFrom, fksFrom, typeOf, typeOfCol)
import Language.CQL.Collage (Collage(..), assembleGens, attsFrom, fksFrom, typeOf, typeOfCol)
import Language.CQL.Common (elem', intercalate, fromListAccum, mapl, section, sepTup, toMapSafely, Deps(..), Err, Kind(INSTANCE), MultiTyMap, TyMap, type (+))
import Language.CQL.Mapping as Mapping
import Language.CQL.Options
Expand Down Expand Up @@ -422,18 +423,6 @@ deriving instance TyMap Ord '[en, fk, att, gen, sk] => Ord (TalgGen en fk att ge

deriving instance TyMap Eq '[fk, att, gen, sk] => Eq (TalgGen en fk att gen sk)

assembleGens
:: (MultiTyMap '[Show, Ord, NFData] '[var, ty, sym, en, fk, att, gen, sk])
=> Collage var ty sym en fk att gen sk
-> [Carrier en fk gen]
-> Map en (Set (Carrier en fk gen))
assembleGens col [] = Map.fromList $ Prelude.map (, Set.empty) $ Set.toList $ cens col
assembleGens col (e:tl) = Map.insert t (Set.insert e s) m
where
m = assembleGens col tl
t = typeOf col e
s = m ! t

close
:: (MultiTyMap '[Show, Ord, NFData] '[var, ty, sym, en, fk, att, gen, sk])
=> Collage var ty sym en fk att gen sk
Expand Down

0 comments on commit 468409e

Please sign in to comment.