diff --git a/CHANGES.md b/CHANGES.md index c95c2790..4e938ae1 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -3,6 +3,22 @@ Changelog for singletons project next ---- +* The suffix for defunctionalized names of symbolic functions (e.g., `(+)`) has + changed. Before, the promoted type name would be suffixed with some number of + dollar signs (e.g., `(:+$)` and `(:+$$)`) to indicate defunctionalization + symbols. Now, the promoted type name is first suffixed with `@#@` and + _then_ followed by dollar signs (e.g., `(:+@#@$)` and `(:+@#@$$)`). + Adopting this conventional eliminates naming conflicts that could arise for + functions that consisted of solely `$` symbols. + +* The promoted/singled/defunctionalized symbols for `($)` have changed: + + * `($)` is now `(:$)` + * `(%$)` is now `(%:$)` + * `($$)` is now `($@#@$)`, and `($$$)` is now `($@#@$$)` + + This makes the treatment of `($)` consistent with other symbolic functions. + * Add promoted and singled versions of `Show`, including `deriving` support. * Permit derived `Ord` instances for empty datatypes. diff --git a/README.md b/README.md index bfb721a1..9b9ff980 100644 --- a/README.md +++ b/README.md @@ -374,7 +374,7 @@ generates. Here are some examples showing how this is done: singleton constructor: `:%+:` - symbols: `:+:$`, `:+:$$`, `:+:$$$` + symbols: `:+:@#@$`, `:+:@#@$$`, `:+:@#@$$$` 5. original value: `pred` @@ -392,7 +392,7 @@ generates. Here are some examples showing how this is done: singleton value: `%:+` - symbols: `:+$`, `:+$$`, `:+$$$` + symbols: `:+@#@$`, `:+@#@$$`, `:+@#@$$$` 7. original class: `Num` @@ -412,7 +412,8 @@ generates. Here are some examples showing how this is done: Special names ------------- -There are some special cases, listed below (with asterisks\* denoting special treatment): +There are some special cases, listed below (with asterisks\* denoting special +treatment): 1. original datatype: `[]` @@ -421,13 +422,13 @@ There are some special cases, listed below (with asterisks\* denoting special tr singleton type\*: `SList` -2. original constructor: `[]` +2. original constructor: `[]` - promoted type: `'[]` + promoted type: `'[]` - singleton constructor\*: `SNil` + singleton constructor\*: `SNil` - symbols\*: `NilSym0` + symbols\*: `NilSym0` 3. original constructor: `:` @@ -436,7 +437,7 @@ There are some special cases, listed below (with asterisks\* denoting special tr singleton constructor\*: `SCons` - symbols\*: `ConsSym0`, `ConsSym1` + symbols: `:@#@$`, `:@#@$` 4. original datatype: `(,)` diff --git a/src/Data/Promotion/Prelude.hs b/src/Data/Promotion/Prelude.hs index 86a80a68..3adf6375 100644 --- a/src/Data/Promotion/Prelude.hs +++ b/src/Data/Promotion/Prelude.hs @@ -46,7 +46,7 @@ module Data.Promotion.Prelude ( PShow(..), ShowS, SChar, show_, (:<>), Shows, ShowChar, ShowString, ShowParen, -- ** Miscellaneous functions - Id, Const, (:.), type ($), type ($!), Flip, AsTypeOf, Until, Seq, + Id, Const, (:.), (:$), (:$!), Flip, AsTypeOf, Until, Seq, -- * List operations Map, (:++), Filter, @@ -75,7 +75,9 @@ module Data.Promotion.Prelude ( -- * Defunctionalization symbols FalseSym0, TrueSym0, - NotSym0, NotSym1, (:&&$), (:&&$$), (:&&$$$), (:||$), (:||$$), (:||$$$), + NotSym0, NotSym1, + (:&&@#@$), (:&&@#@$$), (:&&@#@$$$), + (:||@#@$), (:||@#@$$), (:||@#@$$$), OtherwiseSym0, NothingSym0, JustSym0, JustSym1, @@ -95,27 +97,27 @@ module Data.Promotion.Prelude ( CurrySym0, CurrySym1, CurrySym2, CurrySym3, UncurrySym0, UncurrySym1, UncurrySym2, - (:^$), (:^$$), + (:^@#@$), (:^@#@$$), ShowsPrecSym0, ShowsPrecSym1, ShowsPrecSym2, ShowsPrecSym3, Show_Sym0, Show_Sym1, ShowListSym0, ShowListSym1, ShowListSym2, - (:<>$), (:<>$$), (:<>$$$), + (:<>@#@$), (:<>@#@$$), (:<>@#@$$$), ShowsSym0, ShowsSym1, ShowsSym2, ShowCharSym0, ShowCharSym1, ShowCharSym2, ShowStringSym0, ShowStringSym1, ShowStringSym2, ShowParenSym0, ShowParenSym1, ShowParenSym2, IdSym0, IdSym1, ConstSym0, ConstSym1, ConstSym2, - (:.$), (:.$$), (:.$$$), - type ($$), type ($$$), type ($$$$), - type ($!$), type ($!$$), type ($!$$$), + (:.@#@$), (:.@#@$$), (:.@#@$$$), + (:$@#@$), (:$@#@$$), (:$@#@$$$), + (:$!@#@$), (:$!@#@$$), (:$!@#@$$$), FlipSym0, FlipSym1, FlipSym2, AsTypeOfSym0, AsTypeOfSym1, AsTypeOfSym2, SeqSym0, SeqSym1, SeqSym2, - (:$), (:$$), (:$$$), NilSym0, + (:@#@$), (:@#@$$), (:@#@$$$), NilSym0, MapSym0, MapSym1, MapSym2, ReverseSym0, ReverseSym1, - (:++$$), (:++$), HeadSym0, HeadSym1, LastSym0, LastSym1, + (:++@#@$$), (:++@#@$), HeadSym0, HeadSym1, LastSym0, LastSym1, TailSym0, TailSym1, InitSym0, InitSym1, NullSym0, NullSym1, FoldlSym0, FoldlSym1, FoldlSym2, FoldlSym3, @@ -159,7 +161,7 @@ module Data.Promotion.Prelude ( BreakSym0, BreakSym1, BreakSym2, LookupSym0, LookupSym1, LookupSym2, FilterSym0, FilterSym1, FilterSym2, - (:!!$), (:!!$$), (:!!$$$), + (:!!@#@$), (:!!@#@$$), (:!!@#@$$$), ) where import Data.Promotion.Prelude.Base diff --git a/src/Data/Promotion/Prelude/Base.hs b/src/Data/Promotion/Prelude/Base.hs index 6ea6a302..1f3e8457 100644 --- a/src/Data/Promotion/Prelude/Base.hs +++ b/src/Data/Promotion/Prelude/Base.hs @@ -23,19 +23,19 @@ module Data.Promotion.Prelude.Base ( -- * Promoted functions from @GHC.Base@ - Foldr, Map, (:++), Otherwise, Id, Const, (:.), type ($), type ($!), + Foldr, Map, (:++), Otherwise, Id, Const, (:.), (:$), (:$!), Flip, Until, AsTypeOf, Seq, -- * Defunctionalization symbols FoldrSym0, FoldrSym1, FoldrSym2, FoldrSym3, MapSym0, MapSym1, MapSym2, - (:++$), (:++$$), (:++$$$), + (:++@#@$), (:++@#@$$), (:++@#@$$$), OtherwiseSym0, IdSym0, IdSym1, ConstSym0, ConstSym1, ConstSym2, - (:.$), (:.$$), (:.$$$), (:.$$$$), - type ($$), type ($$$), type ($$$$), - type ($!$), type ($!$$), type ($!$$$), + (:.@#@$), (:.@#@$$), (:.@#@$$$), (:.@#@$$$$), + (:$@#@$), (:$@#@$$), (:$@#@$$$), + (:$!@#@$), (:$!@#@$$), (:$!@#@$$$), FlipSym0, FlipSym1, FlipSym2, FlipSym3, UntilSym0, UntilSym1, UntilSym2, UntilSym3, AsTypeOfSym0, AsTypeOfSym1, AsTypeOfSym2, diff --git a/src/Data/Promotion/Prelude/Bool.hs b/src/Data/Promotion/Prelude/Bool.hs index 55d65f5c..395a3e50 100644 --- a/src/Data/Promotion/Prelude/Bool.hs +++ b/src/Data/Promotion/Prelude/Bool.hs @@ -33,8 +33,8 @@ module Data.Promotion.Prelude.Bool ( TrueSym0, FalseSym0, NotSym0, NotSym1, - (:&&$), (:&&$$), (:&&$$$), - (:||$), (:||$$), (:||$$$), + (:&&@#@$), (:&&@#@$$), (:&&@#@$$$), + (:||@#@$), (:||@#@$$), (:||@#@$$$), Bool_Sym0, Bool_Sym1, Bool_Sym2, Bool_Sym3, OtherwiseSym0 ) where diff --git a/src/Data/Promotion/Prelude/Eq.hs b/src/Data/Promotion/Prelude/Eq.hs index 7c506fc9..618d8ce6 100644 --- a/src/Data/Promotion/Prelude/Eq.hs +++ b/src/Data/Promotion/Prelude/Eq.hs @@ -13,7 +13,9 @@ {-# LANGUAGE ExplicitNamespaces #-} module Data.Promotion.Prelude.Eq ( - PEq(..), (:==$), (:==$$), (:==$$$), (:/=$), (:/=$$), (:/=$$$) + PEq(..), + (:==@#@$), (:==@#@$$), (:==@#@$$$), + (:/=@#@$), (:/=@#@$$), (:/=@#@$$$) ) where import Data.Singletons.Prelude.Eq diff --git a/src/Data/Promotion/Prelude/Function.hs b/src/Data/Promotion/Prelude/Function.hs index 2b6f791c..8c7ec48c 100644 --- a/src/Data/Promotion/Prelude/Function.hs +++ b/src/Data/Promotion/Prelude/Function.hs @@ -21,17 +21,17 @@ module Data.Promotion.Prelude.Function ( -- * "Prelude" re-exports - Id, Const, (:.), Flip, type ($) + Id, Const, (:.), Flip, (:$) -- * Other combinators , (:&), On -- * Defunctionalization symbols , IdSym0, IdSym1 , ConstSym0, ConstSym1, ConstSym2 - , (:.$), (:.$$), (:.$$$), (:.$$$$) + , (:.@#@$), (:.@#@$$), (:.@#@$$$), (:.@#@$$$$) , FlipSym0, FlipSym1, FlipSym2, FlipSym3 - , type ($$), type ($$$), type ($$$$) - , (:&$), (:&$$), (:&$$$) + , (:$@#@$), (:$@#@$$), (:$@#@$$$) + , (:&@#@$), (:&@#@$$), (:&@#@$$$) , OnSym0, OnSym1, OnSym2, OnSym3, OnSym4 ) where diff --git a/src/Data/Promotion/Prelude/List.hs b/src/Data/Promotion/Prelude/List.hs index 5b193d31..59fc2937 100644 --- a/src/Data/Promotion/Prelude/List.hs +++ b/src/Data/Promotion/Prelude/List.hs @@ -102,9 +102,10 @@ module Data.Promotion.Prelude.List ( -- * Defunctionalization symbols NilSym0, - (:$), (:$$), (:$$$), + (:@#@$), (:@#@$$), (:@#@$$$), - (:++$$$), (:++$$), (:++$), HeadSym0, HeadSym1, LastSym0, LastSym1, + (:++@#@$$$), (:++@#@$$), (:++@#@$), + HeadSym0, HeadSym1, LastSym0, LastSym1, TailSym0, TailSym1, InitSym0, InitSym1, NullSym0, NullSym1, MapSym0, MapSym1, MapSym2, ReverseSym0, ReverseSym1, @@ -157,7 +158,7 @@ module Data.Promotion.Prelude.List ( Unzip7Sym0, Unzip7Sym1, DeleteSym0, DeleteSym1, DeleteSym2, - (:\\$), (:\\$$), (:\\$$$), + (:\\@#@$), (:\\@#@$$), (:\\@#@$$$), IntersectSym0, IntersectSym1, IntersectSym2, InsertSym0, InsertSym1, InsertSym2, @@ -193,7 +194,7 @@ module Data.Promotion.Prelude.List ( FilterSym0, FilterSym1, FilterSym2, PartitionSym0, PartitionSym1, PartitionSym2, - (:!!$), (:!!$$), (:!!$$$), + (:!!@#@$), (:!!@#@$$), (:!!@#@$$$), ElemIndexSym0, ElemIndexSym1, ElemIndexSym2, ElemIndicesSym0, ElemIndicesSym1, ElemIndicesSym2, diff --git a/src/Data/Promotion/Prelude/List/NonEmpty.hs b/src/Data/Promotion/Prelude/List/NonEmpty.hs index 35118f1d..cedce977 100644 --- a/src/Data/Promotion/Prelude/List/NonEmpty.hs +++ b/src/Data/Promotion/Prelude/List/NonEmpty.hs @@ -69,7 +69,7 @@ module Data.Promotion.Prelude.List.NonEmpty ( Xor, -- * Defunctionalization symbols - (:|$), (:|$$), (:|$$$), + (:|@#@$), (:|@#@$$), (:|@#@$$$), MapSym0, MapSym1, MapSym2, IntersperseSym0, IntersperseSym1, IntersperseSym2, ScanlSym0, ScanlSym1, ScanlSym2, ScanlSym3, @@ -84,7 +84,7 @@ module Data.Promotion.Prelude.List.NonEmpty ( TailSym0, TailSym1, LastSym0, LastSym1, InitSym0, InitSym1, - (:<|$), (:<|$$), (:<|$$$), + (:<|@#@$), (:<|@#@$$), (:<|@#@$$$), ConsSym0, ConsSym1, ConsSym2, UnconsSym0, UnconsSym1, UnfoldrSym0, UnfoldrSym1, UnfoldrSym2, @@ -114,7 +114,7 @@ module Data.Promotion.Prelude.List.NonEmpty ( IsPrefixOfSym0, IsPrefixOfSym1, IsPrefixOfSym2, NubSym0, NubSym1, NubBySym0, NubBySym1, NubBySym2, - (:!!$), (:!!$$), (:!!$$$), + (:!!@#@$), (:!!@#@$$), (:!!@#@$$$), ZipSym0, ZipSym1, ZipSym2, ZipWithSym0, ZipWithSym1, ZipWithSym2, ZipWithSym3, UnzipSym0, UnzipSym1, diff --git a/src/Data/Promotion/Prelude/Num.hs b/src/Data/Promotion/Prelude/Num.hs index cfb00054..67569ff8 100644 --- a/src/Data/Promotion/Prelude/Num.hs +++ b/src/Data/Promotion/Prelude/Num.hs @@ -16,9 +16,9 @@ module Data.Promotion.Prelude.Num ( PNum(..), Subtract, -- ** Defunctionalization symbols - (:+$), (:+$$), (:+$$$), - (:-$), (:-$$), (:-$$$), - (:*$), (:*$$), (:*$$$), + (:+@#@$), (:+@#@$$), (:+@#@$$$), + (:-@#@$), (:-@#@$$), (:-@#@$$$), + (:*@#@$), (:*@#@$$), (:*@#@$$$), NegateSym0, NegateSym1, AbsSym0, AbsSym1, SignumSym0, SignumSym1, diff --git a/src/Data/Promotion/Prelude/Ord.hs b/src/Data/Promotion/Prelude/Ord.hs index 0893abf3..f5738802 100644 --- a/src/Data/Promotion/Prelude/Ord.hs +++ b/src/Data/Promotion/Prelude/Ord.hs @@ -15,10 +15,10 @@ module Data.Promotion.Prelude.Ord ( POrd(..), LTSym0, EQSym0, GTSym0, CompareSym0, CompareSym1, CompareSym2, - (:<$), (:<$$), (:<$$$), - (:<=$), (:<=$$), (:<=$$$), - (:>$), (:>$$), (:>$$$), - (:>=$), (:>=$$), (:>=$$$), + (:<@#@$), (:<@#@$$), (:<@#@$$$), + (:<=@#@$), (:<=@#@$$), (:<=@#@$$$), + (:>@#@$), (:>@#@$$), (:>@#@$$$), + (:>=@#@$), (:>=@#@$$), (:>=@#@$$$), MaxSym0, MaxSym1, MaxSym2, MinSym0, MinSym1, MinSym2 ) where diff --git a/src/Data/Promotion/Prelude/Show.hs b/src/Data/Promotion/Prelude/Show.hs index 04e63b13..e6c5c937 100644 --- a/src/Data/Promotion/Prelude/Show.hs +++ b/src/Data/Promotion/Prelude/Show.hs @@ -20,7 +20,7 @@ module Data.Promotion.Prelude.Show ( ShowsPrecSym0, ShowsPrecSym1, ShowsPrecSym2, ShowsPrecSym3, Show_Sym0, Show_Sym1, ShowListSym0, ShowListSym1, ShowListSym2, - (:<>$), (:<>$$), (:<>$$$), + (:<>@#@$), (:<>@#@$$), (:<>@#@$$$), ShowsSym0, ShowsSym1, ShowsSym2, ShowListWithSym0, ShowListWithSym1, ShowListWithSym2, ShowListWithSym3, ShowCharSym0, ShowCharSym1, ShowCharSym2, diff --git a/src/Data/Singletons/Names.hs b/src/Data/Singletons/Names.hs index 96be7e65..38f718ad 100644 --- a/src/Data/Singletons/Names.hs +++ b/src/Data/Singletons/Names.hs @@ -175,7 +175,8 @@ promoteTySym name sat = let capped = toUpcaseStr noPrefix name in if isHsLetter (head capped) then mkName (capped ++ "Sym" ++ (show sat)) - else mkName (capped ++ (replicate (sat + 1) '$')) + else mkName (capped ++ "@#@" -- See Note [Defunctionalization symbol suffixes] + ++ (replicate (sat + 1) '$')) promoteClassName :: Name -> Name promoteClassName = prefixUCName "P" "#" @@ -249,3 +250,30 @@ foldApply = foldl apply -- make and equality predicate mkEqPred :: DType -> DType -> DPred mkEqPred ty1 ty2 = foldl DAppPr (DConPr equalityName) [ty1, ty2] + +{- +Note [Defunctionalization symbol suffixes] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Before, we used to denote defunctionalization symbols by simply appending dollar +signs at the end (e.g., (:+$) and (:+$$)). But this can lead to ambiguity when you +have function names that consist of solely $ characters. For instance, if you +tried to promote ($) and ($$) simultaneously, you'd get these promoted types: + +:$ +:$$ + +And these defunctionalization symbols: + +:$$ +:$$$ + +But now there's a name clash between the promoted type for ($) and the +defunctionalization symbol for ($$)! The solution is to use a precede these +defunctionalization dollar signs with another string (we choose @#@). +So now the new defunctionalization symbols would be: + +:$@#@$ +:$@#@$$ + +And there is no conflict. +-} diff --git a/src/Data/Singletons/Prelude.hs b/src/Data/Singletons/Prelude.hs index 25014fe1..11396d74 100644 --- a/src/Data/Singletons/Prelude.hs +++ b/src/Data/Singletons/Prelude.hs @@ -59,7 +59,7 @@ module Data.Singletons.Prelude ( Shows, sShows, ShowChar, sShowChar, ShowString, sShowString, ShowParen, sShowParen, -- ** Miscellaneous functions - Id, sId, Const, sConst, (:.), (%:.), type ($), (%$), type ($!), (%$!), + Id, sId, Const, sConst, (:.), (%:.), (:$), (%:$), (:$!), (%:$!), Flip, sFlip, AsTypeOf, sAsTypeOf, Seq, sSeq, @@ -94,7 +94,9 @@ module Data.Singletons.Prelude ( -- * Defunctionalization symbols FalseSym0, TrueSym0, - NotSym0, NotSym1, (:&&$), (:&&$$), (:&&$$$), (:||$), (:||$$), (:||$$$), + NotSym0, NotSym1, + (:&&@#@$), (:&&@#@$$), (:&&@#@$$$), + (:||@#@$), (:||@#@$$), (:||@#@$$$), OtherwiseSym0, NothingSym0, JustSym0, JustSym1, @@ -117,22 +119,22 @@ module Data.Singletons.Prelude ( ShowsPrecSym0, ShowsPrecSym1, ShowsPrecSym2, ShowsPrecSym3, Show_Sym0, Show_Sym1, ShowListSym0, ShowListSym1, ShowListSym2, - (:<>$), (:<>$$), (:<>$$$), + (:<>@#@$), (:<>@#@$$), (:<>@#@$$$), ShowsSym0, ShowsSym1, ShowsSym2, ShowCharSym0, ShowCharSym1, ShowCharSym2, ShowStringSym0, ShowStringSym1, ShowStringSym2, ShowParenSym0, ShowParenSym1, ShowParenSym2, IdSym0, IdSym1, ConstSym0, ConstSym1, ConstSym2, - (:.$), (:.$$), (:.$$$), - type ($$), type ($$$), type ($$$$), - type ($!$), type ($!$$), type ($!$$$), + (:.@#@$), (:.@#@$$), (:.@#@$$$), + (:$@#@$), (:$@#@$$), (:$@#@$$$), + (:$!@#@$), (:$!@#@$$), (:$!@#@$$$), FlipSym0, FlipSym1, FlipSym2, AsTypeOfSym0, AsTypeOfSym1, AsTypeOfSym2, SeqSym0, SeqSym1, SeqSym2, - (:$), (:$$), (:$$$), NilSym0, + (:@#@$), (:@#@$$), (:@#@$$$), NilSym0, MapSym0, MapSym1, MapSym2, ReverseSym0, ReverseSym1, - (:++$$), (:++$), HeadSym0, HeadSym1, LastSym0, LastSym1, + (:++@#@$$), (:++@#@$), HeadSym0, HeadSym1, LastSym0, LastSym1, TailSym0, TailSym1, InitSym0, InitSym1, NullSym0, NullSym1, FoldlSym0, FoldlSym1, FoldlSym2, FoldlSym3, diff --git a/src/Data/Singletons/Prelude/Base.hs b/src/Data/Singletons/Prelude/Base.hs index 3adb4b8a..bab34d36 100644 --- a/src/Data/Singletons/Prelude/Base.hs +++ b/src/Data/Singletons/Prelude/Base.hs @@ -24,20 +24,20 @@ module Data.Singletons.Prelude.Base ( -- * Basic functions Foldr, sFoldr, Map, sMap, (:++), (%:++), Otherwise, sOtherwise, - Id, sId, Const, sConst, (:.), (%:.), type ($), type ($!), (%$), (%$!), + Id, sId, Const, sConst, (:.), (%:.), (:$), (:$!), (%:$), (%:$!), Flip, sFlip, AsTypeOf, sAsTypeOf, Seq, sSeq, -- * Defunctionalization symbols FoldrSym0, FoldrSym1, FoldrSym2, FoldrSym3, MapSym0, MapSym1, MapSym2, - (:++$), (:++$$), (:++$$$), + (:++@#@$), (:++@#@$$), (:++@#@$$$), OtherwiseSym0, IdSym0, IdSym1, ConstSym0, ConstSym1, ConstSym2, - (:.$), (:.$$), (:.$$$), (:.$$$$), - type ($$), type ($$$), type ($$$$), - type ($!$), type ($!$$), type ($!$$$), + (:.@#@$), (:.@#@$$), (:.@#@$$$), (:.@#@$$$$), + (:$@#@$), (:$@#@$$), (:$@#@$$$), + (:$!@#@$), (:$!@#@$$), (:$!@#@$$$), FlipSym0, FlipSym1, FlipSym2, FlipSym3, AsTypeOfSym0, AsTypeOfSym1, AsTypeOfSym2, SeqSym0, SeqSym1, SeqSym2 @@ -45,7 +45,6 @@ module Data.Singletons.Prelude.Base ( import Data.Singletons.Prelude.Instances import Data.Singletons.Single -import Data.Singletons import Data.Singletons.Prelude.Bool -- Promoted and singletonized versions of "otherwise" are imported and @@ -84,45 +83,17 @@ $(singletonsOnly [d| asTypeOf :: a -> a -> a asTypeOf = const + ($) :: (a -> b) -> a -> b + f $ x = f x + infixr 0 $ + + ($!) :: (a -> b) -> a -> b + f $! x = let {-!-}vx = x in f vx + infixr 0 $! + -- This is not part of GHC.Base, but we need to emulate seq and this is a good -- place to do it. seq :: a -> b -> b seq _ x = x infixr 0 `seq` |]) - --- ($) is a special case, because its kind-inference data constructors --- clash with (:). See #29. -type family (f :: TyFun a b -> *) $ (x :: a) :: b -type instance f $ x = f @@ x -infixr 0 $ - -data ($$) :: TyFun (TyFun a b -> *) (TyFun a b -> *) -> * -type instance Apply ($$) arg = ($$$) arg - -data ($$$) :: (TyFun a b -> *) -> TyFun a b -> * -type instance Apply (($$$) f) arg = ($$$$) f arg - -type ($$$$) a b = ($) a b - -(%$) :: forall (f :: TyFun a b -> *) (x :: a). - Sing f -> Sing x -> Sing (($$) @@ f @@ x) -f %$ x = applySing f x -infixr 0 %$ - -type family (f :: TyFun a b -> *) $! (x :: a) :: b -type instance f $! x = f @@ x -infixr 0 $! - -data ($!$) :: TyFun (TyFun a b -> *) (TyFun a b -> *) -> * -type instance Apply ($!$) arg = ($!$$) arg - -data ($!$$) :: (TyFun a b -> *) -> TyFun a b -> * -type instance Apply (($!$$) f) arg = ($!$$$) f arg - -type ($!$$$) a b = ($!) a b - -(%$!) :: forall (f :: TyFun a b -> *) (x :: a). - Sing f -> Sing x -> Sing (($!$) @@ f @@ x) -f %$! x = applySing f x -infixr 0 %$! diff --git a/src/Data/Singletons/Prelude/Bool.hs b/src/Data/Singletons/Prelude/Bool.hs index e9bf83ef..8bdec511 100644 --- a/src/Data/Singletons/Prelude/Bool.hs +++ b/src/Data/Singletons/Prelude/Bool.hs @@ -48,8 +48,8 @@ module Data.Singletons.Prelude.Bool ( TrueSym0, FalseSym0, NotSym0, NotSym1, - (:&&$), (:&&$$), (:&&$$$), - (:||$), (:||$$), (:||$$$), + (:&&@#@$), (:&&@#@$$), (:&&@#@$$$), + (:||@#@$), (:||@#@$$), (:||@#@$$$), Bool_Sym0, Bool_Sym1, Bool_Sym2, Bool_Sym3, OtherwiseSym0 ) where diff --git a/src/Data/Singletons/Prelude/Eq.hs b/src/Data/Singletons/Prelude/Eq.hs index e0621b3b..bb535812 100644 --- a/src/Data/Singletons/Prelude/Eq.hs +++ b/src/Data/Singletons/Prelude/Eq.hs @@ -17,7 +17,8 @@ module Data.Singletons.Prelude.Eq ( PEq(..), SEq(..), - (:==$), (:==$$), (:==$$$), (:/=$), (:/=$$), (:/=$$$) + (:==@#@$), (:==@#@$$), (:==@#@$$$), + (:/=@#@$), (:/=@#@$$), (:/=@#@$$$) ) where import Data.Singletons.Prelude.Bool diff --git a/src/Data/Singletons/Prelude/Function.hs b/src/Data/Singletons/Prelude/Function.hs index 7810aba4..dff31269 100644 --- a/src/Data/Singletons/Prelude/Function.hs +++ b/src/Data/Singletons/Prelude/Function.hs @@ -22,17 +22,17 @@ module Data.Singletons.Prelude.Function ( -- * "Prelude" re-exports - Id, sId, Const, sConst, (:.), (%:.), Flip, sFlip, type ($), (%$) + Id, sId, Const, sConst, (:.), (%:.), Flip, sFlip, (:$), (%:$) -- * Other combinators , (:&), (%:&), On, sOn -- * Defunctionalization symbols , IdSym0, IdSym1 , ConstSym0, ConstSym1, ConstSym2 - , (:.$), (:.$$), (:.$$$), (:.$$$$) + , (:.@#@$), (:.@#@$$), (:.@#@$$$), (:.@#@$$$$) , FlipSym0, FlipSym1, FlipSym2, FlipSym3 - , type ($$), type ($$$), type ($$$$) - , (:&$), (:&$$), (:&$$$) + , (:$@#@$), (:$@#@$$), (:$@#@$$$) + , (:&@#@$), (:&@#@$$), (:&@#@$$$) , OnSym0, OnSym1, OnSym2, OnSym3, OnSym4 ) where diff --git a/src/Data/Singletons/Prelude/List.hs b/src/Data/Singletons/Prelude/List.hs index 6fbc9273..b5cb8397 100644 --- a/src/Data/Singletons/Prelude/List.hs +++ b/src/Data/Singletons/Prelude/List.hs @@ -130,9 +130,10 @@ module Data.Singletons.Prelude.List ( -- * Defunctionalization symbols NilSym0, - (:$), (:$$), (:$$$), + (:@#@$), (:@#@$$), (:@#@$$$), - (:++$$$), (:++$$), (:++$), HeadSym0, HeadSym1, LastSym0, LastSym1, + (:++@#@$$$), (:++@#@$$), (:++@#@$), + HeadSym0, HeadSym1, LastSym0, LastSym1, TailSym0, TailSym1, InitSym0, InitSym1, NullSym0, NullSym1, LengthSym0, LengthSym1, @@ -195,7 +196,7 @@ module Data.Singletons.Prelude.List ( FilterSym0, FilterSym1, FilterSym2, PartitionSym0, PartitionSym1, PartitionSym2, - (:!!$), (:!!$$), (:!!$$$), + (:!!@#@$), (:!!@#@$$), (:!!@#@$$$), ElemIndexSym0, ElemIndexSym1, ElemIndexSym2, ElemIndicesSym0, ElemIndicesSym1, ElemIndicesSym2, FindIndexSym0, FindIndexSym1, FindIndexSym2, @@ -214,7 +215,7 @@ module Data.Singletons.Prelude.List ( NubSym0, NubSym1, DeleteSym0, DeleteSym1, DeleteSym2, - (:\\$), (:\\$$), (:\\$$$), + (:\\@#@$), (:\\@#@$$), (:\\@#@$$$), UnionSym0, UnionSym1, UnionSym2, IntersectSym0, IntersectSym1, IntersectSym2, diff --git a/src/Data/Singletons/Prelude/List/NonEmpty.hs b/src/Data/Singletons/Prelude/List/NonEmpty.hs index 5c2dfd76..60f6df19 100644 --- a/src/Data/Singletons/Prelude/List/NonEmpty.hs +++ b/src/Data/Singletons/Prelude/List/NonEmpty.hs @@ -90,7 +90,7 @@ module Data.Singletons.Prelude.List.NonEmpty ( Xor, sXor, -- * Defunctionalization symbols - (:|$), (:|$$), (:|$$$), + (:|@#@$), (:|@#@$$), (:|@#@$$$), MapSym0, MapSym1, MapSym2, IntersperseSym0, IntersperseSym1, IntersperseSym2, ScanlSym0, ScanlSym1, ScanlSym2, ScanlSym3, @@ -105,7 +105,7 @@ module Data.Singletons.Prelude.List.NonEmpty ( TailSym0, TailSym1, LastSym0, LastSym1, InitSym0, InitSym1, - (:<|$), (:<|$$), (:<|$$$), + (:<|@#@$), (:<|@#@$$), (:<|@#@$$$), ConsSym0, ConsSym1, ConsSym2, UnconsSym0, UnconsSym1, UnfoldrSym0, UnfoldrSym1, UnfoldrSym2, @@ -135,7 +135,7 @@ module Data.Singletons.Prelude.List.NonEmpty ( IsPrefixOfSym0, IsPrefixOfSym1, IsPrefixOfSym2, NubSym0, NubSym1, NubBySym0, NubBySym1, NubBySym2, - (:!!$), (:!!$$), (:!!$$$), + (:!!@#@$), (:!!@#@$$), (:!!@#@$$$), ZipSym0, ZipSym1, ZipSym2, ZipWithSym0, ZipWithSym1, ZipWithSym2, ZipWithSym3, UnzipSym0, UnzipSym1, diff --git a/src/Data/Singletons/Prelude/Num.hs b/src/Data/Singletons/Prelude/Num.hs index 44060364..43c86273 100644 --- a/src/Data/Singletons/Prelude/Num.hs +++ b/src/Data/Singletons/Prelude/Num.hs @@ -21,9 +21,9 @@ module Data.Singletons.Prelude.Num ( PNum(..), SNum(..), Subtract, sSubtract, -- ** Defunctionalization symbols - (:+$), (:+$$), (:+$$$), - (:-$), (:-$$), (:-$$$), - (:*$), (:*$$), (:*$$$), + (:+@#@$), (:+@#@$$), (:+@#@$$$), + (:-@#@$), (:-@#@$$), (:-@#@$$$), + (:*@#@$), (:*@#@$$), (:*@#@$$$), NegateSym0, NegateSym1, AbsSym0, AbsSym1, SignumSym0, SignumSym1, diff --git a/src/Data/Singletons/Prelude/Ord.hs b/src/Data/Singletons/Prelude/Ord.hs index 024166fc..04a917df 100644 --- a/src/Data/Singletons/Prelude/Ord.hs +++ b/src/Data/Singletons/Prelude/Ord.hs @@ -31,10 +31,10 @@ module Data.Singletons.Prelude.Ord ( ThenCmpSym0, ThenCmpSym1, ThenCmpSym2, LTSym0, EQSym0, GTSym0, CompareSym0, CompareSym1, CompareSym2, - (:<$), (:<$$), (:<$$$), - (:<=$), (:<=$$), (:<=$$$), - (:>$), (:>$$), (:>$$$), - (:>=$), (:>=$$), (:>=$$$), + (:<@#@$), (:<@#@$$), (:<@#@$$$), + (:<=@#@$), (:<=@#@$$), (:<=@#@$$$), + (:>@#@$), (:>@#@$$), (:>@#@$$$), + (:>=@#@$), (:>=@#@$$), (:>=@#@$$$), MaxSym0, MaxSym1, MaxSym2, MinSym0, MinSym1, MinSym2, ComparingSym0, ComparingSym1, ComparingSym2, ComparingSym3 diff --git a/src/Data/Singletons/Prelude/Show.hs b/src/Data/Singletons/Prelude/Show.hs index 446177ee..695cadb1 100644 --- a/src/Data/Singletons/Prelude/Show.hs +++ b/src/Data/Singletons/Prelude/Show.hs @@ -40,7 +40,7 @@ module Data.Singletons.Prelude.Show ( ShowsPrecSym0, ShowsPrecSym1, ShowsPrecSym2, ShowsPrecSym3, Show_Sym0, Show_Sym1, ShowListSym0, ShowListSym1, ShowListSym2, - (:<>$), (:<>$$), (:<>$$$), + (:<>@#@$), (:<>@#@$$), (:<>@#@$$$), ShowsSym0, ShowsSym1, ShowsSym2, ShowListWithSym0, ShowListWithSym1, ShowListWithSym2, ShowListWithSym3, ShowCharSym0, ShowCharSym1, ShowCharSym2, @@ -51,7 +51,6 @@ module Data.Singletons.Prelude.Show ( AppPrecSym0, AppPrec1Sym0 ) where -import Data.Kind (Type) import Data.List.NonEmpty (NonEmpty) import Data.Monoid ((<>)) import Data.Singletons.Prelude.Base @@ -87,18 +86,7 @@ sa %:<> sb = SomeSymbol (_ :: Proxy ab) -> unsafeCoerce (SSym :: Sing ab) infixr 6 %:<> -type (:<>$$$) (x :: Symbol) (y :: Symbol) = - (:<>) x y -instance SuppressUnusedWarnings (:<>$$) where - suppressUnusedWarnings = snd ((:<>$$###), ()) -data (:<>$$) (x :: Symbol) (y :: TyFun Symbol Symbol) - = forall arg. KindOf (Apply ((:<>$$) x) arg) ~ KindOf ((:<>$$$) x arg) => (:<>$$###) -type instance Apply ((:<>$$) x) y = (:<>$$$) x y -instance SuppressUnusedWarnings (:<>$) where - suppressUnusedWarnings = snd ((:<>$###), ()) -data (:<>$) (x :: TyFun Symbol (TyFun Symbol Symbol -> Type)) - = forall arg. KindOf (Apply (:<>$) arg) ~ KindOf ((:<>$$) arg) => (:<>$###) -type instance Apply (:<>$) x = (:<>$$) x +$(genDefunSymbols [''(:<>)]) -- | The @shows@ functions return a function that prepends the -- output 'Symbol' to an existing 'Symbol'. This allows constant-time diff --git a/src/Data/Singletons/Promote.hs b/src/Data/Singletons/Promote.hs index c2cf963f..5033c49a 100644 --- a/src/Data/Singletons/Promote.hs +++ b/src/Data/Singletons/Promote.hs @@ -426,7 +426,7 @@ promoteLetDecEnv prefixes (LetDecEnv { lde_defns = value_env promoteInfixDecl :: Fixity -> Name -> Maybe DDec promoteInfixDecl fixity name - | isUpcase name || head (nameBase name) == '$' -- See #29 and #197 + | isUpcase name = Nothing -- no need to promote the decl | otherwise = Just $ DLetDec $ DInfixD fixity (promoteValNameLhs name) diff --git a/src/Data/Singletons/TypeLits.hs b/src/Data/Singletons/TypeLits.hs index 5dcd2c55..9b3521e7 100644 --- a/src/Data/Singletons/TypeLits.hs +++ b/src/Data/Singletons/TypeLits.hs @@ -24,7 +24,7 @@ module Data.Singletons.TypeLits ( KnownNat, KnownNatSym0, KnownNatSym1, natVal, KnownSymbol, KnownSymbolSym0, KnownSymbolSym1, symbolVal, - (:^), (:^$), (:^$$), (:^$$$) + (:^), (:^@#@$), (:^@#@$$), (:^@#@$$$) ) where import Data.Singletons.TypeLits.Internal diff --git a/src/Data/Singletons/TypeLits/Internal.hs b/src/Data/Singletons/TypeLits/Internal.hs index a9fb3fb2..fae4b1c9 100644 --- a/src/Data/Singletons/TypeLits/Internal.hs +++ b/src/Data/Singletons/TypeLits/Internal.hs @@ -27,7 +27,7 @@ module Data.Singletons.TypeLits.Internal ( Error, ErrorSym0, ErrorSym1, sError, KnownNat, natVal, KnownSymbol, symbolVal, - (:^), (:^$), (:^$$), (:^$$$) + (:^), (:^@#@$), (:^@#@$$), (:^@#@$$$) ) where import Data.Singletons.Promote diff --git a/src/Data/Singletons/Util.hs b/src/Data/Singletons/Util.hs index 5a0bbfc6..d8f54a06 100644 --- a/src/Data/Singletons/Util.hs +++ b/src/Data/Singletons/Util.hs @@ -123,8 +123,7 @@ toUpcaseStr (alpha, symb) n upcase_alpha = alpha ++ (toUpper first) : tail str upcase_symb - | first == ':' - || first == '$' -- special case to avoid name clashes. See #29 + | first == ':' = symb ++ str | otherwise = symb ++ ':' : str diff --git a/tests/compile-and-dump/GradingClient/Database.ghc82.template b/tests/compile-and-dump/GradingClient/Database.ghc82.template index 624aee22..d46d1db9 100644 --- a/tests/compile-and-dump/GradingClient/Database.ghc82.template +++ b/tests/compile-and-dump/GradingClient/Database.ghc82.template @@ -18,7 +18,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations type instance Apply SuccSym0 l = Succ l type family Compare_0123456789876543210 (a :: Nat) (a :: Nat) :: Ordering where Compare_0123456789876543210 Zero Zero = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] - Compare_0123456789876543210 (Succ a_0123456789876543210) (Succ b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) + Compare_0123456789876543210 (Succ a_0123456789876543210) (Succ b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) Compare_0123456789876543210 Zero (Succ _) = LTSym0 Compare_0123456789876543210 (Succ _) Zero = GTSym0 type Compare_0123456789876543210Sym2 (t :: Nat) (t :: Nat) = @@ -87,7 +87,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -336,7 +336,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations Let0123456789876543210Scrutinee_0123456789876543210Sym0KindInference type instance Apply Let0123456789876543210Scrutinee_0123456789876543210Sym0 l = Let0123456789876543210Scrutinee_0123456789876543210Sym1 l type family Let0123456789876543210Scrutinee_0123456789876543210 name name' u attrs where - Let0123456789876543210Scrutinee_0123456789876543210 name name' u attrs = Apply (Apply (:==$) name) name' + Let0123456789876543210Scrutinee_0123456789876543210 name name' u attrs = Apply (Apply (:==@#@$) name) name' type family Case_0123456789876543210 name name' u attrs t where Case_0123456789876543210 name name' u attrs True = u Case_0123456789876543210 name name' u attrs False = Apply (Apply LookupSym0 name) (Apply SchSym0 attrs) @@ -421,20 +421,20 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations Lookup name (Sch ((:) (Attr name' u) attrs)) = Case_0123456789876543210 name name' u attrs (Let0123456789876543210Scrutinee_0123456789876543210Sym4 name name' u attrs) type family Occurs (a :: [AChar]) (a :: Schema) :: Bool where Occurs _ (Sch '[]) = FalseSym0 - Occurs name (Sch ((:) (Attr name' _) attrs)) = Apply (Apply (:||$) (Apply (Apply (:==$) name) name')) (Apply (Apply OccursSym0 name) (Apply SchSym0 attrs)) + Occurs name (Sch ((:) (Attr name' _) attrs)) = Apply (Apply (:||@#@$) (Apply (Apply (:==@#@$) name) name')) (Apply (Apply OccursSym0 name) (Apply SchSym0 attrs)) type family AttrNotIn (a :: Attribute) (a :: Schema) :: Bool where AttrNotIn _ (Sch '[]) = TrueSym0 - AttrNotIn (Attr name u) (Sch ((:) (Attr name' _) t)) = Apply (Apply (:&&$) (Apply (Apply (:/=$) name) name')) (Apply (Apply AttrNotInSym0 (Apply (Apply AttrSym0 name) u)) (Apply SchSym0 t)) + AttrNotIn (Attr name u) (Sch ((:) (Attr name' _) t)) = Apply (Apply (:&&@#@$) (Apply (Apply (:/=@#@$) name) name')) (Apply (Apply AttrNotInSym0 (Apply (Apply AttrSym0 name) u)) (Apply SchSym0 t)) type family Disjoint (a :: Schema) (a :: Schema) :: Bool where Disjoint (Sch '[]) _ = TrueSym0 - Disjoint (Sch ((:) h t)) s = Apply (Apply (:&&$) (Apply (Apply AttrNotInSym0 h) s)) (Apply (Apply DisjointSym0 (Apply SchSym0 t)) s) + Disjoint (Sch ((:) h t)) s = Apply (Apply (:&&@#@$) (Apply (Apply AttrNotInSym0 h) s)) (Apply (Apply DisjointSym0 (Apply SchSym0 t)) s) type family Append (a :: Schema) (a :: Schema) :: Schema where - Append (Sch s1) (Sch s2) = Apply SchSym0 (Apply (Apply (:++$) s1) s2) + Append (Sch s1) (Sch s2) = Apply SchSym0 (Apply (Apply (:++@#@$) s1) s2) type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: U) (a :: Symbol) :: Symbol where ShowsPrec_0123456789876543210 _ BOOL a_0123456789876543210 = Apply (Apply ShowStringSym0 "BOOL") a_0123456789876543210 ShowsPrec_0123456789876543210 _ STRING a_0123456789876543210 = Apply (Apply ShowStringSym0 "STRING") a_0123456789876543210 ShowsPrec_0123456789876543210 _ NAT a_0123456789876543210 = Apply (Apply ShowStringSym0 "NAT") a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 (VEC arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "VEC ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (VEC arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "VEC ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: U) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -592,7 +592,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations sScrutinee_0123456789876543210 :: Sing (Let0123456789876543210Scrutinee_0123456789876543210Sym4 name name' u attrs) sScrutinee_0123456789876543210 - = (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sName)) + = (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sName)) sName' in case sScrutinee_0123456789876543210 of STrue -> sU @@ -606,8 +606,8 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations (SSch (SCons (SAttr (sName' :: Sing name') _) (sAttrs :: Sing attrs))) = (applySing - ((applySing ((singFun2 @(:||$)) (%:||))) - ((applySing ((applySing ((singFun2 @(:==$)) (%:==))) sName)) + ((applySing ((singFun2 @(:||@#@$)) (%:||))) + ((applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sName)) sName'))) ((applySing ((applySing ((singFun2 @OccursSym0) sOccurs)) sName)) ((applySing ((singFun1 @SchSym0) SSch)) sAttrs)) @@ -616,8 +616,8 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations (SAttr (sName :: Sing name) (sU :: Sing u)) (SSch (SCons (SAttr (sName' :: Sing name') _) (sT :: Sing t))) = (applySing - ((applySing ((singFun2 @(:&&$)) (%:&&))) - ((applySing ((applySing ((singFun2 @(:/=$)) (%:/=))) sName)) + ((applySing ((singFun2 @(:&&@#@$)) (%:&&))) + ((applySing ((applySing ((singFun2 @(:/=@#@$)) (%:/=))) sName)) sName'))) ((applySing ((applySing ((singFun2 @AttrNotInSym0) sAttrNotIn)) @@ -628,7 +628,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations (SSch (SCons (sH :: Sing h) (sT :: Sing t))) (sS :: Sing s) = (applySing - ((applySing ((singFun2 @(:&&$)) (%:&&))) + ((applySing ((singFun2 @(:&&@#@$)) (%:&&))) ((applySing ((applySing ((singFun2 @AttrNotInSym0) sAttrNotIn)) sH)) sS))) @@ -638,7 +638,7 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations sS) sAppend (SSch (sS1 :: Sing s1)) (SSch (sS2 :: Sing s2)) = (applySing ((singFun1 @SchSym0) SSch)) - ((applySing ((applySing ((singFun2 @(:++$)) (%:++))) sS1)) sS2) + ((applySing ((applySing ((singFun2 @(:++@#@$)) (%:++))) sS1)) sS2) data instance Sing (z :: U) = z ~ BOOL => SBOOL | z ~ STRING => SSTRING | @@ -811,20 +811,20 @@ GradingClient/Database.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "VEC ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowSpaceSym0) sShowSpace))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) diff --git a/tests/compile-and-dump/GradingClient/Main.ghc82.template b/tests/compile-and-dump/GradingClient/Main.ghc82.template index 94054529..8654729a 100644 --- a/tests/compile-and-dump/GradingClient/Main.ghc82.template +++ b/tests/compile-and-dump/GradingClient/Main.ghc82.template @@ -39,19 +39,19 @@ GradingClient/Main.hs:(0,0)-(0,0): Splicing declarations type GradingSchemaSym0 = GradingSchema type NamesSym0 = Names type family MajorName :: [AChar] where - = Apply (Apply (:$) CMSym0) (Apply (Apply (:$) CASym0) (Apply (Apply (:$) CJSym0) (Apply (Apply (:$) COSym0) (Apply (Apply (:$) CRSym0) '[])))) + = Apply (Apply (:@#@$) CMSym0) (Apply (Apply (:@#@$) CASym0) (Apply (Apply (:@#@$) CJSym0) (Apply (Apply (:@#@$) COSym0) (Apply (Apply (:@#@$) CRSym0) '[])))) type family GradeName :: [AChar] where - = Apply (Apply (:$) CGSym0) (Apply (Apply (:$) CRSym0) (Apply (Apply (:$) CASym0) (Apply (Apply (:$) CDSym0) (Apply (Apply (:$) CESym0) '[])))) + = Apply (Apply (:@#@$) CGSym0) (Apply (Apply (:@#@$) CRSym0) (Apply (Apply (:@#@$) CASym0) (Apply (Apply (:@#@$) CDSym0) (Apply (Apply (:@#@$) CESym0) '[])))) type family YearName :: [AChar] where - = Apply (Apply (:$) CYSym0) (Apply (Apply (:$) CESym0) (Apply (Apply (:$) CASym0) (Apply (Apply (:$) CRSym0) '[]))) + = Apply (Apply (:@#@$) CYSym0) (Apply (Apply (:@#@$) CESym0) (Apply (Apply (:@#@$) CASym0) (Apply (Apply (:@#@$) CRSym0) '[]))) type family FirstName :: [AChar] where - = Apply (Apply (:$) CFSym0) (Apply (Apply (:$) CISym0) (Apply (Apply (:$) CRSym0) (Apply (Apply (:$) CSSym0) (Apply (Apply (:$) CTSym0) '[])))) + = Apply (Apply (:@#@$) CFSym0) (Apply (Apply (:@#@$) CISym0) (Apply (Apply (:@#@$) CRSym0) (Apply (Apply (:@#@$) CSSym0) (Apply (Apply (:@#@$) CTSym0) '[])))) type family LastName :: [AChar] where - = Apply (Apply (:$) CLSym0) (Apply (Apply (:$) CASym0) (Apply (Apply (:$) CSSym0) (Apply (Apply (:$) CTSym0) '[]))) + = Apply (Apply (:@#@$) CLSym0) (Apply (Apply (:@#@$) CASym0) (Apply (Apply (:@#@$) CSSym0) (Apply (Apply (:@#@$) CTSym0) '[]))) type family GradingSchema :: Schema where - = Apply SchSym0 (Apply (Apply (:$) (Apply (Apply AttrSym0 LastNameSym0) STRINGSym0)) (Apply (Apply (:$) (Apply (Apply AttrSym0 FirstNameSym0) STRINGSym0)) (Apply (Apply (:$) (Apply (Apply AttrSym0 YearNameSym0) NATSym0)) (Apply (Apply (:$) (Apply (Apply AttrSym0 GradeNameSym0) NATSym0)) (Apply (Apply (:$) (Apply (Apply AttrSym0 MajorNameSym0) BOOLSym0)) '[]))))) + = Apply SchSym0 (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 LastNameSym0) STRINGSym0)) (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 FirstNameSym0) STRINGSym0)) (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 YearNameSym0) NATSym0)) (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 GradeNameSym0) NATSym0)) (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 MajorNameSym0) BOOLSym0)) '[]))))) type family Names :: Schema where - = Apply SchSym0 (Apply (Apply (:$) (Apply (Apply AttrSym0 FirstNameSym0) STRINGSym0)) (Apply (Apply (:$) (Apply (Apply AttrSym0 LastNameSym0) STRINGSym0)) '[])) + = Apply SchSym0 (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 FirstNameSym0) STRINGSym0)) (Apply (Apply (:@#@$) (Apply (Apply AttrSym0 LastNameSym0) STRINGSym0)) '[])) sMajorName :: Sing (MajorNameSym0 :: [AChar]) sGradeName :: Sing (GradeNameSym0 :: [AChar]) sYearName :: Sing (YearNameSym0 :: [AChar]) @@ -60,64 +60,64 @@ GradingClient/Main.hs:(0,0)-(0,0): Splicing declarations sGradingSchema :: Sing (GradingSchemaSym0 :: Schema) sNames :: Sing (NamesSym0 :: Schema) sMajorName - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SCM)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCA)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCJ)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCO)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCR)) SNil)))) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCM)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCA)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCJ)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCO)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCR)) SNil)))) sGradeName - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SCG)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCR)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCA)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCD)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCE)) SNil)))) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCG)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCR)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCA)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCD)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCE)) SNil)))) sYearName - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SCY)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCE)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCA)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCR)) SNil))) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCY)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCE)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCA)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCR)) SNil))) sFirstName - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SCF)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCI)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCR)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCS)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCT)) SNil)))) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCF)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCI)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCR)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCS)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCT)) SNil)))) sLastName - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SCL)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCA)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCS)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SCT)) SNil))) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCL)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCA)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCS)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SCT)) SNil))) sGradingSchema = (applySing ((singFun1 @SchSym0) SSch)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sLastName)) SSTRING))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sFirstName)) SSTRING))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sYearName)) SNAT))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sGradeName)) SNAT))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sMajorName)) SBOOL))) SNil))))) sNames = (applySing ((singFun1 @SchSym0) SSch)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sFirstName)) SSTRING))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @AttrSym0) SAttr)) sLastName)) SSTRING))) SNil)) diff --git a/tests/compile-and-dump/InsertionSort/InsertionSortImp.ghc82.template b/tests/compile-and-dump/InsertionSort/InsertionSortImp.ghc82.template index 588f2624..fe14777a 100644 --- a/tests/compile-and-dump/InsertionSort/InsertionSortImp.ghc82.template +++ b/tests/compile-and-dump/InsertionSort/InsertionSortImp.ghc82.template @@ -90,8 +90,8 @@ InsertionSort/InsertionSortImp.hs:(0,0)-(0,0): Splicing declarations type family Let0123456789876543210Scrutinee_0123456789876543210 n h t where Let0123456789876543210Scrutinee_0123456789876543210 n h t = Apply (Apply LeqSym0 n) h type family Case_0123456789876543210 n h t t where - Case_0123456789876543210 n h t True = Apply (Apply (:$) n) (Apply (Apply (:$) h) t) - Case_0123456789876543210 n h t False = Apply (Apply (:$) h) (Apply (Apply InsertSym0 n) t) + Case_0123456789876543210 n h t True = Apply (Apply (:@#@$) n) (Apply (Apply (:@#@$) h) t) + Case_0123456789876543210 n h t False = Apply (Apply (:@#@$) h) (Apply (Apply InsertSym0 n) t) type LeqSym2 (t :: Nat) (t :: Nat) = Leq t t instance SuppressUnusedWarnings LeqSym1 where suppressUnusedWarnings @@ -136,7 +136,7 @@ InsertionSort/InsertionSortImp.hs:(0,0)-(0,0): Splicing declarations Leq (Succ _) Zero = FalseSym0 Leq (Succ a) (Succ b) = Apply (Apply LeqSym0 a) b type family Insert (a :: Nat) (a :: [Nat]) :: [Nat] where - Insert n '[] = Apply (Apply (:$) n) '[] + Insert n '[] = Apply (Apply (:@#@$) n) '[] Insert n ((:) h t) = Case_0123456789876543210 n h t (Let0123456789876543210Scrutinee_0123456789876543210Sym3 n h t) type family InsertionSort (a :: [Nat]) :: [Nat] where InsertionSort '[] = '[] @@ -155,7 +155,7 @@ InsertionSort/InsertionSortImp.hs:(0,0)-(0,0): Splicing declarations sLeq (SSucc (sA :: Sing a)) (SSucc (sB :: Sing b)) = (applySing ((applySing ((singFun2 @LeqSym0) sLeq)) sA)) sB sInsert (sN :: Sing n) SNil - = (applySing ((applySing ((singFun2 @(:$)) SCons)) sN)) SNil + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) sN)) SNil sInsert (sN :: Sing n) (SCons (sH :: Sing h) (sT :: Sing t)) = let sScrutinee_0123456789876543210 :: @@ -164,10 +164,10 @@ InsertionSort/InsertionSortImp.hs:(0,0)-(0,0): Splicing declarations = (applySing ((applySing ((singFun2 @LeqSym0) sLeq)) sN)) sH in case sScrutinee_0123456789876543210 of STrue - -> (applySing ((applySing ((singFun2 @(:$)) SCons)) sN)) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) sH)) sT) + -> (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) sN)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) sH)) sT) SFalse - -> (applySing ((applySing ((singFun2 @(:$)) SCons)) sH)) + -> (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) sH)) ((applySing ((applySing ((singFun2 @InsertSym0) sInsert)) sN)) sT) :: Sing (Case_0123456789876543210 n h t (Let0123456789876543210Scrutinee_0123456789876543210Sym3 n h t) :: [Nat]) diff --git a/tests/compile-and-dump/Promote/Constructors.ghc82.template b/tests/compile-and-dump/Promote/Constructors.ghc82.template index 30e46d99..eadb16f5 100644 --- a/tests/compile-and-dump/Promote/Constructors.ghc82.template +++ b/tests/compile-and-dump/Promote/Constructors.ghc82.template @@ -6,20 +6,21 @@ Promote/Constructors.hs:(0,0)-(0,0): Splicing declarations data Foo = Foo | Foo :+ Foo data Bar = Bar Bar Bar Bar Bar Foo type FooSym0 = Foo - type (:+$$$) (t :: Foo) (t :: Foo) = (:+) t t - instance SuppressUnusedWarnings (:+$$) where + type (:+@#@$$$) (t :: Foo) (t :: Foo) = (:+) t t + instance SuppressUnusedWarnings (:+@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$$###)) GHC.Tuple.()) - data (:+$$) (l :: Foo) (l :: TyFun Foo Foo) - = forall arg. SameKind (Apply ((:+$$) l) arg) ((:+$$$) l arg) => - (:+$$###) - type instance Apply ((:+$$) l) l = (:+) l l - instance SuppressUnusedWarnings (:+$) where + = snd ((GHC.Tuple.(,) (:+@#@$$###)) GHC.Tuple.()) + data (:+@#@$$) (l :: Foo) (l :: TyFun Foo Foo) + = forall arg. SameKind (Apply ((:+@#@$$) l) arg) ((:+@#@$$$) l arg) => + (:+@#@$$###) + type instance Apply ((:+@#@$$) l) l = (:+) l l + instance SuppressUnusedWarnings (:+@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$###)) GHC.Tuple.()) - data (:+$) (l :: TyFun Foo (TyFun Foo Foo -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:+$) arg) ((:+$$) arg) => (:+$###) - type instance Apply (:+$) l = (:+$$) l + = snd ((GHC.Tuple.(,) (:+@#@$###)) GHC.Tuple.()) + data (:+@#@$) (l :: TyFun Foo (TyFun Foo Foo -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:+@#@$) arg) ((:+@#@$$) arg) => + (:+@#@$###) + type instance Apply (:+@#@$) l = (:+@#@$$) l type BarSym5 (t :: Bar) (t :: Bar) (t :: Bar) (t :: Bar) (t :: Foo) = Bar t t t t t instance SuppressUnusedWarnings BarSym4 where diff --git a/tests/compile-and-dump/Promote/GenDefunSymbols.ghc82.template b/tests/compile-and-dump/Promote/GenDefunSymbols.ghc82.template index 0249efc5..fae3d2fd 100644 --- a/tests/compile-and-dump/Promote/GenDefunSymbols.ghc82.template +++ b/tests/compile-and-dump/Promote/GenDefunSymbols.ghc82.template @@ -30,18 +30,18 @@ Promote/GenDefunSymbols.hs:0:0:: Splicing declarations = forall arg. Data.Singletons.SameKind (Apply SuccSym0 arg) (SuccSym1 arg) => SuccSym0KindInference type instance Apply SuccSym0 l = Succ l - type (:+$$$) (t :: Nat) (t :: Nat) = (:+) t t - instance SuppressUnusedWarnings (:+$$) where + type (:+@#@$$$) (t :: Nat) (t :: Nat) = (:+) t t + instance SuppressUnusedWarnings (:+@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$$###)) GHC.Tuple.()) - data (:+$$) (l :: Nat) l - = forall arg. Data.Singletons.SameKind (Apply ((:+$$) l) arg) ((:+$$$) l arg) => - (:+$$###) - type instance Apply ((:+$$) l) l = (:+) l l - instance SuppressUnusedWarnings (:+$) where + = snd ((GHC.Tuple.(,) (:+@#@$$###)) GHC.Tuple.()) + data (:+@#@$$) (l :: Nat) l + = forall arg. Data.Singletons.SameKind (Apply ((:+@#@$$) l) arg) ((:+@#@$$$) l arg) => + (:+@#@$$###) + type instance Apply ((:+@#@$$) l) l = (:+) l l + instance SuppressUnusedWarnings (:+@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$###)) GHC.Tuple.()) - data (:+$) l - = forall arg. Data.Singletons.SameKind (Apply (:+$) arg) ((:+$$) arg) => - (:+$###) - type instance Apply (:+$) l = (:+$$) l + = snd ((GHC.Tuple.(,) (:+@#@$###)) GHC.Tuple.()) + data (:+@#@$) l + = forall arg. Data.Singletons.SameKind (Apply (:+@#@$) arg) ((:+@#@$$) arg) => + (:+@#@$###) + type instance Apply (:+@#@$) l = (:+@#@$$) l diff --git a/tests/compile-and-dump/Promote/Prelude.ghc82.template b/tests/compile-and-dump/Promote/Prelude.ghc82.template index 895548d3..1083483a 100644 --- a/tests/compile-and-dump/Promote/Prelude.ghc82.template +++ b/tests/compile-and-dump/Promote/Prelude.ghc82.template @@ -14,4 +14,4 @@ Promote/Prelude.hs:(0,0)-(0,0): Splicing declarations type instance Apply OddSym0 l = Odd l type family Odd (a :: Nat) :: Bool where Odd 0 = FalseSym0 - Odd n = Apply (Apply ($$) (Apply (Apply (:.$) NotSym0) OddSym0)) (Apply (Apply (:-$) n) (FromInteger 1)) + Odd n = Apply (Apply (:$@#@$) (Apply (Apply (:.@#@$) NotSym0) OddSym0)) (Apply (Apply (:-@#@$) n) (FromInteger 1)) diff --git a/tests/compile-and-dump/Singletons/AsPattern.ghc82.template b/tests/compile-and-dump/Singletons/AsPattern.ghc82.template index 106557a5..610a6f82 100644 --- a/tests/compile-and-dump/Singletons/AsPattern.ghc82.template +++ b/tests/compile-and-dump/Singletons/AsPattern.ghc82.template @@ -73,7 +73,7 @@ Singletons/AsPattern.hs:(0,0)-(0,0): Splicing declarations Let0123456789876543210PSym0KindInference type instance Apply Let0123456789876543210PSym0 l = Let0123456789876543210P l type family Let0123456789876543210P wild_0123456789876543210 where - Let0123456789876543210P wild_0123456789876543210 = Apply (Apply (:$) wild_0123456789876543210) '[] + Let0123456789876543210P wild_0123456789876543210 = Apply (Apply (:@#@$) wild_0123456789876543210) '[] type Let0123456789876543210PSym3 t t t = Let0123456789876543210P t t t instance SuppressUnusedWarnings Let0123456789876543210PSym2 where @@ -104,7 +104,7 @@ Singletons/AsPattern.hs:(0,0)-(0,0): Splicing declarations Let0123456789876543210PSym0KindInference type instance Apply Let0123456789876543210PSym0 l = Let0123456789876543210PSym1 l type family Let0123456789876543210P wild_0123456789876543210 wild_0123456789876543210 wild_0123456789876543210 where - Let0123456789876543210P wild_0123456789876543210 wild_0123456789876543210 wild_0123456789876543210 = Apply (Apply (:$) wild_0123456789876543210) (Apply (Apply (:$) wild_0123456789876543210) wild_0123456789876543210) + Let0123456789876543210P wild_0123456789876543210 wild_0123456789876543210 wild_0123456789876543210 = Apply (Apply (:@#@$) wild_0123456789876543210) (Apply (Apply (:@#@$) wild_0123456789876543210) wild_0123456789876543210) type Let0123456789876543210PSym2 t t = Let0123456789876543210P t t instance SuppressUnusedWarnings Let0123456789876543210PSym1 where suppressUnusedWarnings @@ -257,7 +257,8 @@ Singletons/AsPattern.hs:(0,0)-(0,0): Splicing declarations sP :: Sing (Let0123456789876543210PSym1 wild_0123456789876543210) sP = (applySing - ((applySing ((singFun2 @(:$)) SCons)) sWild_0123456789876543210)) + ((applySing ((singFun2 @(:@#@$)) SCons)) + sWild_0123456789876543210)) SNil in sP sFoo @@ -269,9 +270,11 @@ Singletons/AsPattern.hs:(0,0)-(0,0): Splicing declarations Sing (Let0123456789876543210PSym3 wild_0123456789876543210 wild_0123456789876543210 wild_0123456789876543210) sP = (applySing - ((applySing ((singFun2 @(:$)) SCons)) sWild_0123456789876543210)) + ((applySing ((singFun2 @(:@#@$)) SCons)) + sWild_0123456789876543210)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) sWild_0123456789876543210)) + ((applySing ((singFun2 @(:@#@$)) SCons)) + sWild_0123456789876543210)) sWild_0123456789876543210) in sP sTup diff --git a/tests/compile-and-dump/Singletons/Classes.ghc82.template b/tests/compile-and-dump/Singletons/Classes.ghc82.template index 2085dd10..f020ef17 100644 --- a/tests/compile-and-dump/Singletons/Classes.ghc82.template +++ b/tests/compile-and-dump/Singletons/Classes.ghc82.template @@ -123,23 +123,23 @@ Singletons/Classes.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply MycompareSym0 arg) (MycompareSym1 arg) => MycompareSym0KindInference type instance Apply MycompareSym0 l = MycompareSym1 l - type (:<=>$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = + type (:<=>@#@$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:<=>) t t - instance SuppressUnusedWarnings (:<=>$$) where + instance SuppressUnusedWarnings (:<=>@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:<=>$$###)) GHC.Tuple.()) - data (:<=>$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 Ordering) - = forall arg. SameKind (Apply ((:<=>$$) l) arg) ((:<=>$$$) l arg) => - (:<=>$$###) - type instance Apply ((:<=>$$) l) l = (:<=>) l l - instance SuppressUnusedWarnings (:<=>$) where + = snd ((GHC.Tuple.(,) (:<=>@#@$$###)) GHC.Tuple.()) + data (:<=>@#@$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 Ordering) + = forall arg. SameKind (Apply ((:<=>@#@$$) l) arg) ((:<=>@#@$$$) l arg) => + (:<=>@#@$$###) + type instance Apply ((:<=>@#@$$) l) l = (:<=>) l l + instance SuppressUnusedWarnings (:<=>@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:<=>$###)) GHC.Tuple.()) - data (:<=>$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 Ordering - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:<=>$) arg) ((:<=>$$) arg) => - (:<=>$###) - type instance Apply (:<=>$) l = (:<=>$$) l + = snd ((GHC.Tuple.(,) (:<=>@#@$###)) GHC.Tuple.()) + data (:<=>@#@$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 Ordering + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:<=>@#@$) arg) ((:<=>@#@$$) arg) => + (:<=>@#@$###) + type instance Apply (:<=>@#@$) l = (:<=>@#@$$) l type family TFHelper_0123456789876543210 (a :: a) (a :: a) :: Ordering where TFHelper_0123456789876543210 a_0123456789876543210 a_0123456789876543210 = Apply (Apply MycompareSym0 a_0123456789876543210) a_0123456789876543210 type TFHelper_0123456789876543210Sym2 (t :: a0123456789876543210) (t :: a0123456789876543210) = @@ -309,11 +309,11 @@ Singletons/Classes.hs:(0,0)-(0,0): Splicing declarations -> Sing t -> Sing (Apply (Apply MycompareSym0 t) t :: Ordering) (%:<=>) :: forall (t :: a) (t :: a). - Sing t -> Sing t -> Sing (Apply (Apply (:<=>$) t) t :: Ordering) + Sing t -> Sing t -> Sing (Apply (Apply (:<=>@#@$) t) t :: Ordering) default (%:<=>) :: forall (t :: a) (t :: a). - (Apply (Apply (:<=>$) t) t :: Ordering) ~ Apply (Apply TFHelper_0123456789876543210Sym0 t) t => - Sing t -> Sing t -> Sing (Apply (Apply (:<=>$) t) t :: Ordering) + (Apply (Apply (:<=>@#@$) t) t :: Ordering) ~ Apply (Apply TFHelper_0123456789876543210Sym0 t) t => + Sing t -> Sing t -> Sing (Apply (Apply (:<=>@#@$) t) t :: Ordering) (%:<=>) (sA_0123456789876543210 :: Sing a_0123456789876543210) (sA_0123456789876543210 :: Sing a_0123456789876543210) diff --git a/tests/compile-and-dump/Singletons/Contains.ghc82.template b/tests/compile-and-dump/Singletons/Contains.ghc82.template index b91d06a2..d013f0e4 100644 --- a/tests/compile-and-dump/Singletons/Contains.ghc82.template +++ b/tests/compile-and-dump/Singletons/Contains.ghc82.template @@ -26,7 +26,7 @@ Singletons/Contains.hs:(0,0)-(0,0): Splicing declarations type instance Apply ContainsSym0 l = ContainsSym1 l type family Contains (a :: a) (a :: [a]) :: Bool where Contains _ '[] = FalseSym0 - Contains elt ((:) h t) = Apply (Apply (:||$) (Apply (Apply (:==$) elt) h)) (Apply (Apply ContainsSym0 elt) t) + Contains elt ((:) h t) = Apply (Apply (:||@#@$) (Apply (Apply (:==@#@$) elt) h)) (Apply (Apply ContainsSym0 elt) t) sContains :: forall (t :: a) (t :: [a]). SEq a => @@ -34,8 +34,9 @@ Singletons/Contains.hs:(0,0)-(0,0): Splicing declarations sContains _ SNil = SFalse sContains (sElt :: Sing elt) (SCons (sH :: Sing h) (sT :: Sing t)) = (applySing - ((applySing ((singFun2 @(:||$)) (%:||))) - ((applySing ((applySing ((singFun2 @(:==$)) (%:==))) sElt)) sH))) + ((applySing ((singFun2 @(:||@#@$)) (%:||))) + ((applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sElt)) + sH))) ((applySing ((applySing ((singFun2 @ContainsSym0) sContains)) sElt)) sT) diff --git a/tests/compile-and-dump/Singletons/DataValues.ghc82.template b/tests/compile-and-dump/Singletons/DataValues.ghc82.template index b49ec2d9..fc9fefb3 100644 --- a/tests/compile-and-dump/Singletons/DataValues.ghc82.template +++ b/tests/compile-and-dump/Singletons/DataValues.ghc82.template @@ -38,15 +38,15 @@ Singletons/DataValues.hs:(0,0)-(0,0): Splicing declarations type ComplexSym0 = Complex type PrSym0 = Pr type family AList where - = Apply (Apply (:$) ZeroSym0) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:$) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0))) '[])) + = Apply (Apply (:@#@$) ZeroSym0) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:@#@$) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0))) '[])) type family Tuple where = Apply (Apply (Apply Tuple3Sym0 FalseSym0) (Apply JustSym0 ZeroSym0)) TrueSym0 type family Complex where = Apply (Apply PairSym0 (Apply (Apply PairSym0 (Apply JustSym0 ZeroSym0)) ZeroSym0)) FalseSym0 type family Pr where - = Apply (Apply PairSym0 (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:$) ZeroSym0) '[]) + = Apply (Apply PairSym0 (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:@#@$) ZeroSym0) '[]) type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Pair a b) (a :: Symbol) :: Symbol where - ShowsPrec_0123456789876543210 p_0123456789876543210 (Pair arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "Pair ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (Pair arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "Pair ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Pair a0123456789876543210 b0123456789876543210) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -86,12 +86,12 @@ Singletons/DataValues.hs:(0,0)-(0,0): Splicing declarations sComplex :: Sing ComplexSym0 sPr :: Sing PrSym0 sAList - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)))) SNil)) @@ -112,7 +112,7 @@ Singletons/DataValues.hs:(0,0)-(0,0): Splicing declarations = (applySing ((applySing ((singFun2 @PairSym0) SPair)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) SNil) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) SNil) data instance Sing (z :: Pair a b) = forall (n :: a) (n :: b). z ~ Pair n n => SPair (Sing (n :: a)) (Sing (n :: b)) @@ -147,20 +147,20 @@ Singletons/DataValues.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Pair ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowSpaceSym0) sShowSpace))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) diff --git a/tests/compile-and-dump/Singletons/EnumDeriving.ghc82.template b/tests/compile-and-dump/Singletons/EnumDeriving.ghc82.template index b4c9a717..fdb9b903 100644 --- a/tests/compile-and-dump/Singletons/EnumDeriving.ghc82.template +++ b/tests/compile-and-dump/Singletons/EnumDeriving.ghc82.template @@ -19,12 +19,12 @@ Singletons/EnumDeriving.hs:(0,0)-(0,0): Splicing declarations Case_0123456789876543210 n False = Apply ErrorSym0 "toEnum: bad argument" type family Case_0123456789876543210 n t where Case_0123456789876543210 n True = BazSym0 - Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 2)) + Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 2)) type family Case_0123456789876543210 n t where Case_0123456789876543210 n True = BarSym0 - Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) + Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) type family ToEnum_0123456789876543210 (a :: GHC.Types.Nat) :: Foo where - ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) + ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) type ToEnum_0123456789876543210Sym1 (t :: GHC.Types.Nat) = ToEnum_0123456789876543210 t instance SuppressUnusedWarnings ToEnum_0123456789876543210Sym0 where @@ -86,26 +86,26 @@ Singletons/EnumDeriving.hs:(0,0)-(0,0): Splicing declarations -> GHC.Types.Type) t :: GHC.Types.Nat) sToEnum (sN :: Sing n) = case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 0)) of STrue -> SBar SFalse -> case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 1)) of STrue -> SBaz SFalse -> case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 2)) of STrue -> SBum SFalse -> sError (sing :: Sing "toEnum: bad argument") :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 2)) :: Foo) :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) :: Foo) :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) :: Foo) + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 2)) :: Foo) :: + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) :: Foo) :: + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) :: Foo) sFromEnum SBar = sFromInteger (sing :: Sing 0) sFromEnum SBaz = sFromInteger (sing :: Sing 1) sFromEnum SBum = sFromInteger (sing :: Sing 2) @@ -127,9 +127,9 @@ Singletons/EnumDeriving.hs:0:0:: Splicing declarations Case_0123456789876543210 n False = Apply ErrorSym0 "toEnum: bad argument" type family Case_0123456789876543210 n t where Case_0123456789876543210 n True = Q1Sym0 - Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) + Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) type family ToEnum_0123456789876543210 (a :: GHC.Types.Nat) :: Quux where - ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) + ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) type ToEnum_0123456789876543210Sym1 (t :: GHC.Types.Nat) = ToEnum_0123456789876543210 t instance SuppressUnusedWarnings ToEnum_0123456789876543210Sym0 where @@ -171,18 +171,18 @@ Singletons/EnumDeriving.hs:0:0:: Splicing declarations -> GHC.Types.Type) t :: GHC.Types.Nat) sToEnum (sN :: Sing n) = case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 0)) of STrue -> SQ1 SFalse -> case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 1)) of STrue -> SQ2 SFalse -> sError (sing :: Sing "toEnum: bad argument") :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) :: Quux) :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) :: Quux) + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) :: Quux) :: + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) :: Quux) sFromEnum SQ1 = sFromInteger (sing :: Sing 0) sFromEnum SQ2 = sFromInteger (sing :: Sing 1) diff --git a/tests/compile-and-dump/Singletons/Fixity.ghc82.template b/tests/compile-and-dump/Singletons/Fixity.ghc82.template index 1d9dfc7d..e42b2bd3 100644 --- a/tests/compile-and-dump/Singletons/Fixity.ghc82.template +++ b/tests/compile-and-dump/Singletons/Fixity.ghc82.template @@ -16,53 +16,53 @@ Singletons/Fixity.hs:(0,0)-(0,0): Splicing declarations (====) :: a -> a -> a (====) a _ = a infix 4 ==== - type (:====$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = + type (:====@#@$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:====) t t - instance SuppressUnusedWarnings (:====$$) where + instance SuppressUnusedWarnings (:====@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:====$$###)) GHC.Tuple.()) - data (:====$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 a0123456789876543210) - = forall arg. SameKind (Apply ((:====$$) l) arg) ((:====$$$) l arg) => - (:====$$###) - type instance Apply ((:====$$) l) l = (:====) l l - instance SuppressUnusedWarnings (:====$) where + = snd ((GHC.Tuple.(,) (:====@#@$$###)) GHC.Tuple.()) + data (:====@#@$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 a0123456789876543210) + = forall arg. SameKind (Apply ((:====@#@$$) l) arg) ((:====@#@$$$) l arg) => + (:====@#@$$###) + type instance Apply ((:====@#@$$) l) l = (:====) l l + instance SuppressUnusedWarnings (:====@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:====$###)) GHC.Tuple.()) - data (:====$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 a0123456789876543210 - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:====$) arg) ((:====$$) arg) => - (:====$###) - type instance Apply (:====$) l = (:====$$) l + = snd ((GHC.Tuple.(,) (:====@#@$###)) GHC.Tuple.()) + data (:====@#@$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 a0123456789876543210 + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:====@#@$) arg) ((:====@#@$$) arg) => + (:====@#@$###) + type instance Apply (:====@#@$) l = (:====@#@$$) l type family (:====) (a :: a) (a :: a) :: a where (:====) a _ = a infix 4 :==== infix 4 :<=> - type (:<=>$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = + type (:<=>@#@$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:<=>) t t - instance SuppressUnusedWarnings (:<=>$$) where + instance SuppressUnusedWarnings (:<=>@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:<=>$$###)) GHC.Tuple.()) - data (:<=>$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 Ordering) - = forall arg. SameKind (Apply ((:<=>$$) l) arg) ((:<=>$$$) l arg) => - (:<=>$$###) - type instance Apply ((:<=>$$) l) l = (:<=>) l l - instance SuppressUnusedWarnings (:<=>$) where + = snd ((GHC.Tuple.(,) (:<=>@#@$$###)) GHC.Tuple.()) + data (:<=>@#@$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 Ordering) + = forall arg. SameKind (Apply ((:<=>@#@$$) l) arg) ((:<=>@#@$$$) l arg) => + (:<=>@#@$$###) + type instance Apply ((:<=>@#@$$) l) l = (:<=>) l l + instance SuppressUnusedWarnings (:<=>@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:<=>$###)) GHC.Tuple.()) - data (:<=>$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 Ordering - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:<=>$) arg) ((:<=>$$) arg) => - (:<=>$###) - type instance Apply (:<=>$) l = (:<=>$$) l + = snd ((GHC.Tuple.(,) (:<=>@#@$###)) GHC.Tuple.()) + data (:<=>@#@$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 Ordering + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:<=>@#@$) arg) ((:<=>@#@$$) arg) => + (:<=>@#@$###) + type instance Apply (:<=>@#@$) l = (:<=>@#@$$) l class PMyOrd (a :: GHC.Types.Type) where type (:<=>) (arg :: a) (arg :: a) :: Ordering infix 4 %:==== infix 4 %:<=> (%:====) :: forall (t :: a) (t :: a). - Sing t -> Sing t -> Sing (Apply (Apply (:====$) t) t :: a) + Sing t -> Sing t -> Sing (Apply (Apply (:====@#@$) t) t :: a) (%:====) (sA :: Sing a) _ = sA class SMyOrd a where (%:<=>) :: forall (t :: a) (t :: a). - Sing t -> Sing t -> Sing (Apply (Apply (:<=>$) t) t :: Ordering) + Sing t -> Sing t -> Sing (Apply (Apply (:<=>@#@$) t) t :: Ordering) diff --git a/tests/compile-and-dump/Singletons/HigherOrder.ghc82.template b/tests/compile-and-dump/Singletons/HigherOrder.ghc82.template index f1bfa023..44553fe9 100644 --- a/tests/compile-and-dump/Singletons/HigherOrder.ghc82.template +++ b/tests/compile-and-dump/Singletons/HigherOrder.ghc82.template @@ -298,7 +298,7 @@ Singletons/HigherOrder.hs:(0,0)-(0,0): Splicing declarations Foo f g a = Apply (Apply f g) a type family ZipWith (a :: TyFun a (TyFun b c -> GHC.Types.Type) -> GHC.Types.Type) (a :: [a]) (a :: [b]) :: [c] where - ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) + ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:@#@$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) ZipWith _ '[] '[] = '[] ZipWith _ ((:) _ _) '[] = '[] ZipWith _ '[] ((:) _ _) = '[] @@ -313,7 +313,7 @@ Singletons/HigherOrder.hs:(0,0)-(0,0): Splicing declarations type family Map (a :: TyFun a b -> GHC.Types.Type) (a :: [a]) :: [b] where Map _ '[] = '[] - Map f ((:) h t) = Apply (Apply (:$) (Apply f h)) (Apply (Apply MapSym0 f) t) + Map f ((:) h t) = Apply (Apply (:@#@$) (Apply f h)) (Apply (Apply MapSym0 f) t) sFoo :: forall (t :: TyFun (TyFun a b -> GHC.Types.Type) (TyFun a b -> GHC.Types.Type) @@ -351,7 +351,7 @@ Singletons/HigherOrder.hs:(0,0)-(0,0): Splicing declarations (SCons (sX :: Sing x) (sXs :: Sing xs)) (SCons (sY :: Sing y) (sYs :: Sing ys)) = (applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing sF) sX)) sY))) ((applySing ((applySing ((applySing ((singFun3 @ZipWithSym0) sZipWith)) sF)) @@ -401,7 +401,7 @@ Singletons/HigherOrder.hs:(0,0)-(0,0): Splicing declarations sMap _ SNil = SNil sMap (sF :: Sing f) (SCons (sH :: Sing h) (sT :: Sing t)) = (applySing - ((applySing ((singFun2 @(:$)) SCons)) ((applySing sF) sH))) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing sF) sH))) ((applySing ((applySing ((singFun2 @MapSym0) sMap)) sF)) sT) data instance Sing (z :: Either a b) = forall (n :: a). z ~ Left n => SLeft (Sing (n :: a)) | diff --git a/tests/compile-and-dump/Singletons/LambdasComprehensive.ghc82.template b/tests/compile-and-dump/Singletons/LambdasComprehensive.ghc82.template index cf2a07a3..7b7f89f2 100644 --- a/tests/compile-and-dump/Singletons/LambdasComprehensive.ghc82.template +++ b/tests/compile-and-dump/Singletons/LambdasComprehensive.ghc82.template @@ -28,9 +28,9 @@ Singletons/LambdasComprehensive.hs:(0,0)-(0,0): Splicing declarations type BarSym0 = Bar type FooSym0 = Foo type family Bar :: [Nat] where - = Apply (Apply MapSym0 (Apply (Apply Either_Sym0 PredSym0) SuccSym0)) (Apply (Apply (:$) (Apply LeftSym0 ZeroSym0)) (Apply (Apply (:$) (Apply RightSym0 (Apply SuccSym0 ZeroSym0))) '[])) + = Apply (Apply MapSym0 (Apply (Apply Either_Sym0 PredSym0) SuccSym0)) (Apply (Apply (:@#@$) (Apply LeftSym0 ZeroSym0)) (Apply (Apply (:@#@$) (Apply RightSym0 (Apply SuccSym0 ZeroSym0))) '[])) type family Foo :: [Nat] where - = Apply (Apply MapSym0 Lambda_0123456789876543210Sym0) (Apply (Apply (:$) (Apply LeftSym0 ZeroSym0)) (Apply (Apply (:$) (Apply RightSym0 (Apply SuccSym0 ZeroSym0))) '[])) + = Apply (Apply MapSym0 Lambda_0123456789876543210Sym0) (Apply (Apply (:@#@$) (Apply LeftSym0 ZeroSym0)) (Apply (Apply (:@#@$) (Apply RightSym0 (Apply SuccSym0 ZeroSym0))) '[])) sBar :: Sing (BarSym0 :: [Nat]) sFoo :: Sing (FooSym0 :: [Nat]) sBar @@ -41,10 +41,10 @@ Singletons/LambdasComprehensive.hs:(0,0)-(0,0): Splicing declarations ((singFun1 @PredSym0) sPred))) ((singFun1 @SuccSym0) SSucc)))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @LeftSym0) SLeft)) SZero))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @RightSym0) SRight)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)))) SNil)) @@ -62,10 +62,10 @@ Singletons/LambdasComprehensive.hs:(0,0)-(0,0): Splicing declarations ((singFun1 @SuccSym0) SSucc))) sX })))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @LeftSym0) SLeft)) SZero))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @RightSym0) SRight)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)))) SNil)) diff --git a/tests/compile-and-dump/Singletons/LetStatements.ghc82.template b/tests/compile-and-dump/Singletons/LetStatements.ghc82.template index 9a133999..53d1b531 100644 --- a/tests/compile-and-dump/Singletons/LetStatements.ghc82.template +++ b/tests/compile-and-dump/Singletons/LetStatements.ghc82.template @@ -245,36 +245,36 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations type instance Apply Let0123456789876543210BarSym0 l = Let0123456789876543210Bar l type family Let0123456789876543210Bar x :: a where Let0123456789876543210Bar x = x - type (:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) t (t :: Nat) (t :: Nat) = + type (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) t (t :: Nat) (t :: Nat) = (:<<<%%%%%%%%%%%%%%%%%%%:+) t t t - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) where + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) l l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) l l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l (l :: TyFun Nat (TyFun Nat Nat - -> GHC.Types.Type)) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l (l :: TyFun Nat (TyFun Nat Nat + -> GHC.Types.Type)) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$) l - = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$###) - type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l + = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###) + type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l type family (:<<<%%%%%%%%%%%%%%%%%%%:+) x (a :: Nat) (a :: Nat) :: Nat where (:<<<%%%%%%%%%%%%%%%%%%%:+) x Zero m = m - (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) n) x) + (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) n) x) type Let0123456789876543210ZSym1 t = Let0123456789876543210Z t instance SuppressUnusedWarnings Let0123456789876543210ZSym0 where suppressUnusedWarnings @@ -285,68 +285,68 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply Let0123456789876543210ZSym0 arg) (Let0123456789876543210ZSym1 arg) => Let0123456789876543210ZSym0KindInference type instance Apply Let0123456789876543210ZSym0 l = Let0123456789876543210Z l - type (:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) t (t :: Nat) (t :: Nat) = + type (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) t (t :: Nat) (t :: Nat) = (:<<<%%%%%%%%%%%%%%%%%%%:+) t t t - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) where + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) l l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) l l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l (l :: TyFun Nat (TyFun Nat Nat - -> GHC.Types.Type)) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l (l :: TyFun Nat (TyFun Nat Nat + -> GHC.Types.Type)) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$) l - = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$###) - type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l + = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###) + type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l type family Let0123456789876543210Z x :: Nat where Let0123456789876543210Z x = x type family (:<<<%%%%%%%%%%%%%%%%%%%:+) x (a :: Nat) (a :: Nat) :: Nat where (:<<<%%%%%%%%%%%%%%%%%%%:+) x Zero m = m - (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) n) m) - type (:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) t (t :: Nat) (t :: Nat) = + (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) n) m) + type (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) t (t :: Nat) (t :: Nat) = (:<<<%%%%%%%%%%%%%%%%%%%:+) t t t - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) where + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$$) l l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$$) l l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+) l l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l (l :: TyFun Nat (TyFun Nat Nat - -> GHC.Types.Type)) - = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$$###) - type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$$) l l - instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+$) where + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l (l :: TyFun Nat (TyFun Nat Nat + -> GHC.Types.Type)) + = forall arg. SameKind (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$###) + type instance Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$$) l l + instance SuppressUnusedWarnings (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) where suppressUnusedWarnings = snd - ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+$###)) GHC.Tuple.()) - data (:<<<%%%%%%%%%%%%%%%%%%%:+$) l - = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) arg) => - (:<<<%%%%%%%%%%%%%%%%%%%:+$###) - type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+$$) l + ((GHC.Tuple.(,) (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###)) GHC.Tuple.()) + data (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l + = forall arg. SameKind (Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) arg) ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) arg) => + (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$###) + type instance Apply (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$) l = (:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) l type family (:<<<%%%%%%%%%%%%%%%%%%%:+) x (a :: Nat) (a :: Nat) :: Nat where (:<<<%%%%%%%%%%%%%%%%%%%:+) x Zero m = m - (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) n) m) + (:<<<%%%%%%%%%%%%%%%%%%%:+) x (Succ n) m = Apply SuccSym0 (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) n) m) type family Lambda_0123456789876543210 x a_0123456789876543210 t where Lambda_0123456789876543210 x a_0123456789876543210 x = x type Lambda_0123456789876543210Sym3 t t t = @@ -695,11 +695,11 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations type family Foo13 (a :: a) :: a where Foo13 x = Apply Foo13_Sym0 (Let0123456789876543210BarSym1 x) type family Foo12 (a :: Nat) :: Nat where - Foo12 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) x) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0)) + Foo12 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) x) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0)) type family Foo11 (a :: Nat) :: Nat where - Foo11 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) (Apply SuccSym0 ZeroSym0)) (Let0123456789876543210ZSym1 x) + Foo11 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) (Apply SuccSym0 ZeroSym0)) (Let0123456789876543210ZSym1 x) type family Foo10 (a :: Nat) :: Nat where - Foo10 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) (Apply SuccSym0 ZeroSym0)) x + Foo10 x = Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) (Apply SuccSym0 ZeroSym0)) x type family Foo9 (a :: Nat) :: Nat where Foo9 x = Apply (Let0123456789876543210ZSym1 x) x type family Foo8 (a :: Nat) :: Nat where @@ -780,17 +780,19 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations forall (t :: Nat) (t :: Nat). Sing t -> Sing t - -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) t) t :: Nat) + -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) t) t :: Nat) (%:+) SZero (sM :: Sing m) = sM (%:+) (SSucc (sN :: Sing n)) (sM :: Sing m) = (applySing ((singFun1 @SuccSym0) SSucc)) ((applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) sN)) sX) in (applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) sX)) ((applySing ((singFun1 @SuccSym0) SSucc)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)) @@ -801,18 +803,20 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations forall (t :: Nat) (t :: Nat). Sing t -> Sing t - -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) t) t :: Nat) + -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) t) t :: Nat) sZ = sX (%:+) SZero (sM :: Sing m) = sM (%:+) (SSucc (sN :: Sing n)) (sM :: Sing m) = (applySing ((singFun1 @SuccSym0) SSucc)) ((applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) sN)) sM) in (applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) sZ sFoo10 (sX :: Sing x) @@ -821,17 +825,19 @@ Singletons/LetStatements.hs:(0,0)-(0,0): Splicing declarations forall (t :: Nat) (t :: Nat). Sing t -> Sing t - -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x) t) t :: Nat) + -> Sing (Apply (Apply ((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x) t) t :: Nat) (%:+) SZero (sM :: Sing m) = sM (%:+) (SSucc (sN :: Sing n)) (sM :: Sing m) = (applySing ((singFun1 @SuccSym0) SSucc)) ((applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) sN)) sM) in (applySing - ((applySing ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+$$) x)) (%:+))) + ((applySing + ((singFun2 @((:<<<%%%%%%%%%%%%%%%%%%%:+@#@$$) x)) (%:+))) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) sX sFoo9 (sX :: Sing x) diff --git a/tests/compile-and-dump/Singletons/Maybe.ghc82.template b/tests/compile-and-dump/Singletons/Maybe.ghc82.template index bab31fb9..f29d94df 100644 --- a/tests/compile-and-dump/Singletons/Maybe.ghc82.template +++ b/tests/compile-and-dump/Singletons/Maybe.ghc82.template @@ -18,7 +18,7 @@ Singletons/Maybe.hs:(0,0)-(0,0): Splicing declarations type instance Apply JustSym0 l = Just l type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Maybe a) (a :: GHC.Types.Symbol) :: GHC.Types.Symbol where ShowsPrec_0123456789876543210 _ Nothing a_0123456789876543210 = Apply (Apply ShowStringSym0 "Nothing") a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 (Just arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "Just ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (Just arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "Just ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Maybe a0123456789876543210) (t :: GHC.Types.Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -102,10 +102,10 @@ Singletons/Maybe.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Just ")))) ((applySing diff --git a/tests/compile-and-dump/Singletons/Nat.ghc82.template b/tests/compile-and-dump/Singletons/Nat.ghc82.template index 826ac9a9..40cf50c5 100644 --- a/tests/compile-and-dump/Singletons/Nat.ghc82.template +++ b/tests/compile-and-dump/Singletons/Nat.ghc82.template @@ -64,7 +64,7 @@ Singletons/Nat.hs:(0,0)-(0,0): Splicing declarations Plus (Succ n) m = Apply SuccSym0 (Apply (Apply PlusSym0 n) m) type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Nat) (a :: GHC.Types.Symbol) :: GHC.Types.Symbol where ShowsPrec_0123456789876543210 _ Zero a_0123456789876543210 = Apply (Apply ShowStringSym0 "Zero") a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 (Succ arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "Succ ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (Succ arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (Data.Singletons.Prelude.Num.FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "Succ ")) (Apply (Apply ShowsPrecSym0 (Data.Singletons.Prelude.Num.FromInteger 11)) arg_0123456789876543210))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Nat) (t :: GHC.Types.Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -157,10 +157,10 @@ Singletons/Nat.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (Data.Singletons.Prelude.Num.sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Succ ")))) ((applySing diff --git a/tests/compile-and-dump/Singletons/Operators.ghc82.template b/tests/compile-and-dump/Singletons/Operators.ghc82.template index 5d65afa1..21408686 100644 --- a/tests/compile-and-dump/Singletons/Operators.ghc82.template +++ b/tests/compile-and-dump/Singletons/Operators.ghc82.template @@ -23,35 +23,36 @@ Singletons/Operators.hs:(0,0)-(0,0): Splicing declarations (+) Zero m = m (+) (Succ n) m = Succ (n + m) type FLeafSym0 = FLeaf - type (:+:$$$) (t :: Foo) (t :: Foo) = (:+:) t t - instance SuppressUnusedWarnings (:+:$$) where + type (:+:@#@$$$) (t :: Foo) (t :: Foo) = (:+:) t t + instance SuppressUnusedWarnings (:+:@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+:$$###)) GHC.Tuple.()) - data (:+:$$) (l :: Foo) (l :: TyFun Foo Foo) - = forall arg. SameKind (Apply ((:+:$$) l) arg) ((:+:$$$) l arg) => - (:+:$$###) - type instance Apply ((:+:$$) l) l = (:+:) l l - instance SuppressUnusedWarnings (:+:$) where + = snd ((GHC.Tuple.(,) (:+:@#@$$###)) GHC.Tuple.()) + data (:+:@#@$$) (l :: Foo) (l :: TyFun Foo Foo) + = forall arg. SameKind (Apply ((:+:@#@$$) l) arg) ((:+:@#@$$$) l arg) => + (:+:@#@$$###) + type instance Apply ((:+:@#@$$) l) l = (:+:) l l + instance SuppressUnusedWarnings (:+:@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+:$###)) GHC.Tuple.()) - data (:+:$) (l :: TyFun Foo (TyFun Foo Foo -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:+:$) arg) ((:+:$$) arg) => - (:+:$###) - type instance Apply (:+:$) l = (:+:$$) l - type (:+$$$) (t :: Nat) (t :: Nat) = (:+) t t - instance SuppressUnusedWarnings (:+$$) where + = snd ((GHC.Tuple.(,) (:+:@#@$###)) GHC.Tuple.()) + data (:+:@#@$) (l :: TyFun Foo (TyFun Foo Foo -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:+:@#@$) arg) ((:+:@#@$$) arg) => + (:+:@#@$###) + type instance Apply (:+:@#@$) l = (:+:@#@$$) l + type (:+@#@$$$) (t :: Nat) (t :: Nat) = (:+) t t + instance SuppressUnusedWarnings (:+@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$$###)) GHC.Tuple.()) - data (:+$$) (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply ((:+$$) l) arg) ((:+$$$) l arg) => - (:+$$###) - type instance Apply ((:+$$) l) l = (:+) l l - instance SuppressUnusedWarnings (:+$) where + = snd ((GHC.Tuple.(,) (:+@#@$$###)) GHC.Tuple.()) + data (:+@#@$$) (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:+@#@$$) l) arg) ((:+@#@$$$) l arg) => + (:+@#@$$###) + type instance Apply ((:+@#@$$) l) l = (:+) l l + instance SuppressUnusedWarnings (:+@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$###)) GHC.Tuple.()) - data (:+$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:+$) arg) ((:+$$) arg) => (:+$###) - type instance Apply (:+$) l = (:+$$) l + = snd ((GHC.Tuple.(,) (:+@#@$###)) GHC.Tuple.()) + data (:+@#@$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:+@#@$) arg) ((:+@#@$$) arg) => + (:+@#@$###) + type instance Apply (:+@#@$) l = (:+@#@$$) l type ChildSym1 (t :: Foo) = Child t instance SuppressUnusedWarnings ChildSym0 where suppressUnusedWarnings @@ -62,19 +63,19 @@ Singletons/Operators.hs:(0,0)-(0,0): Splicing declarations type instance Apply ChildSym0 l = Child l type family (:+) (a :: Nat) (a :: Nat) :: Nat where (:+) Zero m = m - (:+) (Succ n) m = Apply SuccSym0 (Apply (Apply (:+$) n) m) + (:+) (Succ n) m = Apply SuccSym0 (Apply (Apply (:+@#@$) n) m) type family Child (a :: Foo) :: Foo where Child FLeaf = FLeafSym0 Child ((:+:) a _) = a (%:+) :: forall (t :: Nat) (t :: Nat). - Sing t -> Sing t -> Sing (Apply (Apply (:+$) t) t :: Nat) + Sing t -> Sing t -> Sing (Apply (Apply (:+@#@$) t) t :: Nat) sChild :: forall (t :: Foo). Sing t -> Sing (Apply ChildSym0 t :: Foo) (%:+) SZero (sM :: Sing m) = sM (%:+) (SSucc (sN :: Sing n)) (sM :: Sing m) = (applySing ((singFun1 @SuccSym0) SSucc)) - ((applySing ((applySing ((singFun2 @(:+$)) (%:+))) sN)) sM) + ((applySing ((applySing ((singFun2 @(:+@#@$)) (%:+))) sN)) sM) sChild SFLeaf = SFLeaf sChild ((:%+:) (sA :: Sing a) _) = sA data instance Sing (z :: Foo) diff --git a/tests/compile-and-dump/Singletons/OrdDeriving.ghc82.template b/tests/compile-and-dump/Singletons/OrdDeriving.ghc82.template index c7bd5f8c..723a3038 100644 --- a/tests/compile-and-dump/Singletons/OrdDeriving.ghc82.template +++ b/tests/compile-and-dump/Singletons/OrdDeriving.ghc82.template @@ -250,7 +250,7 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations type instance Apply FSym0 l = FSym1 l type family Compare_0123456789876543210 (a :: Nat) (a :: Nat) :: Ordering where Compare_0123456789876543210 Zero Zero = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] - Compare_0123456789876543210 (Succ a_0123456789876543210) (Succ b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) + Compare_0123456789876543210 (Succ a_0123456789876543210) (Succ b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) Compare_0123456789876543210 Zero (Succ _) = LTSym0 Compare_0123456789876543210 (Succ _) Zero = GTSym0 type Compare_0123456789876543210Sym2 (t :: Nat) (t :: Nat) = @@ -277,12 +277,12 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations instance POrd Nat where type Compare (a :: Nat) (a :: Nat) = Apply (Apply Compare_0123456789876543210Sym0 a) a type family Compare_0123456789876543210 (a :: Foo a b c d) (a :: Foo a b c d) :: Ordering where - Compare_0123456789876543210 (A a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (A b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) - Compare_0123456789876543210 (B a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (B b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) - Compare_0123456789876543210 (C a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (C b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) - Compare_0123456789876543210 (D a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (D b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) - Compare_0123456789876543210 (E a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (E b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) - Compare_0123456789876543210 (F a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (F b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (A a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (A b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (B a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (B b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (C a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (C b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (D a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (D b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (E a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (E b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) + Compare_0123456789876543210 (F a_0123456789876543210 a_0123456789876543210 a_0123456789876543210 a_0123456789876543210) (F b_0123456789876543210 b_0123456789876543210 b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])))) Compare_0123456789876543210 (A _ _ _ _) (B _ _ _ _) = LTSym0 Compare_0123456789876543210 (A _ _ _ _) (C _ _ _ _) = LTSym0 Compare_0123456789876543210 (A _ _ _ _) (D _ _ _ _) = LTSym0 @@ -472,7 +472,7 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -505,25 +505,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -544,25 +544,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -583,25 +583,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -622,25 +622,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -661,25 +661,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -700,25 +700,25 @@ Singletons/OrdDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) diff --git a/tests/compile-and-dump/Singletons/PatternMatching.ghc82.template b/tests/compile-and-dump/Singletons/PatternMatching.ghc82.template index 5b4ac5fc..003f141e 100644 --- a/tests/compile-and-dump/Singletons/PatternMatching.ghc82.template +++ b/tests/compile-and-dump/Singletons/PatternMatching.ghc82.template @@ -38,15 +38,15 @@ Singletons/PatternMatching.hs:(0,0)-(0,0): Splicing declarations type ComplexSym0 = Complex type PrSym0 = Pr type family AList where - = Apply (Apply (:$) ZeroSym0) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:$) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0))) '[])) + = Apply (Apply (:@#@$) ZeroSym0) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:@#@$) (Apply SuccSym0 (Apply SuccSym0 ZeroSym0))) '[])) type family Tuple where = Apply (Apply (Apply Tuple3Sym0 FalseSym0) (Apply JustSym0 ZeroSym0)) TrueSym0 type family Complex where = Apply (Apply PairSym0 (Apply (Apply PairSym0 (Apply JustSym0 ZeroSym0)) ZeroSym0)) FalseSym0 type family Pr where - = Apply (Apply PairSym0 (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:$) ZeroSym0) '[]) + = Apply (Apply PairSym0 (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:@#@$) ZeroSym0) '[]) type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Pair a b) (a :: Symbol) :: Symbol where - ShowsPrec_0123456789876543210 p_0123456789876543210 (Pair arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "Pair ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (Pair arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "Pair ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Pair a0123456789876543210 b0123456789876543210) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -86,12 +86,12 @@ Singletons/PatternMatching.hs:(0,0)-(0,0): Splicing declarations sComplex :: Sing ComplexSym0 sPr :: Sing PrSym0 sAList - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)))) SNil)) @@ -112,7 +112,7 @@ Singletons/PatternMatching.hs:(0,0)-(0,0): Splicing declarations = (applySing ((applySing ((singFun2 @PairSym0) SPair)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) SNil) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) SNil) data instance Sing (z :: Pair a b) = forall (n :: a) (n :: b). z ~ Pair n n => SPair (Sing (n :: a)) (Sing (n :: b)) @@ -147,20 +147,20 @@ Singletons/PatternMatching.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "Pair ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowSpaceSym0) sShowSpace))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) diff --git a/tests/compile-and-dump/Singletons/Sections.ghc82.template b/tests/compile-and-dump/Singletons/Sections.ghc82.template index 5b9da48b..d4db474e 100644 --- a/tests/compile-and-dump/Singletons/Sections.ghc82.template +++ b/tests/compile-and-dump/Singletons/Sections.ghc82.template @@ -20,7 +20,7 @@ Singletons/Sections.hs:(0,0)-(0,0): Splicing declarations foo3 :: [Nat] foo3 = ((zipWith (+)) [Succ Zero, Succ Zero]) [Zero, Succ Zero] type family Lambda_0123456789876543210 t where - Lambda_0123456789876543210 lhs_0123456789876543210 = Apply (Apply (:+$) lhs_0123456789876543210) (Apply SuccSym0 ZeroSym0) + Lambda_0123456789876543210 lhs_0123456789876543210 = Apply (Apply (:+@#@$) lhs_0123456789876543210) (Apply SuccSym0 ZeroSym0) type Lambda_0123456789876543210Sym1 t = Lambda_0123456789876543210 t instance SuppressUnusedWarnings Lambda_0123456789876543210Sym0 where @@ -32,50 +32,51 @@ Singletons/Sections.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply Lambda_0123456789876543210Sym0 arg) (Lambda_0123456789876543210Sym1 arg) => Lambda_0123456789876543210Sym0KindInference type instance Apply Lambda_0123456789876543210Sym0 l = Lambda_0123456789876543210 l - type (:+$$$) (t :: Nat) (t :: Nat) = (:+) t t - instance SuppressUnusedWarnings (:+$$) where + type (:+@#@$$$) (t :: Nat) (t :: Nat) = (:+) t t + instance SuppressUnusedWarnings (:+@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$$###)) GHC.Tuple.()) - data (:+$$) (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply ((:+$$) l) arg) ((:+$$$) l arg) => - (:+$$###) - type instance Apply ((:+$$) l) l = (:+) l l - instance SuppressUnusedWarnings (:+$) where + = snd ((GHC.Tuple.(,) (:+@#@$$###)) GHC.Tuple.()) + data (:+@#@$$) (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:+@#@$$) l) arg) ((:+@#@$$$) l arg) => + (:+@#@$$###) + type instance Apply ((:+@#@$$) l) l = (:+) l l + instance SuppressUnusedWarnings (:+@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:+$###)) GHC.Tuple.()) - data (:+$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:+$) arg) ((:+$$) arg) => (:+$###) - type instance Apply (:+$) l = (:+$$) l + = snd ((GHC.Tuple.(,) (:+@#@$###)) GHC.Tuple.()) + data (:+@#@$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:+@#@$) arg) ((:+@#@$$) arg) => + (:+@#@$###) + type instance Apply (:+@#@$) l = (:+@#@$$) l type Foo1Sym0 = Foo1 type Foo2Sym0 = Foo2 type Foo3Sym0 = Foo3 type family (:+) (a :: Nat) (a :: Nat) :: Nat where (:+) Zero m = m - (:+) (Succ n) m = Apply SuccSym0 (Apply (Apply (:+$) n) m) + (:+) (Succ n) m = Apply SuccSym0 (Apply (Apply (:+@#@$) n) m) type family Foo1 :: [Nat] where - = Apply (Apply MapSym0 (Apply (:+$) (Apply SuccSym0 ZeroSym0))) (Apply (Apply (:$) ZeroSym0) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) '[])) + = Apply (Apply MapSym0 (Apply (:+@#@$) (Apply SuccSym0 ZeroSym0))) (Apply (Apply (:@#@$) ZeroSym0) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) '[])) type family Foo2 :: [Nat] where - = Apply (Apply MapSym0 Lambda_0123456789876543210Sym0) (Apply (Apply (:$) ZeroSym0) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) '[])) + = Apply (Apply MapSym0 Lambda_0123456789876543210Sym0) (Apply (Apply (:@#@$) ZeroSym0) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) '[])) type family Foo3 :: [Nat] where - = Apply (Apply (Apply ZipWithSym0 (:+$)) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) '[]))) (Apply (Apply (:$) ZeroSym0) (Apply (Apply (:$) (Apply SuccSym0 ZeroSym0)) '[])) + = Apply (Apply (Apply ZipWithSym0 (:+@#@$)) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) '[]))) (Apply (Apply (:@#@$) ZeroSym0) (Apply (Apply (:@#@$) (Apply SuccSym0 ZeroSym0)) '[])) (%:+) :: forall (t :: Nat) (t :: Nat). - Sing t -> Sing t -> Sing (Apply (Apply (:+$) t) t :: Nat) + Sing t -> Sing t -> Sing (Apply (Apply (:+@#@$) t) t :: Nat) sFoo1 :: Sing (Foo1Sym0 :: [Nat]) sFoo2 :: Sing (Foo2Sym0 :: [Nat]) sFoo3 :: Sing (Foo3Sym0 :: [Nat]) (%:+) SZero (sM :: Sing m) = sM (%:+) (SSucc (sN :: Sing n)) (sM :: Sing m) = (applySing ((singFun1 @SuccSym0) SSucc)) - ((applySing ((applySing ((singFun2 @(:+$)) (%:+))) sN)) sM) + ((applySing ((applySing ((singFun2 @(:+@#@$)) (%:+))) sN)) sM) sFoo1 = (applySing ((applySing ((singFun2 @MapSym0) sMap)) - ((applySing ((singFun2 @(:+$)) (%:+))) + ((applySing ((singFun2 @(:+@#@$)) (%:+))) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero)))) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) SNil)) sFoo2 @@ -86,27 +87,28 @@ Singletons/Sections.hs:(0,0)-(0,0): Splicing declarations -> case sLhs_0123456789876543210 of { _ :: Sing lhs_0123456789876543210 -> (applySing - ((applySing ((singFun2 @(:+$)) (%:+))) sLhs_0123456789876543210)) + ((applySing ((singFun2 @(:+@#@$)) (%:+))) + sLhs_0123456789876543210)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero) })))) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) SNil)) sFoo3 = (applySing ((applySing ((applySing ((singFun3 @ZipWithSym0) sZipWith)) - ((singFun2 @(:+$)) (%:+)))) + ((singFun2 @(:+@#@$)) (%:+)))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) SNil)))) - ((applySing ((applySing ((singFun2 @(:$)) SCons)) SZero)) + ((applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SZero)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @SuccSym0) SSucc)) SZero))) SNil)) diff --git a/tests/compile-and-dump/Singletons/ShowDeriving.ghc82.template b/tests/compile-and-dump/Singletons/ShowDeriving.ghc82.template index 2a7f404f..167aae5c 100644 --- a/tests/compile-and-dump/Singletons/ShowDeriving.ghc82.template +++ b/tests/compile-and-dump/Singletons/ShowDeriving.ghc82.template @@ -34,14 +34,14 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply GetFoo3aSym0 arg) (GetFoo3aSym1 arg) => GetFoo3aSym0KindInference type instance Apply GetFoo3aSym0 l = GetFoo3a l - type (:***$$) (t :: Foo3) = (:***) t - instance SuppressUnusedWarnings (:***$) where + type (:***@#@$$) (t :: Foo3) = (:***) t + instance SuppressUnusedWarnings (:***@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:***$###)) GHC.Tuple.()) - data (:***$) (l :: TyFun Foo3 Bool) - = forall arg. SameKind (Apply (:***$) arg) ((:***$$) arg) => - (:***$###) - type instance Apply (:***$) l = (:***) l + = snd ((GHC.Tuple.(,) (:***@#@$###)) GHC.Tuple.()) + data (:***@#@$) (l :: TyFun Foo3 Bool) + = forall arg. SameKind (Apply (:***@#@$) arg) ((:***@#@$$) arg) => + (:***@#@$###) + type instance Apply (:***@#@$) l = (:***) l type family GetFoo3a (a :: Foo3) :: Bool where GetFoo3a (MkFoo3 field _) = field type family (:***) (a :: Foo3) :: Bool where @@ -81,40 +81,40 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply MkFoo2bSym0 arg) (MkFoo2bSym1 arg) => MkFoo2bSym0KindInference type instance Apply MkFoo2bSym0 l = MkFoo2bSym1 l - type (:*:$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = + type (:*:@#@$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:*:) t t - instance SuppressUnusedWarnings (:*:$$) where + instance SuppressUnusedWarnings (:*:@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:*:$$###)) GHC.Tuple.()) - data (:*:$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 (Foo2 a0123456789876543210)) - = forall arg. SameKind (Apply ((:*:$$) l) arg) ((:*:$$$) l arg) => - (:*:$$###) - type instance Apply ((:*:$$) l) l = (:*:) l l - instance SuppressUnusedWarnings (:*:$) where + = snd ((GHC.Tuple.(,) (:*:@#@$$###)) GHC.Tuple.()) + data (:*:@#@$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 (Foo2 a0123456789876543210)) + = forall arg. SameKind (Apply ((:*:@#@$$) l) arg) ((:*:@#@$$$) l arg) => + (:*:@#@$$###) + type instance Apply ((:*:@#@$$) l) l = (:*:) l l + instance SuppressUnusedWarnings (:*:@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:*:$###)) GHC.Tuple.()) - data (:*:$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 (Foo2 a0123456789876543210) - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:*:$) arg) ((:*:$$) arg) => - (:*:$###) - type instance Apply (:*:$) l = (:*:$$) l - type (:&:$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = + = snd ((GHC.Tuple.(,) (:*:@#@$###)) GHC.Tuple.()) + data (:*:@#@$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 (Foo2 a0123456789876543210) + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:*:@#@$) arg) ((:*:@#@$$) arg) => + (:*:@#@$###) + type instance Apply (:*:@#@$) l = (:*:@#@$$) l + type (:&:@#@$$$) (t :: a0123456789876543210) (t :: a0123456789876543210) = (:&:) t t - instance SuppressUnusedWarnings (:&:$$) where + instance SuppressUnusedWarnings (:&:@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:&:$$###)) GHC.Tuple.()) - data (:&:$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 (Foo2 a0123456789876543210)) - = forall arg. SameKind (Apply ((:&:$$) l) arg) ((:&:$$$) l arg) => - (:&:$$###) - type instance Apply ((:&:$$) l) l = (:&:) l l - instance SuppressUnusedWarnings (:&:$) where + = snd ((GHC.Tuple.(,) (:&:@#@$$###)) GHC.Tuple.()) + data (:&:@#@$$) (l :: a0123456789876543210) (l :: TyFun a0123456789876543210 (Foo2 a0123456789876543210)) + = forall arg. SameKind (Apply ((:&:@#@$$) l) arg) ((:&:@#@$$$) l arg) => + (:&:@#@$$###) + type instance Apply ((:&:@#@$$) l) l = (:&:) l l + instance SuppressUnusedWarnings (:&:@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:&:$###)) GHC.Tuple.()) - data (:&:$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 (Foo2 a0123456789876543210) - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:&:$) arg) ((:&:$$) arg) => - (:&:$###) - type instance Apply (:&:$) l = (:&:$$) l + = snd ((GHC.Tuple.(,) (:&:@#@$###)) GHC.Tuple.()) + data (:&:@#@$) (l :: TyFun a0123456789876543210 (TyFun a0123456789876543210 (Foo2 a0123456789876543210) + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:&:@#@$) arg) ((:&:@#@$$) arg) => + (:&:@#@$###) + type instance Apply (:&:@#@$) l = (:&:@#@$$) l type MkFoo3Sym2 (t :: Bool) (t :: Bool) = MkFoo3 t t instance SuppressUnusedWarnings MkFoo3Sym1 where suppressUnusedWarnings @@ -168,10 +168,10 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations instance PShow Foo1 where type ShowsPrec (a :: GHC.Types.Nat) (a :: Foo1) (a :: Symbol) = Apply (Apply (Apply ShowsPrec_0123456789876543210Sym0 a) a) a type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Foo2 a) (a :: Symbol) :: Symbol where - ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo2a arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "MkFoo2a ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo2b argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 5))) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argL_0123456789876543210)) (Apply (Apply (:.$) (Apply ShowStringSym0 " `MkFoo2b` ")) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argR_0123456789876543210)))) a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 ((:*:) arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "(:*:) ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 - ShowsPrec_0123456789876543210 p_0123456789876543210 ((:&:) argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 5))) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argL_0123456789876543210)) (Apply (Apply (:.$) (Apply ShowStringSym0 " :&: ")) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argR_0123456789876543210)))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo2a arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "MkFoo2a ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo2b argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 5))) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argL_0123456789876543210)) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 " `MkFoo2b` ")) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argR_0123456789876543210)))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 ((:*:) arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "(:*:) ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowSpaceSym0) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_0123456789876543210))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 ((:&:) argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 5))) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argL_0123456789876543210)) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 " :&: ")) (Apply (Apply ShowsPrecSym0 (FromInteger 6)) argR_0123456789876543210)))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Foo2 a0123456789876543210) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -207,7 +207,7 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations instance PShow (Foo2 a) where type ShowsPrec (a :: GHC.Types.Nat) (a :: Foo2 a) (a :: Symbol) = Apply (Apply (Apply ShowsPrec_0123456789876543210Sym0 a) a) a type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: Foo3) (a :: Symbol) :: Symbol where - ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo3 arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.$) (Apply ShowStringSym0 "MkFoo3 ")) (Apply (Apply (:.$) (Apply ShowCharSym0 "{")) (Apply (Apply (:.$) (Apply ShowStringSym0 "getFoo3a = ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 0)) arg_0123456789876543210)) (Apply (Apply (:.$) ShowCommaSpaceSym0) (Apply (Apply (:.$) (Apply ShowStringSym0 "(***) = ")) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 0)) arg_0123456789876543210)) (Apply ShowCharSym0 "}"))))))))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 (MkFoo3 arg_0123456789876543210 arg_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 10))) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "MkFoo3 ")) (Apply (Apply (:.@#@$) (Apply ShowCharSym0 "{")) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "getFoo3a = ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 0)) arg_0123456789876543210)) (Apply (Apply (:.@#@$) ShowCommaSpaceSym0) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 "(***) = ")) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 0)) arg_0123456789876543210)) (Apply ShowCharSym0 "}"))))))))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: Foo3) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -349,20 +349,20 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "MkFoo2a ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowSpaceSym0) sShowSpace))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) @@ -378,16 +378,16 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 5))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 6)))) sArgL_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing " `MkFoo2b` ")))) ((applySing @@ -404,20 +404,20 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "(:*:) ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 11)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowSpaceSym0) sShowSpace))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) @@ -433,16 +433,16 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 5))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 6)))) sArgL_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing " :&: ")))) ((applySing @@ -472,35 +472,35 @@ Singletons/ShowDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 10))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "MkFoo3 ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowCharSym0) sShowChar)) (sing :: Sing "{")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "getFoo3a = ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 0)))) sArg_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((singFun1 @ShowCommaSpaceSym0) sShowCommaSpace))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing "(***) = ")))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 0)))) diff --git a/tests/compile-and-dump/Singletons/StandaloneDeriving.ghc82.template b/tests/compile-and-dump/Singletons/StandaloneDeriving.ghc82.template index ea6a0efc..56fc4be3 100644 --- a/tests/compile-and-dump/Singletons/StandaloneDeriving.ghc82.template +++ b/tests/compile-and-dump/Singletons/StandaloneDeriving.ghc82.template @@ -25,27 +25,27 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations deriving instance Show S deriving instance Bounded S deriving instance Enum S - type (:*:$$$) (t :: a0123456789876543210) (t :: b0123456789876543210) = + type (:*:@#@$$$) (t :: a0123456789876543210) (t :: b0123456789876543210) = (:*:) t t - instance SuppressUnusedWarnings (:*:$$) where + instance SuppressUnusedWarnings (:*:@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:*:$$###)) GHC.Tuple.()) - data (:*:$$) (l :: a0123456789876543210) (l :: TyFun b0123456789876543210 (T a0123456789876543210 b0123456789876543210)) - = forall arg. SameKind (Apply ((:*:$$) l) arg) ((:*:$$$) l arg) => - (:*:$$###) - type instance Apply ((:*:$$) l) l = (:*:) l l - instance SuppressUnusedWarnings (:*:$) where + = snd ((GHC.Tuple.(,) (:*:@#@$$###)) GHC.Tuple.()) + data (:*:@#@$$) (l :: a0123456789876543210) (l :: TyFun b0123456789876543210 (T a0123456789876543210 b0123456789876543210)) + = forall arg. SameKind (Apply ((:*:@#@$$) l) arg) ((:*:@#@$$$) l arg) => + (:*:@#@$$###) + type instance Apply ((:*:@#@$$) l) l = (:*:) l l + instance SuppressUnusedWarnings (:*:@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:*:$###)) GHC.Tuple.()) - data (:*:$) (l :: TyFun a0123456789876543210 (TyFun b0123456789876543210 (T a0123456789876543210 b0123456789876543210) - -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:*:$) arg) ((:*:$$) arg) => - (:*:$###) - type instance Apply (:*:$) l = (:*:$$) l + = snd ((GHC.Tuple.(,) (:*:@#@$###)) GHC.Tuple.()) + data (:*:@#@$) (l :: TyFun a0123456789876543210 (TyFun b0123456789876543210 (T a0123456789876543210 b0123456789876543210) + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:*:@#@$) arg) ((:*:@#@$$) arg) => + (:*:@#@$###) + type instance Apply (:*:@#@$) l = (:*:@#@$$) l type S1Sym0 = S1 type S2Sym0 = S2 type family Compare_0123456789876543210 (a :: T a ()) (a :: T a ()) :: Ordering where - Compare_0123456789876543210 ((:*:) a_0123456789876543210 a_0123456789876543210) ((:*:) b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])) + Compare_0123456789876543210 ((:*:) a_0123456789876543210 a_0123456789876543210) ((:*:) b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])) type Compare_0123456789876543210Sym2 (t :: T a0123456789876543210 ()) (t :: T a0123456789876543210 ()) = Compare_0123456789876543210 t t instance SuppressUnusedWarnings Compare_0123456789876543210Sym1 where @@ -70,7 +70,7 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations instance POrd (T a ()) where type Compare (a :: T a ()) (a :: T a ()) = Apply (Apply Compare_0123456789876543210Sym0 a) a type family ShowsPrec_0123456789876543210 (a :: GHC.Types.Nat) (a :: T a ()) (a :: Symbol) :: Symbol where - ShowsPrec_0123456789876543210 p_0123456789876543210 ((:*:) argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>$) p_0123456789876543210) (FromInteger 6))) (Apply (Apply (:.$) (Apply (Apply ShowsPrecSym0 (FromInteger 7)) argL_0123456789876543210)) (Apply (Apply (:.$) (Apply ShowStringSym0 " :*: ")) (Apply (Apply ShowsPrecSym0 (FromInteger 7)) argR_0123456789876543210)))) a_0123456789876543210 + ShowsPrec_0123456789876543210 p_0123456789876543210 ((:*:) argL_0123456789876543210 argR_0123456789876543210) a_0123456789876543210 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (:>@#@$) p_0123456789876543210) (FromInteger 6))) (Apply (Apply (:.@#@$) (Apply (Apply ShowsPrecSym0 (FromInteger 7)) argL_0123456789876543210)) (Apply (Apply (:.@#@$) (Apply ShowStringSym0 " :*: ")) (Apply (Apply ShowsPrecSym0 (FromInteger 7)) argR_0123456789876543210)))) a_0123456789876543210 type ShowsPrec_0123456789876543210Sym3 (t :: GHC.Types.Nat) (t :: T a0123456789876543210 ()) (t :: Symbol) = ShowsPrec_0123456789876543210 t t t instance SuppressUnusedWarnings ShowsPrec_0123456789876543210Sym2 where @@ -186,9 +186,9 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations Case_0123456789876543210 n False = Apply ErrorSym0 "toEnum: bad argument" type family Case_0123456789876543210 n t where Case_0123456789876543210 n True = S1Sym0 - Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) + Case_0123456789876543210 n False = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) type family ToEnum_0123456789876543210 (a :: GHC.Types.Nat) :: S where - ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) + ToEnum_0123456789876543210 n = Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) type ToEnum_0123456789876543210Sym1 (t :: GHC.Types.Nat) = ToEnum_0123456789876543210 t instance SuppressUnusedWarnings ToEnum_0123456789876543210Sym0 where @@ -270,13 +270,13 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -304,16 +304,16 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations ((applySing ((applySing ((singFun3 @ShowParenSym0) sShowParen)) ((applySing - ((applySing ((singFun2 @(:>$)) (%:>))) sP_0123456789876543210)) + ((applySing ((singFun2 @(:>@#@$)) (%:>))) sP_0123456789876543210)) (sFromInteger (sing :: Sing 6))))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((applySing ((singFun3 @ShowsPrecSym0) sShowsPrec)) (sFromInteger (sing :: Sing 7)))) sArgL_0123456789876543210))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) ((applySing ((singFun2 @ShowStringSym0) sShowString)) (sing :: Sing " :*: ")))) ((applySing @@ -393,19 +393,19 @@ Singletons/StandaloneDeriving.hs:(0,0)-(0,0): Splicing declarations -> GHC.Types.Type) t :: GHC.Types.Nat) sToEnum (sN :: Sing n) = case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 0)) of STrue -> SS1 SFalse -> case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sN)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sN)) (sFromInteger (sing :: Sing 1)) of STrue -> SS2 SFalse -> sError (sing :: Sing "toEnum: bad argument") :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 1)) :: S) :: - Sing (Case_0123456789876543210 n (Apply (Apply (:==$) n) (FromInteger 0)) :: S) + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 1)) :: S) :: + Sing (Case_0123456789876543210 n (Apply (Apply (:==@#@$) n) (FromInteger 0)) :: S) sFromEnum SS1 = sFromInteger (sing :: Sing 0) sFromEnum SS2 = sFromInteger (sing :: Sing 1) instance SEq a => SEq (T a ()) where diff --git a/tests/compile-and-dump/Singletons/Star.ghc82.template b/tests/compile-and-dump/Singletons/Star.ghc82.template index d88c95c5..3149b7b6 100644 --- a/tests/compile-and-dump/Singletons/Star.ghc82.template +++ b/tests/compile-and-dump/Singletons/Star.ghc82.template @@ -47,8 +47,8 @@ Singletons/Star.hs:0:0:: Splicing declarations Compare_0123456789876543210 Nat Nat = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] Compare_0123456789876543210 Int Int = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] Compare_0123456789876543210 String String = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) '[] - Compare_0123456789876543210 (Maybe a_0123456789876543210) (Maybe b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) - Compare_0123456789876543210 (Vec a_0123456789876543210 a_0123456789876543210) (Vec b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])) + Compare_0123456789876543210 (Maybe a_0123456789876543210) (Maybe b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[]) + Compare_0123456789876543210 (Vec a_0123456789876543210 a_0123456789876543210) (Vec b_0123456789876543210 b_0123456789876543210) = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) (Apply (Apply (:@#@$) (Apply (Apply CompareSym0 a_0123456789876543210) b_0123456789876543210)) '[])) Compare_0123456789876543210 Nat Int = LTSym0 Compare_0123456789876543210 Nat String = LTSym0 Compare_0123456789876543210 Nat (Maybe _) = LTSym0 @@ -131,7 +131,7 @@ Singletons/Star.hs:0:0:: Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) @@ -148,13 +148,13 @@ Singletons/Star.hs:0:0:: Splicing declarations ((singFun2 @ThenCmpSym0) sThenCmp))) SEQ)) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) sB_0123456789876543210))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((applySing ((singFun2 @CompareSym0) sCompare)) sA_0123456789876543210)) diff --git a/tests/compile-and-dump/Singletons/T136.ghc82.template b/tests/compile-and-dump/Singletons/T136.ghc82.template index 24e34200..27fe5d40 100644 --- a/tests/compile-and-dump/Singletons/T136.ghc82.template +++ b/tests/compile-and-dump/Singletons/T136.ghc82.template @@ -30,9 +30,9 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations fromEnum (False GHC.Types.: as) = (2 * (fromEnum as)) fromEnum (True GHC.Types.: as) = (1 + (2 * (fromEnum as))) type family Succ_0123456789876543210 (a :: [Bool]) :: [Bool] where - Succ_0123456789876543210 '[] = Apply (Apply (:$) TrueSym0) '[] - Succ_0123456789876543210 ((:) False as) = Apply (Apply (:$) TrueSym0) as - Succ_0123456789876543210 ((:) True as) = Apply (Apply (:$) FalseSym0) (Apply SuccSym0 as) + Succ_0123456789876543210 '[] = Apply (Apply (:@#@$) TrueSym0) '[] + Succ_0123456789876543210 ((:) False as) = Apply (Apply (:@#@$) TrueSym0) as + Succ_0123456789876543210 ((:) True as) = Apply (Apply (:@#@$) FalseSym0) (Apply SuccSym0 as) type Succ_0123456789876543210Sym1 (t :: [Bool]) = Succ_0123456789876543210 t instance SuppressUnusedWarnings Succ_0123456789876543210Sym0 where @@ -46,8 +46,8 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations type instance Apply Succ_0123456789876543210Sym0 l = Succ_0123456789876543210 l type family Pred_0123456789876543210 (a :: [Bool]) :: [Bool] where Pred_0123456789876543210 '[] = Apply ErrorSym0 "pred 0" - Pred_0123456789876543210 ((:) False as) = Apply (Apply (:$) TrueSym0) (Apply PredSym0 as) - Pred_0123456789876543210 ((:) True as) = Apply (Apply (:$) FalseSym0) as + Pred_0123456789876543210 ((:) False as) = Apply (Apply (:@#@$) TrueSym0) (Apply PredSym0 as) + Pred_0123456789876543210 ((:) True as) = Apply (Apply (:@#@$) FalseSym0) as type Pred_0123456789876543210Sym1 (t :: [Bool]) = Pred_0123456789876543210 t instance SuppressUnusedWarnings Pred_0123456789876543210Sym0 where @@ -64,9 +64,9 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations Case_0123456789876543210 i arg_0123456789876543210 False = Apply SuccSym0 (Apply ToEnumSym0 (Apply PredSym0 i)) type family Case_0123456789876543210 i arg_0123456789876543210 t where Case_0123456789876543210 i arg_0123456789876543210 True = Apply ErrorSym0 "negative toEnum" - Case_0123456789876543210 i arg_0123456789876543210 False = Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:==$) i) (FromInteger 0)) + Case_0123456789876543210 i arg_0123456789876543210 False = Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:==@#@$) i) (FromInteger 0)) type family Case_0123456789876543210 arg_0123456789876543210 t where - Case_0123456789876543210 arg_0123456789876543210 i = Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:<$) i) (FromInteger 0)) + Case_0123456789876543210 arg_0123456789876543210 i = Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:<@#@$) i) (FromInteger 0)) type family ToEnum_0123456789876543210 (a :: GHC.Types.Nat) :: [Bool] where ToEnum_0123456789876543210 arg_0123456789876543210 = Case_0123456789876543210 arg_0123456789876543210 arg_0123456789876543210 type ToEnum_0123456789876543210Sym1 (t :: GHC.Types.Nat) = @@ -82,8 +82,8 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations type instance Apply ToEnum_0123456789876543210Sym0 l = ToEnum_0123456789876543210 l type family FromEnum_0123456789876543210 (a :: [Bool]) :: GHC.Types.Nat where FromEnum_0123456789876543210 '[] = FromInteger 0 - FromEnum_0123456789876543210 ((:) False as) = Apply (Apply (:*$) (FromInteger 2)) (Apply FromEnumSym0 as) - FromEnum_0123456789876543210 ((:) True as) = Apply (Apply (:+$) (FromInteger 1)) (Apply (Apply (:*$) (FromInteger 2)) (Apply FromEnumSym0 as)) + FromEnum_0123456789876543210 ((:) False as) = Apply (Apply (:*@#@$) (FromInteger 2)) (Apply FromEnumSym0 as) + FromEnum_0123456789876543210 ((:) True as) = Apply (Apply (:+@#@$) (FromInteger 1)) (Apply (Apply (:*@#@$) (FromInteger 2)) (Apply FromEnumSym0 as)) type FromEnum_0123456789876543210Sym1 (t :: [Bool]) = FromEnum_0123456789876543210 t instance SuppressUnusedWarnings FromEnum_0123456789876543210Sym0 where @@ -122,29 +122,29 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations -> Sing (Apply (FromEnumSym0 :: TyFun [Bool] GHC.Types.Nat -> GHC.Types.Type) t :: GHC.Types.Nat) sSucc SNil - = (applySing ((applySing ((singFun2 @(:$)) SCons)) STrue)) SNil + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) STrue)) SNil sSucc (SCons SFalse (sAs :: Sing as)) - = (applySing ((applySing ((singFun2 @(:$)) SCons)) STrue)) sAs + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) STrue)) sAs sSucc (SCons STrue (sAs :: Sing as)) - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SFalse)) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SFalse)) ((applySing ((singFun1 @SuccSym0) sSucc)) sAs) sPred SNil = sError (sing :: Sing "pred 0") sPred (SCons SFalse (sAs :: Sing as)) - = (applySing ((applySing ((singFun2 @(:$)) SCons)) STrue)) + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) STrue)) ((applySing ((singFun1 @PredSym0) sPred)) sAs) sPred (SCons STrue (sAs :: Sing as)) - = (applySing ((applySing ((singFun2 @(:$)) SCons)) SFalse)) sAs + = (applySing ((applySing ((singFun2 @(:@#@$)) SCons)) SFalse)) sAs sToEnum (sArg_0123456789876543210 :: Sing arg_0123456789876543210) = case sArg_0123456789876543210 of { sI :: Sing i -> case - (applySing ((applySing ((singFun2 @(:<$)) (%:<))) sI)) + (applySing ((applySing ((singFun2 @(:<@#@$)) (%:<))) sI)) (sFromInteger (sing :: Sing 0)) of STrue -> sError (sing :: Sing "negative toEnum") SFalse -> case - (applySing ((applySing ((singFun2 @(:==$)) (%:==))) sI)) + (applySing ((applySing ((singFun2 @(:==@#@$)) (%:==))) sI)) (sFromInteger (sing :: Sing 0)) of STrue -> SNil @@ -152,20 +152,20 @@ Singletons/T136.hs:(0,0)-(0,0): Splicing declarations -> (applySing ((singFun1 @SuccSym0) sSucc)) ((applySing ((singFun1 @ToEnumSym0) sToEnum)) ((applySing ((singFun1 @PredSym0) sPred)) sI)) :: - Sing (Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:==$) i) (FromInteger 0)) :: [Bool]) :: - Sing (Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:<$) i) (FromInteger 0)) :: [Bool]) } :: + Sing (Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:==@#@$) i) (FromInteger 0)) :: [Bool]) :: + Sing (Case_0123456789876543210 i arg_0123456789876543210 (Apply (Apply (:<@#@$) i) (FromInteger 0)) :: [Bool]) } :: Sing (Case_0123456789876543210 arg_0123456789876543210 arg_0123456789876543210 :: [Bool]) sFromEnum SNil = sFromInteger (sing :: Sing 0) sFromEnum (SCons SFalse (sAs :: Sing as)) = (applySing - ((applySing ((singFun2 @(:*$)) (%:*))) + ((applySing ((singFun2 @(:*@#@$)) (%:*))) (sFromInteger (sing :: Sing 2)))) ((applySing ((singFun1 @FromEnumSym0) sFromEnum)) sAs) sFromEnum (SCons STrue (sAs :: Sing as)) = (applySing - ((applySing ((singFun2 @(:+$)) (%:+))) + ((applySing ((singFun2 @(:+@#@$)) (%:+))) (sFromInteger (sing :: Sing 1)))) ((applySing - ((applySing ((singFun2 @(:*$)) (%:*))) + ((applySing ((singFun2 @(:*@#@$)) (%:*))) (sFromInteger (sing :: Sing 2)))) ((applySing ((singFun1 @FromEnumSym0) sFromEnum)) sAs)) diff --git a/tests/compile-and-dump/Singletons/T159.ghc82.template b/tests/compile-and-dump/Singletons/T159.ghc82.template index ef2aeb12..072734b1 100644 --- a/tests/compile-and-dump/Singletons/T159.ghc82.template +++ b/tests/compile-and-dump/Singletons/T159.ghc82.template @@ -57,21 +57,21 @@ Singletons/T159.hs:0:0:: Splicing declarations = forall arg. SameKind (Apply C1Sym0 arg) (C1Sym1 arg) => C1Sym0KindInference type instance Apply C1Sym0 l = C1Sym1 l - type (:&&$$$) (t :: T0) (t :: T1) = (:&&) t t - instance SuppressUnusedWarnings (:&&$$) where + type (:&&@#@$$$) (t :: T0) (t :: T1) = (:&&) t t + instance SuppressUnusedWarnings (:&&@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:&&$$###)) GHC.Tuple.()) - data (:&&$$) (l :: T0) (l :: TyFun T1 T1) - = forall arg. SameKind (Apply ((:&&$$) l) arg) ((:&&$$$) l arg) => - (:&&$$###) - type instance Apply ((:&&$$) l) l = (:&&) l l - instance SuppressUnusedWarnings (:&&$) where + = snd ((GHC.Tuple.(,) (:&&@#@$$###)) GHC.Tuple.()) + data (:&&@#@$$) (l :: T0) (l :: TyFun T1 T1) + = forall arg. SameKind (Apply ((:&&@#@$$) l) arg) ((:&&@#@$$$) l arg) => + (:&&@#@$$###) + type instance Apply ((:&&@#@$$) l) l = (:&&) l l + instance SuppressUnusedWarnings (:&&@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:&&$###)) GHC.Tuple.()) - data (:&&$) (l :: TyFun T0 (TyFun T1 T1 -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:&&$) arg) ((:&&$$) arg) => - (:&&$###) - type instance Apply (:&&$) l = (:&&$$) l + = snd ((GHC.Tuple.(,) (:&&@#@$###)) GHC.Tuple.()) + data (:&&@#@$) (l :: TyFun T0 (TyFun T1 T1 -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:&&@#@$) arg) ((:&&@#@$$) arg) => + (:&&@#@$###) + type instance Apply (:&&@#@$) l = (:&&@#@$$) l data instance Sing (z :: T1) = z ~ N1 => SN1 | forall (n :: T0) (n :: T1). z ~ C1 n n => @@ -131,21 +131,21 @@ Singletons/T159.hs:(0,0)-(0,0): Splicing declarations = forall arg. SameKind (Apply C2Sym0 arg) (C2Sym1 arg) => C2Sym0KindInference type instance Apply C2Sym0 l = C2Sym1 l - type (:||$$$) (t :: T0) (t :: T2) = (:||) t t - instance SuppressUnusedWarnings (:||$$) where + type (:||@#@$$$) (t :: T0) (t :: T2) = (:||) t t + instance SuppressUnusedWarnings (:||@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:||$$###)) GHC.Tuple.()) - data (:||$$) (l :: T0) (l :: TyFun T2 T2) - = forall arg. SameKind (Apply ((:||$$) l) arg) ((:||$$$) l arg) => - (:||$$###) - type instance Apply ((:||$$) l) l = (:||) l l - instance SuppressUnusedWarnings (:||$) where + = snd ((GHC.Tuple.(,) (:||@#@$$###)) GHC.Tuple.()) + data (:||@#@$$) (l :: T0) (l :: TyFun T2 T2) + = forall arg. SameKind (Apply ((:||@#@$$) l) arg) ((:||@#@$$$) l arg) => + (:||@#@$$###) + type instance Apply ((:||@#@$$) l) l = (:||) l l + instance SuppressUnusedWarnings (:||@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:||$###)) GHC.Tuple.()) - data (:||$) (l :: TyFun T0 (TyFun T2 T2 -> GHC.Types.Type)) - = forall arg. SameKind (Apply (:||$) arg) ((:||$$) arg) => - (:||$###) - type instance Apply (:||$) l = (:||$$) l + = snd ((GHC.Tuple.(,) (:||@#@$###)) GHC.Tuple.()) + data (:||@#@$) (l :: TyFun T0 (TyFun T2 T2 -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:||@#@$) arg) ((:||@#@$$) arg) => + (:||@#@$###) + type instance Apply (:||@#@$) l = (:||@#@$$) l infixr 5 :%|| infixr 5 `SC2` data instance Sing (z :: T2) diff --git a/tests/compile-and-dump/Singletons/T172.ghc82.template b/tests/compile-and-dump/Singletons/T172.ghc82.template index 76731039..b9442399 100644 --- a/tests/compile-and-dump/Singletons/T172.ghc82.template +++ b/tests/compile-and-dump/Singletons/T172.ghc82.template @@ -3,28 +3,29 @@ Singletons/T172.hs:(0,0)-(0,0): Splicing declarations [d| ($>) :: Nat -> Nat -> Nat ($>) = (+) |] ======> - type ($>$$$) (t :: Nat) (t :: Nat) = ($>) t t - instance SuppressUnusedWarnings ($>$$) where + type (:$>@#@$$$) (t :: Nat) (t :: Nat) = (:$>) t t + instance SuppressUnusedWarnings (:$>@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:$>$$###)) GHC.Tuple.()) - data ($>$$) (l :: Nat) (l :: TyFun Nat Nat) - = forall arg. SameKind (Apply (($>$$) l) arg) (($>$$$) l arg) => - (:$>$$###) - type instance Apply (($>$$) l) l = ($>) l l - instance SuppressUnusedWarnings ($>$) where + = snd ((GHC.Tuple.(,) (:$>@#@$$###)) GHC.Tuple.()) + data (:$>@#@$$) (l :: Nat) (l :: TyFun Nat Nat) + = forall arg. SameKind (Apply ((:$>@#@$$) l) arg) ((:$>@#@$$$) l arg) => + (:$>@#@$$###) + type instance Apply ((:$>@#@$$) l) l = (:$>) l l + instance SuppressUnusedWarnings (:$>@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:$>$###)) GHC.Tuple.()) - data ($>$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) - = forall arg. SameKind (Apply ($>$) arg) (($>$$) arg) => (:$>$###) - type instance Apply ($>$) l = ($>$$) l - type family ($>) (a :: Nat) (a :: Nat) :: Nat where - ($>) a_0123456789876543210 a_0123456789876543210 = Apply (Apply (:+$) a_0123456789876543210) a_0123456789876543210 - (%$>) :: + = snd ((GHC.Tuple.(,) (:$>@#@$###)) GHC.Tuple.()) + data (:$>@#@$) (l :: TyFun Nat (TyFun Nat Nat -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:$>@#@$) arg) ((:$>@#@$$) arg) => + (:$>@#@$###) + type instance Apply (:$>@#@$) l = (:$>@#@$$) l + type family (:$>) (a :: Nat) (a :: Nat) :: Nat where + (:$>) a_0123456789876543210 a_0123456789876543210 = Apply (Apply (:+@#@$) a_0123456789876543210) a_0123456789876543210 + (%:$>) :: forall (t :: Nat) (t :: Nat). - Sing t -> Sing t -> Sing (Apply (Apply ($>$) t) t :: Nat) - (%$>) + Sing t -> Sing t -> Sing (Apply (Apply (:$>@#@$) t) t :: Nat) + (%:$>) (sA_0123456789876543210 :: Sing a_0123456789876543210) (sA_0123456789876543210 :: Sing a_0123456789876543210) = (applySing - ((applySing ((singFun2 @(:+$)) (%:+))) sA_0123456789876543210)) + ((applySing ((singFun2 @(:+@#@$)) (%:+))) sA_0123456789876543210)) sA_0123456789876543210 diff --git a/tests/compile-and-dump/Singletons/T197.ghc82.template b/tests/compile-and-dump/Singletons/T197.ghc82.template index 5a2096e1..c7bec605 100644 --- a/tests/compile-and-dump/Singletons/T197.ghc82.template +++ b/tests/compile-and-dump/Singletons/T197.ghc82.template @@ -8,25 +8,27 @@ Singletons/T197.hs:(0,0)-(0,0): Splicing declarations infixl 5 $$: ($$:) :: Bool -> Bool -> Bool ($$:) _ _ = False - type ($$:$$$) (t :: Bool) (t :: Bool) = ($$:) t t - instance SuppressUnusedWarnings ($$:$$) where + type (:$$:@#@$$$) (t :: Bool) (t :: Bool) = (:$$:) t t + instance SuppressUnusedWarnings (:$$:@#@$$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:$$:$$###)) GHC.Tuple.()) - data ($$:$$) (l :: Bool) (l :: TyFun Bool Bool) - = forall arg. SameKind (Apply (($$:$$) l) arg) (($$:$$$) l arg) => - (:$$:$$###) - type instance Apply (($$:$$) l) l = ($$:) l l - instance SuppressUnusedWarnings ($$:$) where + = snd ((GHC.Tuple.(,) (:$$:@#@$$###)) GHC.Tuple.()) + data (:$$:@#@$$) (l :: Bool) (l :: TyFun Bool Bool) + = forall arg. SameKind (Apply ((:$$:@#@$$) l) arg) ((:$$:@#@$$$) l arg) => + (:$$:@#@$$###) + type instance Apply ((:$$:@#@$$) l) l = (:$$:) l l + instance SuppressUnusedWarnings (:$$:@#@$) where suppressUnusedWarnings - = snd ((GHC.Tuple.(,) (:$$:$###)) GHC.Tuple.()) - data ($$:$) (l :: TyFun Bool (TyFun Bool Bool -> GHC.Types.Type)) - = forall arg. SameKind (Apply ($$:$) arg) (($$:$$) arg) => - (:$$:$###) - type instance Apply ($$:$) l = ($$:$$) l - type family ($$:) (a :: Bool) (a :: Bool) :: Bool where - ($$:) _ _ = FalseSym0 - infixl 5 %$$: - (%$$:) :: + = snd ((GHC.Tuple.(,) (:$$:@#@$###)) GHC.Tuple.()) + data (:$$:@#@$) (l :: TyFun Bool (TyFun Bool Bool + -> GHC.Types.Type)) + = forall arg. SameKind (Apply (:$$:@#@$) arg) ((:$$:@#@$$) arg) => + (:$$:@#@$###) + type instance Apply (:$$:@#@$) l = (:$$:@#@$$) l + type family (:$$:) (a :: Bool) (a :: Bool) :: Bool where + (:$$:) _ _ = FalseSym0 + infixl 5 :$$: + infixl 5 %:$$: + (%:$$:) :: forall (t :: Bool) (t :: Bool). - Sing t -> Sing t -> Sing (Apply (Apply ($$:$) t) t :: Bool) - (%$$:) _ _ = SFalse + Sing t -> Sing t -> Sing (Apply (Apply (:$$:@#@$) t) t :: Bool) + (%:$$:) _ _ = SFalse diff --git a/tests/compile-and-dump/Singletons/T29.ghc82.template b/tests/compile-and-dump/Singletons/T29.ghc82.template index e910ae0b..32ef8a48 100644 --- a/tests/compile-and-dump/Singletons/T29.ghc82.template +++ b/tests/compile-and-dump/Singletons/T29.ghc82.template @@ -50,13 +50,13 @@ Singletons/T29.hs:(0,0)-(0,0): Splicing declarations FooSym0KindInference type instance Apply FooSym0 l = Foo l type family Ban (a :: Bool) :: Bool where - Ban x = Apply (Apply ($!$) (Apply (Apply (:.$) NotSym0) (Apply (Apply (:.$) NotSym0) NotSym0))) x + Ban x = Apply (Apply (:$!@#@$) (Apply (Apply (:.@#@$) NotSym0) (Apply (Apply (:.@#@$) NotSym0) NotSym0))) x type family Baz (a :: Bool) :: Bool where - Baz x = Apply (Apply ($!$) NotSym0) x + Baz x = Apply (Apply (:$!@#@$) NotSym0) x type family Bar (a :: Bool) :: Bool where - Bar x = Apply (Apply ($$) (Apply (Apply (:.$) NotSym0) (Apply (Apply (:.$) NotSym0) NotSym0))) x + Bar x = Apply (Apply (:$@#@$) (Apply (Apply (:.@#@$) NotSym0) (Apply (Apply (:.@#@$) NotSym0) NotSym0))) x type family Foo (a :: Bool) :: Bool where - Foo x = Apply (Apply ($$) NotSym0) x + Foo x = Apply (Apply (:$@#@$) NotSym0) x sBan :: forall (t :: Bool). Sing t -> Sing (Apply BanSym0 t :: Bool) sBaz :: @@ -67,27 +67,33 @@ Singletons/T29.hs:(0,0)-(0,0): Splicing declarations forall (t :: Bool). Sing t -> Sing (Apply FooSym0 t :: Bool) sBan (sX :: Sing x) = (applySing - ((applySing ((singFun2 @($!$)) (%$!))) + ((applySing ((singFun2 @(:$!@#@$)) (%:$!))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) + ((singFun1 @NotSym0) sNot))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) + ((singFun1 @NotSym0) sNot))) ((singFun1 @NotSym0) sNot))))) sX sBaz (sX :: Sing x) = (applySing - ((applySing ((singFun2 @($!$)) (%$!))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun2 @(:$!@#@$)) (%:$!))) + ((singFun1 @NotSym0) sNot))) sX sBar (sX :: Sing x) = (applySing - ((applySing ((singFun2 @($$)) (%$))) + ((applySing ((singFun2 @(:$@#@$)) (%:$))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) + ((singFun1 @NotSym0) sNot))) ((applySing - ((applySing ((singFun3 @(:.$)) (%:.))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun3 @(:.@#@$)) (%:.))) + ((singFun1 @NotSym0) sNot))) ((singFun1 @NotSym0) sNot))))) sX sFoo (sX :: Sing x) = (applySing - ((applySing ((singFun2 @($$)) (%$))) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun2 @(:$@#@$)) (%:$))) + ((singFun1 @NotSym0) sNot))) sX diff --git a/tests/compile-and-dump/Singletons/T54.ghc82.template b/tests/compile-and-dump/Singletons/T54.ghc82.template index 31db8383..deed4600 100644 --- a/tests/compile-and-dump/Singletons/T54.ghc82.template +++ b/tests/compile-and-dump/Singletons/T54.ghc82.template @@ -18,7 +18,7 @@ Singletons/T54.hs:(0,0)-(0,0): Splicing declarations Let0123456789876543210Scrutinee_0123456789876543210Sym0KindInference type instance Apply Let0123456789876543210Scrutinee_0123456789876543210Sym0 l = Let0123456789876543210Scrutinee_0123456789876543210 l type family Let0123456789876543210Scrutinee_0123456789876543210 e where - Let0123456789876543210Scrutinee_0123456789876543210 e = Apply (Apply (:$) NotSym0) '[] + Let0123456789876543210Scrutinee_0123456789876543210 e = Apply (Apply (:@#@$) NotSym0) '[] type family Case_0123456789876543210 e t where Case_0123456789876543210 e '[_] = NotSym0 type GSym1 (t :: Bool) = G t @@ -39,7 +39,8 @@ Singletons/T54.hs:(0,0)-(0,0): Splicing declarations Sing (Let0123456789876543210Scrutinee_0123456789876543210Sym1 e) sScrutinee_0123456789876543210 = (applySing - ((applySing ((singFun2 @(:$)) SCons)) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun2 @(:@#@$)) SCons)) + ((singFun1 @NotSym0) sNot))) SNil in case sScrutinee_0123456789876543210 of { SCons _ SNil -> (singFun1 @NotSym0) sNot } :: diff --git a/tests/compile-and-dump/Singletons/TopLevelPatterns.ghc82.template b/tests/compile-and-dump/Singletons/TopLevelPatterns.ghc82.template index a3db0ec9..c213e75f 100644 --- a/tests/compile-and-dump/Singletons/TopLevelPatterns.ghc82.template +++ b/tests/compile-and-dump/Singletons/TopLevelPatterns.ghc82.template @@ -199,13 +199,13 @@ Singletons/TopLevelPatterns.hs:(0,0)-(0,0): Splicing declarations type family Otherwise :: Bool where = TrueSym0 type family X_0123456789876543210 where - = Apply (Apply (:$) NotSym0) (Apply (Apply (:$) IdSym0) '[]) + = Apply (Apply (:@#@$) NotSym0) (Apply (Apply (:@#@$) IdSym0) '[]) type family X_0123456789876543210 where = Apply (Apply Tuple2Sym0 FSym0) GSym0 type family X_0123456789876543210 where = Apply (Apply BarSym0 TrueSym0) (Apply HSym0 FalseSym0) type family X_0123456789876543210 where - = Apply (Apply (:$) (Apply NotSym0 TrueSym0)) (Apply (Apply (:$) (Apply IdSym0 FalseSym0)) '[]) + = Apply (Apply (:@#@$) (Apply NotSym0 TrueSym0)) (Apply (Apply (:@#@$) (Apply IdSym0 FalseSym0)) '[]) sFalse_ :: Sing False_Sym0 sNot :: forall (t :: Bool). Sing t -> Sing (Apply NotSym0 t :: Bool) @@ -282,9 +282,10 @@ Singletons/TopLevelPatterns.hs:(0,0)-(0,0): Splicing declarations sOtherwise = STrue sX_0123456789876543210 = (applySing - ((applySing ((singFun2 @(:$)) SCons)) ((singFun1 @NotSym0) sNot))) + ((applySing ((singFun2 @(:@#@$)) SCons)) + ((singFun1 @NotSym0) sNot))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) ((singFun1 @IdSym0) sId))) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((singFun1 @IdSym0) sId))) SNil) sX_0123456789876543210 = (applySing @@ -296,9 +297,9 @@ Singletons/TopLevelPatterns.hs:(0,0)-(0,0): Splicing declarations ((applySing ((singFun1 @HSym0) sH)) SFalse) sX_0123456789876543210 = (applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @NotSym0) sNot)) STrue))) ((applySing - ((applySing ((singFun2 @(:$)) SCons)) + ((applySing ((singFun2 @(:@#@$)) SCons)) ((applySing ((singFun1 @IdSym0) sId)) SFalse))) SNil)