| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
SumTypesX.TH
Synopsis
- constructSumType :: String -> SumTypeOptions -> [Name] -> Q [Dec]
- data SumTypeOptions
- defaultSumTypeOptions :: SumTypeOptions
- sumTypeOptionsTagOptions :: SumTypeOptions -> SumTypeTagOptions
- data SumTypeTagOptions
- sumTypeOptionsConstructorStrictness :: SumTypeOptions -> SumTypeConstructorStrictness
- data SumTypeConstructorStrictness
- sumTypeConverter :: String -> Name -> Name -> Q [Dec]
- partialSumTypeConverter :: String -> Name -> Name -> Q [Dec]
Constructing sum types
constructSumType :: String -> SumTypeOptions -> [Name] -> Q [Dec] Source #
This is a template haskell function that creates a sum type from a list of types. Here is an example:
data TypeA = TypeA data TypeB = TypeB data TypeC = TypeC constructSumType "MySum" defaultSumTypeOptions [''TypeA, ''TypeB, ''TypeC]
This will produce the following sum type:
data MySum = MySumTypeA TypeA | MySumTypeB TypeB | MySumTypeC TypeC
Note that you can use standalone deriving to derive any instances you want:
deriving instance Show MySum deriving instance Eq MySum
data SumTypeOptions Source #
Options for constructSumType. Note that the constructor for this type is
 not exported, please use defaultSumTypeOptions. (This is done for
 the sake of backwards compatibility in case we add options.)
defaultSumTypeOptions :: SumTypeOptions Source #
Default options for SumTypeOptions
SumTypeOptions{sumTypeOptionsTagOptions=PrefixTagsWithTypeName,sumTypeOptionsConstructorStrictness=LazySumTypeConstructors}
data SumTypeTagOptions Source #
This type specifies how constructSumType will generate the tags for each
 type.
Constructors
| PrefixTagsWithTypeName | This option generates tags with the sum type name prefixed to each tag. | 
| AppendTypeNameToTags | This option generates tags with the sum type name appended to each tag. | 
| ConstructTagName (String -> String) | Uses the given function to construct an arbitrary tag name. The argument to this function is the name of the tagged type. | 
data SumTypeConstructorStrictness Source #
Defines if the constructors for the sum type should be lazy or strict.
Constructors
| LazySumTypeConstructors | Constructors will be lazy | 
| StrictSumTypeConstructors | Constructors will be strict | 
Instances
| Show SumTypeConstructorStrictness Source # | |
| Defined in SumTypesX.TH Methods showsPrec :: Int -> SumTypeConstructorStrictness -> ShowS # show :: SumTypeConstructorStrictness -> String # showList :: [SumTypeConstructorStrictness] -> ShowS # | |
| Eq SumTypeConstructorStrictness Source # | |
| Defined in SumTypesX.TH Methods (==) :: SumTypeConstructorStrictness -> SumTypeConstructorStrictness -> Bool # (/=) :: SumTypeConstructorStrictness -> SumTypeConstructorStrictness -> Bool # | |
Converting between sum types
sumTypeConverter :: String -> Name -> Name -> Q [Dec] Source #
This template haskell function creates a conversion function between two sum types. It works by matching up constructors that share the same inner type. Note that all types in the source sum type must be present in the target sum type, or you will get an error.
data MySum = MySumTypeA TypeA | MySumTypeB TypeB | MySumTypeC TypeC data OtherSum = OtherSumTypeA TypeA | OtherSumTypeB TypeB sumTypeConverter "otherSumToMySum" ''OtherSum ''MySum
This will producing the following code:
otherSumToMySum :: OtherSum -> MySum otherSumToMySum (OtherSumTypeA typeA) = MySumTypeA typeA otherSumToMySum (OtherSumTypeB typeB) = MySumTypeB typeB
partialSumTypeConverter :: String -> Name -> Name -> Q [Dec] Source #
Similar to sumTypeConverter, except not all types in the source sum type
 need to be present in the target sum type.
Note that this doesn't produce a partial function in the Haskell sense; you
 won't get an error with the generated function on any arguments. The word
 partial is used mathematically to denote that not all types from the source
 sum type are present in the target sum type.
data MySum = MySumTypeA TypeA | MySumTypeB TypeB | MySumTypeC TypeC data OtherSum = OtherSumTypeA TypeA | OtherSumTypeB TypeB partialSumTypeConverter "mySumToOtherSum" ''MySum ''OtherSum
This will producing the following code:
mySumToOtherSum :: MySum -> Maybe OtherSum mySumToOtherSum (MySumTypeA typeA) = Just $ OtherSumTypeA typeA mySumToOtherSum (MySumTypeB typeB) = Just $ OtherSumTypeB typeB mySumToOtherSum other = Nothing