Skip to content

Commit

Permalink
fixes for GHC 7.8.3, faster build for uhc-light
Browse files Browse the repository at this point in the history
  • Loading branch information
atzedijkstra committed Dec 17, 2014
1 parent 3cf2e2b commit 6c4a761
Show file tree
Hide file tree
Showing 15 changed files with 66 additions and 12 deletions.
2 changes: 1 addition & 1 deletion EHC/changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

## 1.1.8.2

-
- [build] Fixes some GHC 7.8.3 Typeable warnings

## 1.1.8.1 - 20141217

Expand Down
2 changes: 1 addition & 1 deletion EHC/mk/shared.mk.in
Original file line number Diff line number Diff line change
Expand Up @@ -597,7 +597,7 @@ FUN_GEN_CABAL_UHC_LIGHT = \
echo " Main-Is: $(strip $(9)).hs" ; \
echo "" ; \
echo "Executable $(strip $(16))" ; \
echo " Hs-Source-Dirs: $(18), $(17)" ; \
echo " Hs-Source-Dirs: $(18)" ; \
echo " Build-Depends: $(strip $(1))==$(strip $(2)), $(subst $(space),$(comma),$(strip @CABAL_BASE_LIB_DEPENDS@ @CABAL_EXTRA_LIB_DEPENDS@ $(CABAL_ENABLEDASPECT_LIB_DEPENDS) $(3)))" ; \
echo " Extensions: $(subst $(space),$(comma),$(strip RankNTypes MultiParamTypeClasses FunctionalDependencies $(4)))" ; \
echo " Main-Is: $(strip $(15)).hs" ; \
Expand Down
8 changes: 8 additions & 0 deletions EHC/src/ehc/Base/Common.chs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
%%[0 hs
{-# LANGUAGE CPP #-}
%%]

%%[0 lhs2tex
%include lhs2TeX.fmt
%include afp.fmt
Expand Down Expand Up @@ -1074,7 +1078,11 @@ deriving instance Data TagDataInfo
deriving instance Typeable Fixity
deriving instance Data Fixity

#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable AlwaysEq
#else
deriving instance Typeable1 AlwaysEq
#endif
deriving instance Data x => Data (AlwaysEq x)

deriving instance Typeable PredOccId
Expand Down
8 changes: 8 additions & 0 deletions EHC/src/ehc/Base/Fld.chs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
%%[0 hs
{-# LANGUAGE CPP #-}
%%]

%%[0 lhs2tex
%include lhs2TeX.fmt
%include afp.fmt
Expand Down Expand Up @@ -123,7 +127,11 @@ instance HSNM inx => RefOfFld (Fld' inx) HsName where
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%%[50
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable Fld'
#else
deriving instance Typeable1 Fld'
#endif
deriving instance Data x => Data (Fld' x)
%%]

Expand Down
8 changes: 8 additions & 0 deletions EHC/src/ehc/Base/RLList.chs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
%%[0 hs
{-# LANGUAGE CPP #-}
%%]

%%[0 lhs2tex
%include lhs2TeX.fmt
%include afp.fmt
Expand Down Expand Up @@ -118,7 +122,11 @@ instance Show a => Show (RLList a) where
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%%[50
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable RLList
#else
deriving instance Typeable1 RLList
#endif
deriving instance Data x => Data (RLList x)

%%]
Expand Down
11 changes: 10 additions & 1 deletion EHC/src/ehc/Base/TreeTrie.chs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
%%[0 hs
{-# LANGUAGE CPP #-}
%%]

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% TreeTrie, variation which allows matching on subtrees marked as a variable (kind of unification)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Expand Down Expand Up @@ -38,7 +42,7 @@ candidates is returned.
%%[9 import(UHC.Util.Pretty hiding (empty), qualified UHC.Util.Pretty as PP)
%%]

%%[50 import(Data.Typeable(Typeable,Typeable1), Data.Generics(Data))
%%[50 import(Data.Typeable, Data.Generics(Data))
%%]
%%[50 hs import(Control.Monad)
%%]
Expand Down Expand Up @@ -85,8 +89,13 @@ mkTreeTrieKeys = Prelude.map (\k -> TTK (TT1K_One k) [])
%%]

%%[50
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable TreeTrie1Key
deriving instance Typeable TreeTrieMp1Key
#else
deriving instance Typeable1 TreeTrie1Key
deriving instance Typeable1 TreeTrieMp1Key
#endif
deriving instance Data x => Data (TreeTrie1Key x)
deriving instance Data x => Data (TreeTrieMp1Key x)
%%]
Expand Down
10 changes: 9 additions & 1 deletion EHC/src/ehc/CHR/Constraint.chs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
%%[0 hs
{-# LANGUAGE CPP #-}
%%]

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% Constraint Handling Rules: Constraint language
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Expand All @@ -16,7 +20,7 @@

%%[(50 hmtyinfer || hmtyast) import(Control.Monad, UHC.Util.Binary, UHC.Util.Serialize)
%%]
%%[(50 hmtyinfer || hmtyast) import(Data.Typeable(Typeable,Typeable2), Data.Generics(Data))
%%[(50 hmtyinfer || hmtyast) import(Data.Typeable, Data.Generics(Data))
%%]

%%[(50 hmtyinfer || hmtyast) import({%{EH}Opts.Base})
Expand Down Expand Up @@ -55,7 +59,11 @@ mkReduction p i ps
%%]

%%[(50 hmtyinfer || hmtyast)
#if __GLASGOW_HASKELL__ >= 708
deriving instance Typeable Constraint
#else
deriving instance Typeable2 Constraint
#endif
deriving instance (Data x, Data y) => Data (Constraint x y)
%%]

Expand Down
2 changes: 1 addition & 1 deletion EHC/src/ehc/CHR/Solve.chs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ Assumptions (to be documented further)
%%[(9 hmtyinfer || hmtyast) import(UHC.Util.Pretty as Pretty)
%%]

%%[50 import(Data.Typeable(Typeable,Typeable1), Data.Generics(Data))
%%[50 import(Data.Typeable, Data.Generics(Data))
%%]
%%[(50 hmtyinfer || hmtyast) import(UHC.Util.Serialize)
%%]
Expand Down
3 changes: 2 additions & 1 deletion EHC/src/ehc/CoreRun/Run/Val/RunExplStk.chs
Original file line number Diff line number Diff line change
Expand Up @@ -255,7 +255,8 @@ rvalExplStkExp e = do
-- FFI
Exp_FFI pr as -> V.mapM_ rsemSExp as >> renvFrStkPopMV (V.length as) >>= (liftIO . V.freeze) >>= rsemPrim pr

e -> err $ "CoreRun.Run.Val.RunExplStk.rvalExplStkExp:" >#< e
-- necessary only when case is non-saturated w.r.t. alternatives of datatype Exp
-- e -> err $ "CoreRun.Run.Val.RunExplStk.rvalExplStkExp:" >#< e

%%[[8
rsemTr $ "<E:" >#< (e) -- >-< e')
Expand Down
3 changes: 2 additions & 1 deletion EHC/src/ehc/CoreRun/Run/Val/RunImplStk.chs
Original file line number Diff line number Diff line change
Expand Up @@ -215,7 +215,8 @@ rvalImplStkExp e = do
-- FFI
Exp_FFI pr as -> V.mapM rsemSExp as >>= rsemPrim pr

e -> err $ "CoreRun.Run.Val.RunExplStk.rvalImplStkExp:" >#< e
-- necessary only when case is non-saturated w.r.t. alternatives of datatype Exp
-- e -> err $ "CoreRun.Run.Val.RunExplStk.rvalImplStkExp:" >#< e

%%[[8
rsemTr $ "<E:" >#< e -- (e >-< e')
Expand Down
2 changes: 2 additions & 0 deletions EHC/src/ehc/EHC/Main/Utils.chs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@

%%[1 import(qualified {%{EH}Config} as Cfg)
%%]
%%[1 import({%{EH}Opts}) export(module {%{EH}Opts})
%%]
%%[50 import(qualified {%{EH}SourceCodeSig} as Sig)
%%]

Expand Down
4 changes: 2 additions & 2 deletions EHC/src/ehc/EHCRun.chs
Original file line number Diff line number Diff line change
Expand Up @@ -8,13 +8,13 @@
%%[(8 corerun) import({%{EH}EHC.Main.Utils})
%%]

%%[(8 corerun) import(qualified {%{EH}Config} as Cfg)
%%[(8888 corerun) import(qualified {%{EH}Config} as Cfg)
%%]

%%[(8 corerun) import({%{EH}Base.API}, {%{EH}CoreRun.API})
%%]

%%[(8 corerun) import({%{EH}Opts})
%%[(8888 corerun) import({%{EH}Opts})
%%]

%%[(8 corerun) import(UHC.Util.Pretty, UHC.Util.FPath)
Expand Down
2 changes: 1 addition & 1 deletion EHC/src/ehc/LamInfo.chs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ Currently the following is maintained:

%%[(50 codegen) import(Control.Monad, UHC.Util.Serialize)
%%]
%%[(50 codegen) import(Data.Typeable(Typeable,Typeable2), Data.Generics(Data))
%%[(50 codegen) import(Data.Typeable, Data.Generics(Data))
%%]

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Expand Down
9 changes: 9 additions & 0 deletions EHC/src/ehc/Ty.cag
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
%%[0 hs
-- 20141217 AD: fix shuffle to propagate this for .cag files as well...
{-# LANGUAGE CPP #-}
%%]

%%[0 lhs2tex
%include lhs2TeX.fmt
%include afp.fmt
Expand Down Expand Up @@ -579,7 +584,11 @@ cpo2PredOcc i o
%%]

%%[(50 hmtyinfer || hmtyast) hs
-- #if __GLASGOW_HASKELL__ >= 708
-- deriving instance Typeable CHRPredOcc'
-- #else
deriving instance Typeable1 CHRPredOcc'
-- #endif
deriving instance Data CHRPredOcc
%%]

Expand Down
4 changes: 2 additions & 2 deletions EHC/src/ehc/files2.mk
Original file line number Diff line number Diff line change
Expand Up @@ -207,9 +207,9 @@ uhc-light-cabal-dist: # $(EHC_HS_ALL_DRV_HS_NO_MAIN) $(EHC_HS_MAIN_DRV_HS)
ehc_ehclib_lib_dir="$(EHCLIB_INS_LIB_DIR)" ; \
ehc_ehclib_files="$(filter-out $(EHCLIB_INS_LIB_DIR) %DS_Store,$(subst $(EHCLIB_INS_LIB_PREFIX),,$(shell find $(call FUN_PREFIX2DIR,$(EHCLIB_INS_LIB_PREFIX)) \( -name '*' -type f \) )))" ; \
ehc_ehclib_names="`echo $${ehc_ehclib_files} | sed -e 's=\([^ ]*\)=$(call FUN_VARIANT_LIB_PREFIX,$(EHC_VARIANT))\1=g' -e 's/ /,/g'`" ; \
ehc_nomain_exposed_hs_files="$(subst $(EHC_BLD_LIBEHC_VARIANT_PREFIX),,$(call FILTER_OUT_EMPTY_FILES,$(filter %API.hs,$(shell find $(call FUN_PREFIX2DIR,$(EHC_BLD_LIBEHC_VARIANT_PREFIX)) \( -name '*.hs' \)))))" ; \
ehc_nomain_exposed_hs_files="$(subst $(EHC_BLD_LIBEHC_VARIANT_PREFIX),,$(call FILTER_OUT_EMPTY_FILES,$(filter %Main.hs %Main/Utils.hs %API.hs,$(shell find $(call FUN_PREFIX2DIR,$(EHC_BLD_LIBEHC_VARIANT_PREFIX)) \( -name '*.hs' \)))))" ; \
ehc_nomain_exposed_names="`echo $${ehc_nomain_exposed_hs_files} | sed -e 's/\.hs//g' -e 's/ /,/g' -e 's+$(PATH_SEP)+.+g'`" ; \
ehc_nomain_nonexposed_hs_files="$(filter-out %Paths_uhc_light.hs dist%, $(subst $(EHC_BLD_LIBEHC_VARIANT_PREFIX),,$(call FILTER_OUT_EMPTY_FILES,$(filter-out %API.hs,$(shell find $(call FUN_PREFIX2DIR,$(EHC_BLD_LIBEHC_VARIANT_PREFIX)) \( -name '*.hs' \))))))" ; \
ehc_nomain_nonexposed_hs_files="$(filter-out %Paths_uhc_light.hs dist%, $(subst $(EHC_BLD_LIBEHC_VARIANT_PREFIX),,$(call FILTER_OUT_EMPTY_FILES,$(filter-out %Main.hs %Main/Utils.hs %API.hs,$(shell find $(call FUN_PREFIX2DIR,$(EHC_BLD_LIBEHC_VARIANT_PREFIX)) \( -name '*.hs' \))))))" ; \
ehc_nomain_nonexposed_names="Paths_uhc_light,`echo $${ehc_nomain_nonexposed_hs_files} | sed -e 's/\.hs//g' -e 's/ /,/g' -e 's+$(PATH_SEP)+.+g'`" ; \
ehc_main_hs_files="$(subst $(EHC_BLD_VARIANT_ASPECTS_PREFIX),,$(call FILTER_OUT_EMPTY_FILES,$(EHC_HS_MAIN_DRV_HS) $(EHCRUN_HS_MAIN_DRV_HS)))" ; \
$(call FUN_COPY_FILES_BY_TAR,$(EHC_BLD_LIBEHC_VARIANT_PREFIX),$(CABALDIST_UHCLIGHT_SRC_PREFIX),$${ehc_nomain_exposed_hs_files} $${ehc_nomain_nonexposed_hs_files}) ; \
Expand Down

0 comments on commit 6c4a761

Please sign in to comment.