Changelog for th-desugar-1.17
th-desugar
release notes
Version 1.17 [2024.05.12]
- Support GHC 9.10.
- Add support namespace identifiers in fixity declarations. As part of these
changes, the
DInfixD
data constructor now has aNamespaceSpecifier
field. - Add support for
SCC
declarations via the newDSCCP
data constructor for theDPragma
data type. - Add partial support for embedded types in expressions (via the new
DTypeE
data constructor) and in patterns (via the newDTypeP
data constructor). This is only partial support because the use ofDTypeP
is supported in the clauses of function declarations, but not in lambda expressions,\case
expressions, or\cases
expressions. See the "Known limitations" section of theth-desugar
README
for full details. - Add partial support for invisible type patterns via the new
DInvisP
data constructor. Just like withDTypeP
,th-desugar
only supports the use ofDInvisP
in the clauses of function declarations. See the "Known limitations" section of theth-desugar
README
for full details. extractBoundNamesDPat
no longer extracts type variables from constructor patterns. That this function ever did extract type variables was a mistake, and the new behavior ofextractBoundNamesDPat
brings it in line with the behaviorextractBoundNamesPat
.- The
unboxedTupleNameDegree_maybe
function now returns:Just 0
when the argument is''Unit#
Just 1
when the argument is''Solo#
Just <N>
when the argument is''Tuple<N>#
This is primarily motivated by the fact that with GHC 9.10 or later,''(##)
is syntactic sugar for''Unit#
,''(#,#)
is syntactic sugar forTuple2#
, and so on.
- The
unboxedSumNameDegree_maybe
function now returnsJust n
when the argument isSum<N>#
. This is primarily motivated by the fact that with GHC 9.10 or later,''(#|#)
is syntactic sugar forSum2#
,''(#||#)
is syntactic sugar forSum3#
, and so on. - Add
Foldable
andTraversable
instances forDTyVarBndrSpec
.
Version 1.16 [2023.10.13]
-
Support GHC 9.8.
-
Require
th-abstraction-0.6
or later. -
Add support for invisible binders in type-level declarations. As part of this change:
Language.Haskell.TH.Desugar
now exports aDTyVarBndrVis
type synonym, which is theth-desugar
counterpart toTyVarBndrVis
. It also exports adsTvbVis
function, which is theDTyVarBndrVis
counterpart todsTvbSpec
anddsTvbUnit
.Language.Haskell.TH.Desugar
now re-exportsBndrVis
fromtemplate-haskell
.- The
DDataD
,DTySynD
,DClassD
,DDataFamilyD
, andDTypeFamilyHead
parts of theth-desugar
AST now useDTyVarBndrVis
instead ofDTyVarBndrUnit
. - The
mkExtraDKindBinders
,dsCon
, anddsDataDec
functions now useDTyVarBndrVis
instead ofDTyVarBndrUnit
. - The
getDataD
function now usesTyVarBndrVis
instead ofTyVarBndrUnit
.
It is possible that you will need to convert between
TyVarBndrUnit
andTyVarBndrVis
to adapt your existingth-desugar
code. (Note thatTyVarBndr flag
is an instance ofFunctor
, so this can be accomplished withfmap
.) -
Language.Haskell.TH.Desugar
now exports a family of functions for converting type variable binders into type arguments while preserving their visibility:- The
tyVarBndrVisToTypeArg
andtyVarBndrVisToTypeArgWithSig
functions convert aTyVarBndrVis
to aTypeArg
.tyVarBndrVisToTypeArg
omits kind signatures when convertingKindedTV
s, whiletyVarBndrVisToTypeArgWithSig
preserves kind signatures. - The
dTyVarBndrVisToDTypeArg
anddTyVarBndrVisToDTypeArgWithSig
functions convert aDTyVarBndrVis
to aDTypeArg
.dTyVarBndrVisToDTypeArg
omits kind signatures when convertingDKindedTV
s, whiledTyVarBndrVisToDTypeArgWithSig
preserves kind signatures.
- The
-
th-desugar
now supports generating typed Template Haskell quotes and splices via the newDTypedBracketE
andDTypedSpliceE
constructors ofDExp
, respectively. -
The
lookupValueNameWithLocals
function will no longer reify field selectors when theNoFieldSelectors
language extension is set, mirroring the behavior of thelookupValueName
function intemplate-haskell
. Note that this will only happen when using GHC 9.8 or later, as previous versions of GHC do not equip Template Haskell with enough information to conclude whether a value is a record field or not. -
The
tupleNameDegree_maybe
function now returns:Just 0
when the argument is''Unit
Just 1
when the argument is''Solo
or'MkSolo
Just <N>
when the argument is''Tuple<N>
This is primarily motivated by the fact that with GHC 9.8 or later,''()
is syntactic sugar for''Unit
,''(,)
is syntactic sugar forTuple2
, and so on. We also include cases for''Solo
and'MkSolo
for the sake of completeness, even though they do not have any special syntactic sugar.
-
The
tupleDegree_maybe
,unboxedSumDegree_maybe
, andunboxedTupleDegree_maybe
functions have been removed. Their only use sites were in thetupleNameDegree_maybe
,unboxedSumNameDegree_maybe
, andunboxedTupleNameDegree_maybe
functions, respectively. Moreover,tupleDegree_maybe
's semantics were questionable, considering that it could potentially returnJust <N>
for a custom data type namedTuple<N>
, even if the custom data type has no relation to theTuple<N>
types defined inGHC.Tuple
. -
The
matchTy
function now looks through visible kind applications (i.e.,DAppKindT
s) wheneverYesIgnoreKinds
is given. -
Fix a bug in which infix data family declaration would mistakenly be rejected when reified locally.
-
Fix a bug in which data types that use visible dependent quantification would produce ill-scoped code when desugared.
Version 1.15 [2023.03.12]
-
Support GHC 9.6.
-
The
NewOrData
data type has been renamed toDataFlavor
and extended to supporttype data
declarations:-data NewOrData = NewType | Data +data DataFlavor = NewType | Data | TypeData
Desugaring upholds the following properties regarding
TypeData
:- A
DDataD
with aDataFlavor
ofTypeData
cannot have any deriving clauses or datatype contexts, and theDConFields
in eachDCon
will be aNormalC
where eachBang
is equal toBang NoSourceUnpackedness NoSourceStrictness
. - A
DDataInstD
can have aDataFlavor
ofNewType
orData
, but notTypeData
.
- A
-
The type of
getDataD
has been changed to also include aDataFlavor
:-getDataD :: DsMonad q => String -> Name -> q ([TyVarBndrUnit], [Con]) +getDataD :: DsMonad q => String -> Name -> q (DataFlavor, [TyVarBndrUnit], [Con])
-
Local reification can now reify the types of pattern synonym record selectors.
-
Fix a bug in which the types of locally reified GADT record selectors would sometimes have type variables quantified in the wrong order.
Version 1.14 [2022.08.23]
- Support GHC 9.4.
- Drop support for GHC 7.8 and 7.10. As a consequence of this, the
strictToBang
function was removed as it no longer serves a useful purpose. - Desugared lambda expressions and guards that bind multiple patterns can now
have patterns with unlifted types. The desugared code uses
UnboxedTuples
to make this possible, so if you load the desugared code into GHCi on prior to GHC 9.2, you will need to enable-fobject-code
. th-desugar
now desugarsPromotedInfixT
andPromotedUInfixT
, which were added in GHC 9.4. Mirroring the existing treatment of otherPromoted*
Type
s,PromotedInfixT
is desugared to an application of aDConT
applied to two arguments, just likeInfixT
is desugared. Similarly, attempting to desugar aPromotedUInfixT
results in an error, just like attempting to desugar aUInfixT
would be.th-desugar
now supportsDefaultD
(i.e.,default
declarations) andOpaqueP
(i.e.,OPAQUE
pragmas), which were added in GHC 9.4.th-desugar
now desugarsLamCasesE
(i.e.,\cases
expressions), which was added in GHC 9.4. A\cases
expression is desugared to an ordinary lambda expression, much like\case
is currently desugared.- Fix an inconsistency which caused non-exhaustive
case
expressions to be desugared into uses ofEmptyCase
. Non-exhaustivecase
expressions are now desugared into code that throws a "Non-exhaustive patterns in...
" error at runtime, just as all other forms of non-exhaustive expressions are desugared. - Fix a bug in which
expandType
would not expand closed type families when applied to arguments containing type variables.
Version 1.13.1 [2022.05.20]
- Allow building with
mtl-2.3.*
.
Version 1.13 [2021.10.30]
-
Support GHC 9.2.
-
Add support for visible type application in data constructor patterns. As a result of these changes, the
DConP
constructor now has an extra field to represent type arguments:data DPat = ... - | DConP Name [DPat] -- fun (Just x) = ... + | DConP Name [DType] [DPat] -- fun (Just @t x) = ... | ...
-
Add support for the
e.field
and(.field)
syntax from theOverloadedRecordDot
language extension. -
The
Maybe [DTyVarBndrUnit]
fields inDInstanceD
andDStandaloneDerivD
are no longer used when sweetening. Previously,th-desugar
would attempt to sweeten theseDTyVarBndrUnit
s by turning them into a nestedForallT
, but GHC 9.2 or later no longer allow this, as they forbid nestedforall
s in instance heads entirely. As a result, theMaybe [DTyVarBndrUnit]
fields are now only useful for functions that consumeDDec
s directly. -
Fix a bug in which desugared GADT constructors would sometimes incorrectly claim that they were declared infix, despite this not being the case.
Version 1.12 [2021.03.12]
-
Support GHC 9.0.
-
Add support for explicit specificity. As part of this change, the way
th-desugar
represents type variable binders has been overhauled:-
The
DTyVarBndr
data type is now parameterized by aflag
type parameter:data DTyVarBndr flag = DPlainTV Name flag | DKindedTV Name flag DKind
This can be instantiated to
Specificity
(for type variable binders that can be specified or inferred) or()
(for type variable binders where specificity is irrelevant).DTyVarBndrSpec
andDTyVarBndrUnit
are also provided as type synonyms forDTyVarBndr Specificity
andDTyVarBndr ()
, respectively. -
In order to interface with
TyVarBndr
(the TH counterpart toDTyVarBndr
) in a backwards-compatible way,th-desugar
now depends on theth-abstraction
library. -
The
ForallVisFlag
has been removed in favor of the newDForallTelescope
data type, which not only distinguishes between invisible and visibleforall
s but also uses the correct type variable flag for invisible type variables (Specificity
) and visible type variables (()
). -
The type of the
dsTvb
is now different on pre-9.0 versions of GHC:#if __GLASGOW_HASKELL__ >= 900 dsTvb :: DsMonad q => TyVarBndr flag -> q (DTyVarBndr flag) #else dsTvb :: DsMonad q => flag -> TyVarBndr -> q (DTyVarBndr flag) #endif
This is unfortunately required by the fact that prior to GHC 9.0, there is no
flag
information stored anywhere in aTyVarBndr
. If you need to usedsTvb
in a backward-compatible way,L.H.TH.Desugar
now providesdsTvbSpec
anddsTvbUnit
functions which specialisedsTvb
to particularflag
types:dsTvbSpec :: DsMonad q => TyVarBndrSpec -> q DTyVarBndrSpec dsTvbUnit :: DsMonad q => TyVarBndrUnit -> q DTyVarBndrUnit
-
-
The type of the
getRecordSelectors
function has changed:-getRecordSelectors :: DsMonad q => DType -> [DCon] -> q [DLetDec] +getRecordSelectors :: DsMonad q => [DCon] -> q [DLetDec]
The old type signature had a
DType
argument whose sole purpose was to help determine which type variables were existential, as this information was used to filter out "naughty" record selectors, like the example below:data Some :: (Type -> Type) -> Type where MkSome :: { getSome :: f a } -> Some f
The old implementation of
getRecordSelectors
would not includegetSome
in the returned list, as its typef a
mentions an existential type variable,a
, that is not mentioned in the return typeSome f
. The new implementation ofgetRecordSelectors
, on the other hand, makes no attempt to filter out naughty record selectors, so it would includegetSome
.This reason for this change is ultimately because determining which type variables are existentially quantified in the context of Template Haskell is rather challenging in the general case. There are heuristics we could employ to guess which variables are existential, but we have found these heuristics difficult to predict (let alone specify). As a result, we take the slightly less correct (but much easier to explain) approach of returning all record selectors, regardless of whether they are naughty or not.
-
The
conExistentialTvbs
function has been removed. It was horribly buggy, especially in the presence of GADT constructors. Moreover, this function was used in the implementation ofgetRecordSelectors
function, so bugs inconExistentialTvbs
often affected the results ofgetRecordSelectors
. -
The types of
decToTH
,letDecToTH
, andpragmaToTH
have changed:-decToTH :: DDec -> [Dec] +decToTH :: DDec -> Dec -letDecToTH :: DLetDec -> Maybe Dec +letDecToTH :: DLetDec -> Dec -pragmaToTH :: DPragma -> Maybe Pragma +pragmaToTH :: DPragma -> Pragma
The semantics of
pragmaToTH
have changed accordingly. Previously,pragmaToTH
would returnNothing
when the argument is aDPragma
that is not supported on an old version of GHC, but now an error will be thrown instead.decToTH
andletDecToTH
, which transitively invokepragmaToTH
, have had their types updated to accommodatepragmaToTH
's type change. -
The type of the
substTyVarBndrs
function has been simplified to avoid the needless use of continuation-passing style:-substTyVarBndrs :: Quasi q => DSubst -> [DTyVarBndr flag] -> (DSubst -> [DTyVarBndr flag] -> q a) -> q a +substTyVarBndrs :: Quasi q => DSubst -> [DTyVarBndr flag] -> q (DSubst, [DTyVarBndr flag])
-
mkDLamEFromDPats
has now generates slightly more direct code for certain lambda expressions with@
-patterns. For example,\x@y -> f x y
would previously desugar to\arg -> case arg of { y -> let x = y in f x y }
, but it now desugars to\y -> let x = y in f x y
. -
mkDLamEFromDPats
now requires only aQuasi
context instead ofDsMonad
.
Version 1.11 [2020.03.25]
- Support GHC 8.10.
- Add support for visible dependent quantification. As part of this change,
the way
th-desugar
representsforall
and constraint types has been overhauled:-
The existing
DForallT
constructor has been split into two smaller constructors:data DType = ... - | DForallT [DTyVarBndr] DCxt DType + | DForallT ForallVisFlag [DTyVarBndr] DType + | DConstrainedT DCxt DType | ... +data ForallVisFlag + = ForallVis + | ForallInvis
The previous design combined
forall
s and constraints into a single constructor, while the new design puts them in distinct constructorsDForallT
andDConstrainedT
, respectively. The newDForallT
constructor also has aForallVisFlag
field to distinguish invisibleforall
s (e.g.,forall a. a
) from visibleforall
s (e.g.,forall a -> a
). -
The
unravel
function has been renamed tounravelDType
and now returns(DFunArgs, DType)
, whereDFunArgs
is a data type that represents the possible arguments in a function type (see the Haddocks forDFunArgs
for more details). There is also anunravelDType
counterpart forType
s namedunravelType
, complete with its ownFunArgs
data type.{D}FunArgs
also have some supporting operations, includingfilter{D}VisFunArgs
(to obtain only the visible arguments) andravel{D}Type
(to construct a function type using{D}FunArgs
and a return{D}Type
).
-
- Support standalone kind signatures by adding a
DKiSigD
constructor toDDec
. - Add
dsReifyType
,reifyTypeWithLocals_maybe
, andreifyTypeWithLocals
, which allow looking up the types or kinds of locally declared entities. - Fix a bug in which
reifyFixityWithLocals
would not look into local fixity declarations inside of type classes. - Fix a bug in which
reifyFixityWithLocals
would return incorrect results for classes with associated type family defaults.
Version 1.10
-
Support GHC 8.8. Drop support for GHC 7.6.
-
Add support for visible kind application, type variable
foralls
inRULES
, and explicitforall
s in type family instances. Correspondingly,-
There is now a
DAppKindT
constructor inDType
. -
Previously, the
DDataInstD
constructor had fields of typeName
and[DType]
. Those have been scrapped in favor of a single field of typeDType
, representing the application of the data family name (which was previously theName
) to its arguments (which was previously the[DType]
).DDataInstD
also has a new field of typeMaybe [DTyVarBndr]
to represent its explicitly quantified type variables (if present). -
Previously, the
DTySynEqn
constructor had a field of type[DType]
. That has been scrapped in favor of a field of typeDType
, representing the application of the type family name (whichDTySynEqn
did not used to contain!) to its arguments (which was previously the[DType]
).DTySynEqn
also has a new field of typeMaybe [DTyVarBndr]
to represent its explicitly quantified type variables (if present). -
DTySynInstD
no longer has a field of typeName
, as that is redundant now that eachDTySynEqn
contains the sameName
. -
There is now a field of type
Maybe [DTyVarBndr]
in theDRuleP
constructor to represent bound type variables inRULES
(if present).
-
-
Add a field of type
Maybe [DTyVarBndr]
toDInstanceD
andDStandaloneDerivD
for optionally quantifying type variables explicitly. If supplied with aJust
, this sweetens the instance type to use aForallT
to represent the explicit quantification. This trick is not supported forInstanceD
on GHC 8.0 and forStandaloneDerivD
on GHC 7.10 or 8.0, so be aware of this limitation if you supplyJust
for this field. -
Add support for desugaring implicit params. This does not involve any changes to the
th-desugar
AST, as:(?x :: a) => ...
is desugared toIP "x" a => ...
.id ?x
is desugared toid (ip @"x")
.let ?x = 42 in ...
is desugared tolet new_x_val = 42 in bindIP @"x" new_x_val ...
(wherebindIP
is a new utility function exported byLanguage.Haskell.TH.Desugar
on GHC 8.0 or later).
In order to support this desugaring, the type signatures of
dsLetDec
anddsLetDecs
now return([DLetDec], DExp -> DExp)
instead of just[DLetDec]
, whereDExp -> DExp
is the expression which binds the values of implicit params (e.g.,\z -> bindIP @"x" new_x_val z
) if any are bound. (If none are bound, this is simply theid
function.) -
Fix a bug in which
toposortTyVarsOf
would error at runtime if given types containingforall
s as arguments. -
Fix a bug in which
fvDType
would return incorrect results if given a type containing quantified constraints. -
Fix a bug in which
expandType
would not expand type synonyms in the kinds of type variable binders inforall
s. -
Fix a bug in which
getRecordSelectors
would omit record selectors from GADT constructors. -
Fix a bug in which
toposortTyVarsOf
would sometimes not preserve the left-to-right ordering ofName
s generated withqNewName
. -
Locally reified class methods, data constructors, and record selectors now quantify kind variables properly.
-
Desugared ADT constructors now quantify kind variables properly.
-
Remove
DPred
, as it has become too similar toDType
. This also means that theDPat
constructors, which previously ended with the suffixPa
, can now use the suffixP
, mirroring TH. -
The type of
applyDType
has changed fromDType -> [DType] -> DType
toDType -> [DTypeArg] -> DType
, whereDTypeArg
is a new data type that encodes whether an argument is a normal type argument (e.g., theInt
inMaybe Int
) or a visible kind argument (e.g., the@Type
inProxy @Type Char
). ATypeArg
data type (which is likeDTypeArg
, but withType
s/Kind
s instead ofDType
s/DKind
s) is also provided.A handful of utility functions for manipulating
TypeArg
s andDTypeArg
s are also exported. -
th-desugar
functions that compute free variables (e.g.,fvDType
) now return anOSet
, a variant ofSet
that remembers the order in which elements were inserted. A consequence of this change is that it fixes a bug that causes free variables to be computed in different orders depending on which unique numbers GHC happened to generate internally. -
Substition and type synonym expansion are now more efficient by avoiding the use of
syb
in inner loops.
Version 1.9
-
Suppose GHC 8.6.
-
Add support for
DerivingVia
. Correspondingly, there is now aDDerivStrategy
data type. -
Add support for
QuantifiedConstraints
. Correspondingly, there is now aDForallPr
constructor inDPred
to represent quantified constraint types. -
Remove the
DStarT
constructor ofDType
in favor ofDConT ''Type
. Two utility functions have been added toLanguage.Haskell.TH.Desugar
to ease this transition:isTypeKindName
: returnsTrue
if the argumentName
is that ofType
or★
(or*
, to support older GHCs).typeKindName
: the name ofType
(on GHC 8.0 or later) or*
(on older GHCs).
-
th-desugar
now desugars all data types to GADT syntax. The most significant API-facing changes resulting from this new design are:-
The
DDataD
,DDataFamilyD
, andDDataFamInstD
constructors ofDDec
now haveMaybe DKind
fields that either haveJust
an explicit return kind (e.g., thek -> Type -> Type
indata Foo :: k -> Type -> Type
) orNothing
(if lacking an explicit return kind). -
The
DCon
constructor previously had a field of typeMaybe DType
, since there was a possibility it could be a GADT (with an explicit return type) or non-GADT (without an explicit return type) constructor. Since all data types are desugared to GADTs now, this field has been changed to be simply aDType
. -
The type signature of
dsCon
was previously:dsCon :: DsMonad q => Con -> q [DCon]
However, desugaring constructors now needs more information than before, since GADT constructors have richer type signatures. Accordingly, the type of
dsCon
is now:dsCon :: DsMonad q => [DTyVarBndr] -- ^ The universally quantified type variables -- (used if desugaring a non-GADT constructor) -> DType -- ^ The original data declaration's type -- (used if desugaring a non-GADT constructor). -> Con -> q [DCon]
The
instance Desugar [Con] [DCon]
has also been removed, as the previous implementation ofdesugar
(concatMapM dsCon
) no longer has enough information to work.
Some other utility functions have also been added as part of this change:
-
A
conExistentialTvbs
function has been introduced to determine the existentially quantified type variables of aDCon
. Note that this function is not 100% accurate—refer to the documentation forconExistentialTvbs
for more information. -
A
mkExtraDKindBinders
function has been introduced to turn a data type's return kind into explicit, fresh type variable binders. -
A
toposortTyVarsOf
function, which finds the free variables of a list ofDType
s and returns them in a well scoped list that has been sorted in reverse topological order.
-
-
th-desugar
now desugars partial pattern matches indo
-notation and list/monad comprehensions to the appropriate invocation offail
. (Previously, these were incorrectly desugared intocase
expressions with incomplete patterns.) -
Add a
mkDLamEFromDPats
function for constructing aDLamE
expression using a list ofDPat
arguments and aDExp
body. -
Add an
unravel
function for decomposing a function type into itsforall
'd type variables, its context, its argument types, and its result type. -
Export a
substTyVarBndrs
function fromLanguage.Haskell.TH.Desugar.Subst
, which substitutes over type variable binders in a capture-avoiding fashion. -
getDataD
,dataConNameToDataName
, anddataConNameToCon
fromLanguage.Haskell.TH.Desugar.Reify
now look up local declarations. As a result, the contexts in their type signatures have been strengthened fromQuasi
toDsMonad
. -
Export a
dTyVarBndrToDType
function which converts aDTyVarBndr
to aDType
, which preserves its kind. -
Previously,
th-desugar
would silently accept illegal uses of record construction with fields that did not belong to the constructor, such asIdentity { notAField = "wat" }
. This is now an error.
Version 1.8
-
Support GHC 8.4.
-
substTy
now properly substitutes into kind signatures. -
Expose
fvDType
, which computes the free variables of aDType
. -
Incorporate a
DDeclaredInfix
field intoDNormalC
to indicate if it is a constructor that was declared infix. -
Implement
lookupValueNameWithLocals
,lookupTypeNameWithLocals
,mkDataNameWithLocals
, andmkTypeNameWithLocals
, counterparts tolookupValueName
,lookupTypeName
,mkDataName
, andmkTypeName
which have access to local Template Haskell declarations. -
Implement
reifyNameSpace
to determine aName
'sNameSpace
. -
Export
reifyFixityWithLocals
fromLanguage.Haskell.TH.Desugar
. -
Export
matchTy
(among other goodies) from new moduleLanguage.Haskell.TH.Subst
. This function matches a type template against a target.
Version 1.7
-
Support for TH's support for
TypeApplications
, thanks to @RyanGlScott. -
Support for unboxed sums, thanks to @RyanGlScott.
-
Support for
COMPLETE
pragmas. -
getRecordSelectors
now requires a list ofDCon
s as an argument. This makes it easier to return correct record selector bindings in the event that a record selector appears in multiple constructors. (See goldfirere/singletons#180 for an example of where the old behavior ofgetRecordSelectors
went wrong.) -
Better type family expansion (expanding an open type family with variables works now).
Version 1.6
-
Work with GHC 8, with thanks to @christiaanb for getting this change going. This means that several core datatypes have changed: partcularly, we now have
DTypeFamilyHead
and fixities are now reified separately from other things. -
DKind
is merged withDType
. -
Generic
instances for everything.
Version 1.5.5
- Fix issue #34. This means that desugaring (twice) is idempotent over expressions, after the second time. That is, if you desugar an expression, sweeten it, desugar again, sweeten again, and then desugar a third time, you get the same result as when you desugared the second time. (The extra round-trip is necessary there to make the output smaller in certain common cases.)
Version 1.5.4.1
- Fix issue #32, concerning reification of classes with default methods.
Version 1.5.4
- Added
expandUnsoundly
Version 1.5.3
- More
DsMonad
instances, thanks to David Fox.
Version 1.5.2
- Sweeten kinds more, too.
Version 1.5.1
-
Thanks to David Fox (@ddssff), sweetening now tries to use more of TH's
Type
constructors. -
Also thanks to David Fox, depend usefully on the th-orphans package.
Version 1.5
-
There is now a facility to register a list of
Dec
that internal reification should use when necessary. This avoids the user needing to break up their definition across different top-level splices. SeewithLocalDeclarations
. This has a side effect of changing theQuasi
typeclass constraint on many functions to be the newDsMonad
constraint. Happily, there areDsMonad
instances forQ
andIO
, the two normal inhabitants ofQuasi
. -
"Match flattening" is implemented! The functions
scExp
andscLetDec
remove any nested pattern matches. -
More is now exported from
Language.Haskell.TH.Desugar
for ease of use. -
expand
can now expand closed type families! It still requires that the type to expand contain no type variables. -
Support for standalone-deriving and default signatures in GHC 7.10. This means that there are now two new constructors for
DDec
. -
Support for
static
expressions, which are new in GHC 7.10.
Version 1.4.2
expand
functions now consider open type families, as long as the type to be expanded has no free variables.
Version 1.4.1
-
Added
Language.Haskell.TH.Desugar.Lift
, which providesLift
instances for all of the th-desugar types, as well as several Template Haskell types. -
Added
applyDExp
andapplyDType
as convenience functions.
Version 1.4.0
-
All
Dec
s can now be desugared, to the newDDec
type. -
Sweetening
Dec
s that do not exist in GHC 7.6.3- works on a "best effort" basis: closed type families are sweetened to open ones, and role annotations are dropped. -
Info
s can now be desugared. Desugaring takes into account GHC bug #8884, which meant that reifying poly-kinded type families in GHC 7.6.3- was subtly wrong. -
There is a new function
flattenDValD
which takes a binding likelet (a,b) = foo
and breaks it apart into separate assignments fora
andb
. -
There is a new
Desugar
class with methodsdesugar
andsweeten
. See the documentation inLanguage.Haskell.TH.Desugar
. -
Variable names that are distinct in desugared code are now guaranteed to have distinct answers to
nameBase
. -
Added a new function
getRecordSelectors
that extracts types and definitions of record selectors from a datatype definition.
Version 1.3.1
- Update cabal file to include testing files in sdist.
Version 1.3.0
- Update to work with
type Pred = Type
in GHC 7.9. This changed theDPred
type for all GHC versions, though.
Version 1.2.0
- Generalized interface to allow any member of the
Qausi
class, instead of justQ
.
Version 1.1.1
- Made compatible with HEAD after change in role annotation syntax.
Version 1.1
- Added module
Language.Haskell.TH.Desugar.Expand
, which allows for expansion of type synonyms in desugared types. - Added
Show
,Typeable
, andData
instances to desugared types. - Fixed bug where an as-pattern in a
let
statement was scoped incorrectly. - Changed signature of
dsPat
to be more specific to as-patterns; this allowed for fixing thelet
scoping bug. - Created new functions
dsPatOverExp
anddsPatsOverExp
to allow for easy desugaring of patterns. - Changed signature of
dsLetDec
to return a list ofDLetDec
s. - Added
dsLetDecs
for convenience. Now, instead of usingmapM dsLetDec
, you should usedsLetDecs
.
Version 1.0
- Initial release