#if __GLASGOW_HASKELL__ >= 800
#else
#endif
#include "incoherent-compat.h"
#include "overlapping-compat.h"
module Data.Aeson.TH
(
Options(..)
, SumEncoding(..)
, defaultOptions
, defaultTaggedObject
, deriveJSON
, deriveJSON1
, deriveJSON2
, deriveToJSON
, deriveToJSON1
, deriveToJSON2
, deriveFromJSON
, deriveFromJSON1
, deriveFromJSON2
, mkToJSON
, mkLiftToJSON
, mkLiftToJSON2
, mkToEncoding
, mkLiftToEncoding
, mkLiftToEncoding2
, mkParseJSON
, mkLiftParseJSON
, mkLiftParseJSON2
) where
import Prelude ()
import Prelude.Compat hiding (exp)
import Control.Applicative ((<|>))
import Data.Aeson (Object, (.=), (.:), FromJSON(..), FromJSON1(..), FromJSON2(..), ToJSON(..), ToJSON1(..), ToJSON2(..))
import Data.Aeson.Types (Options(..), Parser, SumEncoding(..), Value(..), defaultOptions, defaultTaggedObject)
import Data.Aeson.Types.Internal ((<?>), JSONPathElement(Key))
import Data.Aeson.Types.FromJSON (parseOptionalFieldWith)
import Control.Monad (liftM2, unless, when)
import Data.Foldable (foldr')
#if MIN_VERSION_template_haskell(2,8,0) && !MIN_VERSION_template_haskell(2,10,0)
import Data.List (nub)
#endif
import Data.List (foldl', genericLength, intercalate, partition, union)
import Data.List.NonEmpty ((<|), NonEmpty((:|)))
import Data.Map (Map)
import Data.Maybe (catMaybes, fromMaybe, mapMaybe)
import Data.Set (Set)
#if MIN_VERSION_template_haskell(2,8,0)
import Language.Haskell.TH hiding (Arity)
#else
import Language.Haskell.TH
#endif
import Language.Haskell.TH.Datatype
#if MIN_VERSION_template_haskell(2,7,0) && !(MIN_VERSION_template_haskell(2,8,0))
import Language.Haskell.TH.Lib (starK)
#endif
#if MIN_VERSION_template_haskell(2,8,0) && !(MIN_VERSION_template_haskell(2,10,0))
import Language.Haskell.TH.Syntax (mkNameG_tc)
#endif
import Text.Printf (printf)
import qualified Data.Aeson as A
import qualified Data.Aeson.Encoding.Internal as E
import qualified Data.Foldable as F (all)
import qualified Data.HashMap.Strict as H (lookup, toList)
import qualified Data.List.NonEmpty as NE (length, reverse)
import qualified Data.Map as M (fromList, keys, lookup , singleton, size)
import qualified Data.Semigroup as Semigroup (Option(..))
import qualified Data.Set as Set (empty, insert, member)
import qualified Data.Text as T (Text, pack, unpack)
import qualified Data.Vector as V (unsafeIndex, null, length, create, empty)
import qualified Data.Vector.Mutable as VM (unsafeNew, unsafeWrite)
deriveJSON :: Options
-> Name
-> Q [Dec]
deriveJSON = deriveJSONBoth deriveToJSON deriveFromJSON
deriveJSON1 :: Options
-> Name
-> Q [Dec]
deriveJSON1 = deriveJSONBoth deriveToJSON1 deriveFromJSON1
deriveJSON2 :: Options
-> Name
-> Q [Dec]
deriveJSON2 = deriveJSONBoth deriveToJSON2 deriveFromJSON2
deriveToJSON :: Options
-> Name
-> Q [Dec]
deriveToJSON = deriveToJSONCommon toJSONClass
deriveToJSON1 :: Options
-> Name
-> Q [Dec]
deriveToJSON1 = deriveToJSONCommon toJSON1Class
deriveToJSON2 :: Options
-> Name
-> Q [Dec]
deriveToJSON2 = deriveToJSONCommon toJSON2Class
deriveToJSONCommon :: JSONClass
-> Options
-> Name
-> Q [Dec]
deriveToJSONCommon = deriveJSONClass [ (ToJSON, \jc _ -> consToValue Value jc)
, (ToEncoding, \jc _ -> consToValue Encoding jc)
]
mkToJSON :: Options
-> Name
-> Q Exp
mkToJSON = mkToJSONCommon toJSONClass
mkLiftToJSON :: Options
-> Name
-> Q Exp
mkLiftToJSON = mkToJSONCommon toJSON1Class
mkLiftToJSON2 :: Options
-> Name
-> Q Exp
mkLiftToJSON2 = mkToJSONCommon toJSON2Class
mkToJSONCommon :: JSONClass
-> Options
-> Name
-> Q Exp
mkToJSONCommon = mkFunCommon (\jc _ -> consToValue Value jc)
mkToEncoding :: Options
-> Name
-> Q Exp
mkToEncoding = mkToEncodingCommon toJSONClass
mkLiftToEncoding :: Options
-> Name
-> Q Exp
mkLiftToEncoding = mkToEncodingCommon toJSON1Class
mkLiftToEncoding2 :: Options
-> Name
-> Q Exp
mkLiftToEncoding2 = mkToEncodingCommon toJSON2Class
mkToEncodingCommon :: JSONClass
-> Options
-> Name
-> Q Exp
mkToEncodingCommon = mkFunCommon (\jc _ -> consToValue Encoding jc)
consToValue :: ToJSONFun
-> JSONClass
-> Options
-> [Type]
-> [ConstructorInfo]
-> Q Exp
consToValue _ _ _ _ [] = error $ "Data.Aeson.TH.consToValue: "
++ "Not a single constructor given!"
consToValue target jc opts vars cons = do
value <- newName "value"
tjs <- newNameList "_tj" $ arityInt jc
tjls <- newNameList "_tjl" $ arityInt jc
let zippedTJs = zip tjs tjls
interleavedTJs = interleave tjs tjls
lastTyVars = map varTToName $ drop (length vars arityInt jc) vars
tvMap = M.fromList $ zip lastTyVars zippedTJs
lamE (map varP $ interleavedTJs ++ [value]) $
caseE (varE value) (matches tvMap)
where
matches tvMap = case cons of
[con] | not (tagSingleConstructors opts) -> [argsToValue target jc tvMap opts False con]
_ | allNullaryToStringTag opts && all isNullary cons ->
[ match (conP conName []) (normalB $ conStr target opts conName) []
| con <- cons
, let conName = constructorName con
]
| otherwise -> [argsToValue target jc tvMap opts True con | con <- cons]
conStr :: ToJSONFun -> Options -> Name -> Q Exp
conStr Value opts = appE [|String|] . conTxt opts
conStr Encoding opts = appE [|E.text|] . conTxt opts
conTxt :: Options -> Name -> Q Exp
conTxt opts = appE [|T.pack|] . stringE . conString opts
conString :: Options -> Name -> String
conString opts = constructorTagModifier opts . nameBase
isNullary :: ConstructorInfo -> Bool
isNullary ConstructorInfo { constructorVariant = NormalConstructor
, constructorFields = tys } = null tys
isNullary _ = False
opaqueSumToValue :: ToJSONFun -> Options -> Bool -> Bool -> Name -> ExpQ -> ExpQ
opaqueSumToValue target opts multiCons nullary conName value =
sumToValue target opts multiCons nullary conName
value
pairs
where
pairs contentsFieldName = listE [toPair target contentsFieldName value]
recordSumToValue :: ToJSONFun -> Options -> Bool -> Bool -> Name -> ExpQ -> ExpQ
recordSumToValue target opts multiCons nullary conName pairs =
sumToValue target opts multiCons nullary conName
(objectExp target pairs)
(const pairs)
sumToValue
:: ToJSONFun
-> Options
-> Bool
-> Bool
-> Name
-> ExpQ
-> (String -> ExpQ)
-> ExpQ
sumToValue target opts multiCons nullary conName value pairs
| multiCons =
case sumEncoding opts of
TwoElemArray ->
array target [conStr target opts conName, value]
TaggedObject{tagFieldName, contentsFieldName} ->
let tag = toPair target tagFieldName (conStr target opts conName)
content = pairs contentsFieldName
in objectExp target $
if nullary then listE [tag] else infixApp tag [|(:)|] content
ObjectWithSingleField ->
object target [(conString opts conName, value)]
UntaggedValue | nullary -> conStr target opts conName
UntaggedValue -> value
| otherwise = value
argsToValue :: ToJSONFun -> JSONClass -> TyVarMap -> Options -> Bool -> ConstructorInfo -> Q Match
argsToValue target jc tvMap opts multiCons
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = argTys } = do
argTys' <- mapM resolveTypeSynonyms argTys
let len = length argTys'
args <- newNameList "arg" len
let js = case [ dispatchToJSON target jc conName tvMap argTy
`appE` varE arg
| (arg, argTy) <- zip args argTys'
] of
[e] -> e
es -> array target es
match (conP conName $ map varP args)
(normalB $ opaqueSumToValue target opts multiCons (null argTys') conName js)
[]
argsToValue target jc tvMap opts multiCons
info@ConstructorInfo { constructorName = conName
, constructorVariant = RecordConstructor fields
, constructorFields = argTys } =
case (unwrapUnaryRecords opts, not multiCons, argTys) of
(True,True,[_]) -> argsToValue target jc tvMap opts multiCons
(info{constructorVariant = NormalConstructor})
_ -> do
argTys' <- mapM resolveTypeSynonyms argTys
args <- newNameList "arg" $ length argTys'
let pairs | omitNothingFields opts = infixApp maybeFields
[|(++)|]
restFields
| otherwise = listE $ map pureToPair argCons
argCons = zip3 (map varE args) argTys' fields
maybeFields = [|catMaybes|] `appE` listE (map maybeToPair maybes)
restFields = listE $ map pureToPair rest
(maybes0, rest0) = partition isMaybe argCons
(options, rest) = partition isOption rest0
maybes = maybes0 ++ map optionToMaybe options
maybeToPair = toPairLifted True
pureToPair = toPairLifted False
toPairLifted lifted (arg, argTy, field) =
let toValue = dispatchToJSON target jc conName tvMap argTy
fieldName = fieldLabel opts field
e arg' = toPair target fieldName (toValue `appE` arg')
in if lifted
then do
x <- newName "x"
infixApp (lam1E (varP x) (e (varE x))) [|(<$>)|] arg
else e arg
match (conP conName $ map varP args)
(normalB $ recordSumToValue target opts multiCons (null argTys) conName pairs)
[]
argsToValue target jc tvMap opts multiCons
ConstructorInfo { constructorName = conName
, constructorVariant = InfixConstructor
, constructorFields = argTys } = do
[alTy, arTy] <- mapM resolveTypeSynonyms argTys
al <- newName "argL"
ar <- newName "argR"
match (infixP (varP al) conName (varP ar))
( normalB
$ opaqueSumToValue target opts multiCons False conName
$ array target
[ dispatchToJSON target jc conName tvMap aTy
`appE` varE a
| (a, aTy) <- [(al,alTy), (ar,arTy)]
]
)
[]
isMaybe :: (a, Type, b) -> Bool
isMaybe (_, AppT (ConT t) _, _) = t == ''Maybe
isMaybe _ = False
isOption :: (a, Type, b) -> Bool
isOption (_, AppT (ConT t) _, _) = t == ''Semigroup.Option
isOption _ = False
optionToMaybe :: (ExpQ, b, c) -> (ExpQ, b, c)
optionToMaybe (a, b, c) = ([|Semigroup.getOption|] `appE` a, b, c)
(<^>) :: ExpQ -> ExpQ -> ExpQ
(<^>) a b = infixApp a [|(E.><)|] b
infixr 6 <^>
(<:>) :: ExpQ -> ExpQ -> ExpQ
(<:>) a b = a <^> [|E.colon|] <^> b
infixr 5 <:>
(<%>) :: ExpQ -> ExpQ -> ExpQ
(<%>) a b = a <^> [|E.comma|] <^> b
infixr 4 <%>
array :: ToJSONFun -> [ExpQ] -> ExpQ
array Encoding [] = [|E.emptyArray_|]
array Value [] = [|Array V.empty|]
array Encoding es = [|E.wrapArray|] `appE` foldr1 (<%>) es
array Value es = do
mv <- newName "mv"
let newMV = bindS (varP mv)
([|VM.unsafeNew|] `appE`
litE (integerL $ fromIntegral (length es)))
stmts = [ noBindS $
[|VM.unsafeWrite|] `appE`
varE mv `appE`
litE (integerL ix) `appE`
e
| (ix, e) <- zip [(0::Integer)..] es
]
ret = noBindS $ [|return|] `appE` varE mv
[|Array|] `appE`
(varE 'V.create `appE`
doE (newMV:stmts++[ret]))
object :: ToJSONFun -> [(String, ExpQ)] -> ExpQ
object target = wrapObject target . catPairs target . fmap (uncurry (toPair target))
catPairs :: ToJSONFun -> [ExpQ] -> ExpQ
catPairs Value = listE
catPairs Encoding = foldr1 (<%>)
objectExp :: ToJSONFun -> ExpQ -> ExpQ
objectExp target = wrapObject target . catPairsExp target
catPairsExp :: ToJSONFun -> ExpQ -> ExpQ
catPairsExp Value e = e
catPairsExp Encoding e = [|commaSep|] `appE` e
toPair :: ToJSONFun -> String -> ExpQ -> ExpQ
toPair Value k v = infixApp [|T.pack k|] [|(.=)|] v
toPair Encoding k v = [|E.string k|] <:> v
wrapObject :: ToJSONFun -> ExpQ -> ExpQ
wrapObject Value e = [|A.object|] `appE` e
wrapObject Encoding e = [|E.wrapObject|] `appE` e
commaSep :: [E.Encoding] -> E.Encoding
commaSep [] = E.empty
commaSep [x] = x
commaSep (x : xs) = x E.>< E.comma E.>< commaSep xs
deriveFromJSON :: Options
-> Name
-> Q [Dec]
deriveFromJSON = deriveFromJSONCommon fromJSONClass
deriveFromJSON1 :: Options
-> Name
-> Q [Dec]
deriveFromJSON1 = deriveFromJSONCommon fromJSON1Class
deriveFromJSON2 :: Options
-> Name
-> Q [Dec]
deriveFromJSON2 = deriveFromJSONCommon fromJSON2Class
deriveFromJSONCommon :: JSONClass
-> Options
-> Name
-> Q [Dec]
deriveFromJSONCommon = deriveJSONClass [(ParseJSON, consFromJSON)]
mkParseJSON :: Options
-> Name
-> Q Exp
mkParseJSON = mkParseJSONCommon fromJSONClass
mkLiftParseJSON :: Options
-> Name
-> Q Exp
mkLiftParseJSON = mkParseJSONCommon fromJSON1Class
mkLiftParseJSON2 :: Options
-> Name
-> Q Exp
mkLiftParseJSON2 = mkParseJSONCommon fromJSON2Class
mkParseJSONCommon :: JSONClass
-> Options
-> Name
-> Q Exp
mkParseJSONCommon = mkFunCommon consFromJSON
consFromJSON :: JSONClass
-> Name
-> Options
-> [Type]
-> [ConstructorInfo]
-> Q Exp
consFromJSON _ _ _ _ [] = error $ "Data.Aeson.TH.consFromJSON: "
++ "Not a single constructor given!"
consFromJSON jc tName opts vars cons = do
value <- newName "value"
pjs <- newNameList "_pj" $ arityInt jc
pjls <- newNameList "_pjl" $ arityInt jc
let zippedPJs = zip pjs pjls
interleavedPJs = interleave pjs pjls
lastTyVars = map varTToName $ drop (length vars arityInt jc) vars
tvMap = M.fromList $ zip lastTyVars zippedPJs
lamE (map varP $ interleavedPJs ++ [value]) $ lamExpr value tvMap
where
checkExi tvMap con = checkExistentialContext jc tvMap
(constructorContext con)
(constructorName con)
lamExpr value tvMap = case cons of
[con]
| not (tagSingleConstructors opts)
-> checkExi tvMap con $ parseArgs jc tvMap tName opts con (Right value)
_ | sumEncoding opts == UntaggedValue
-> parseUntaggedValue tvMap cons value
| otherwise
-> caseE (varE value) $
if allNullaryToStringTag opts && all isNullary cons
then allNullaryMatches
else mixedMatches tvMap
allNullaryMatches =
[ do txt <- newName "txt"
match (conP 'String [varP txt])
(guardedB $
[ liftM2 (,) (normalG $
infixApp (varE txt)
[|(==)|]
(conTxt opts conName)
)
([|pure|] `appE` conE conName)
| con <- cons
, let conName = constructorName con
]
++
[ liftM2 (,)
(normalG [|otherwise|])
( [|noMatchFail|]
`appE` litE (stringL $ show tName)
`appE` ([|T.unpack|] `appE` varE txt)
)
]
)
[]
, do other <- newName "other"
match (varP other)
(normalB $ [|noStringFail|]
`appE` litE (stringL $ show tName)
`appE` ([|valueConName|] `appE` varE other)
)
[]
]
mixedMatches tvMap =
case sumEncoding opts of
TaggedObject {tagFieldName, contentsFieldName} ->
parseObject $ parseTaggedObject tvMap tagFieldName contentsFieldName
UntaggedValue -> error "UntaggedValue: Should be handled already"
ObjectWithSingleField ->
parseObject $ parseObjectWithSingleField tvMap
TwoElemArray ->
[ do arr <- newName "array"
match (conP 'Array [varP arr])
(guardedB
[ liftM2 (,) (normalG $ infixApp ([|V.length|] `appE` varE arr)
[|(==)|]
(litE $ integerL 2))
(parse2ElemArray tvMap arr)
, liftM2 (,) (normalG [|otherwise|])
([|not2ElemArray|]
`appE` litE (stringL $ show tName)
`appE` ([|V.length|] `appE` varE arr))
]
)
[]
, do other <- newName "other"
match (varP other)
( normalB
$ [|noArrayFail|]
`appE` litE (stringL $ show tName)
`appE` ([|valueConName|] `appE` varE other)
)
[]
]
parseObject f =
[ do obj <- newName "obj"
match (conP 'Object [varP obj]) (normalB $ f obj) []
, do other <- newName "other"
match (varP other)
( normalB
$ [|noObjectFail|]
`appE` litE (stringL $ show tName)
`appE` ([|valueConName|] `appE` varE other)
)
[]
]
parseTaggedObject tvMap typFieldName valFieldName obj = do
conKey <- newName "conKey"
doE [ bindS (varP conKey)
(infixApp (varE obj)
[|(.:)|]
([|T.pack|] `appE` stringE typFieldName))
, noBindS $ parseContents tvMap conKey (Left (valFieldName, obj)) 'conNotFoundFailTaggedObject
]
parseUntaggedValue tvMap cons' conVal =
foldr1 (\e e' -> infixApp e [|(<|>)|] e')
(map (\x -> parseValue tvMap x conVal) cons')
parseValue _tvMap
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = [] }
conVal = do
str <- newName "str"
caseE (varE conVal)
[ match (conP 'String [varP str])
(guardedB
[ liftM2 (,) (normalG $ infixApp (varE str) [|(==)|] (conTxt opts conName)
)
([|pure|] `appE` conE conName)
]
)
[]
, matchFailed tName conName "String"
]
parseValue tvMap con conVal =
checkExi tvMap con $ parseArgs jc tvMap tName opts con (Right conVal)
parse2ElemArray tvMap arr = do
conKey <- newName "conKey"
conVal <- newName "conVal"
let letIx n ix =
valD (varP n)
(normalB ([|V.unsafeIndex|] `appE`
varE arr `appE`
litE (integerL ix)))
[]
letE [ letIx conKey 0
, letIx conVal 1
]
(caseE (varE conKey)
[ do txt <- newName "txt"
match (conP 'String [varP txt])
(normalB $ parseContents tvMap
txt
(Right conVal)
'conNotFoundFail2ElemArray
)
[]
, do other <- newName "other"
match (varP other)
( normalB
$ [|firstElemNoStringFail|]
`appE` litE (stringL $ show tName)
`appE` ([|valueConName|] `appE` varE other)
)
[]
]
)
parseObjectWithSingleField tvMap obj = do
conKey <- newName "conKey"
conVal <- newName "conVal"
caseE ([e|H.toList|] `appE` varE obj)
[ match (listP [tupP [varP conKey, varP conVal]])
(normalB $ parseContents tvMap conKey (Right conVal) 'conNotFoundFailObjectSingleField)
[]
, do other <- newName "other"
match (varP other)
(normalB $ [|wrongPairCountFail|]
`appE` litE (stringL $ show tName)
`appE` ([|show . length|] `appE` varE other)
)
[]
]
parseContents tvMap conKey contents errorFun =
caseE (varE conKey)
[ match wildP
( guardedB $
[ do g <- normalG $ infixApp (varE conKey)
[|(==)|]
([|T.pack|] `appE`
conNameExp opts con)
e <- checkExi tvMap con $
parseArgs jc tvMap tName opts con contents
return (g, e)
| con <- cons
]
++
[ liftM2 (,)
(normalG [e|otherwise|])
( varE errorFun
`appE` litE (stringL $ show tName)
`appE` listE (map ( litE
. stringL
. constructorTagModifier opts
. nameBase
. constructorName
) cons
)
`appE` ([|T.unpack|] `appE` varE conKey)
)
]
)
[]
]
parseNullaryMatches :: Name -> Name -> [Q Match]
parseNullaryMatches tName conName =
[ do arr <- newName "arr"
match (conP 'Array [varP arr])
(guardedB
[ liftM2 (,) (normalG $ [|V.null|] `appE` varE arr)
([|pure|] `appE` conE conName)
, liftM2 (,) (normalG [|otherwise|])
(parseTypeMismatch tName conName
(litE $ stringL "an empty Array")
(infixApp (litE $ stringL "Array of length ")
[|(++)|]
([|show . V.length|] `appE` varE arr)
)
)
]
)
[]
, matchFailed tName conName "Array"
]
parseUnaryMatches :: JSONClass -> TyVarMap -> Type -> Name -> [Q Match]
parseUnaryMatches jc tvMap argTy conName =
[ do arg <- newName "arg"
match (varP arg)
( normalB $ infixApp (conE conName)
[|(<$>)|]
(dispatchParseJSON jc conName tvMap argTy
`appE` varE arg)
)
[]
]
parseRecord :: JSONClass
-> TyVarMap
-> [Type]
-> Options
-> Name
-> Name
-> [Name]
-> Name
-> ExpQ
parseRecord jc tvMap argTys opts tName conName fields obj =
foldl' (\a b -> infixApp a [|(<*>)|] b)
(infixApp (conE conName) [|(<$>)|] x)
xs
where
x:xs = [ [|lookupField|]
`appE` dispatchParseJSON jc conName tvMap argTy
`appE` litE (stringL $ show tName)
`appE` litE (stringL $ constructorTagModifier opts $ nameBase conName)
`appE` varE obj
`appE` ( [|T.pack|] `appE` stringE (fieldLabel opts field)
)
| (field, argTy) <- zip fields argTys
]
getValField :: Name -> String -> [MatchQ] -> Q Exp
getValField obj valFieldName matches = do
val <- newName "val"
doE [ bindS (varP val) $ infixApp (varE obj)
[|(.:)|]
([|T.pack|] `appE`
litE (stringL valFieldName))
, noBindS $ caseE (varE val) matches
]
matchCases :: Either (String, Name) Name -> [MatchQ] -> Q Exp
matchCases (Left (valFieldName, obj)) = getValField obj valFieldName
matchCases (Right valName) = caseE (varE valName)
parseArgs :: JSONClass
-> TyVarMap
-> Name
-> Options
-> ConstructorInfo
-> Either (String, Name) Name
-> Q Exp
parseArgs _ _ _ _
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = [] }
(Left _) =
[|pure|] `appE` conE conName
parseArgs _ _ tName _
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = [] }
(Right valName) =
caseE (varE valName) $ parseNullaryMatches tName conName
parseArgs jc tvMap _ _
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = [argTy] }
contents = do
argTy' <- resolveTypeSynonyms argTy
matchCases contents $ parseUnaryMatches jc tvMap argTy' conName
parseArgs jc tvMap tName _
ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = argTys }
contents = do
argTys' <- mapM resolveTypeSynonyms argTys
let len = genericLength argTys'
matchCases contents $ parseProduct jc tvMap argTys' tName conName len
parseArgs jc tvMap tName opts
ConstructorInfo { constructorName = conName
, constructorVariant = RecordConstructor fields
, constructorFields = argTys }
(Left (_, obj)) = do
argTys' <- mapM resolveTypeSynonyms argTys
parseRecord jc tvMap argTys' opts tName conName fields obj
parseArgs jc tvMap tName opts
info@ConstructorInfo { constructorName = conName
, constructorVariant = RecordConstructor fields
, constructorFields = argTys }
(Right valName) =
case (unwrapUnaryRecords opts,argTys) of
(True,[_])-> parseArgs jc tvMap tName opts
(info{constructorVariant = NormalConstructor})
(Right valName)
_ -> do
obj <- newName "recObj"
argTys' <- mapM resolveTypeSynonyms argTys
caseE (varE valName)
[ match (conP 'Object [varP obj]) (normalB $
parseRecord jc tvMap argTys' opts tName conName fields obj) []
, matchFailed tName conName "Object"
]
parseArgs jc tvMap tName _
ConstructorInfo { constructorName = conName
, constructorVariant = InfixConstructor
, constructorFields = argTys }
contents = do
argTys' <- mapM resolveTypeSynonyms argTys
matchCases contents $ parseProduct jc tvMap argTys' tName conName 2
parseProduct :: JSONClass
-> TyVarMap
-> [Type]
-> Name
-> Name
-> Integer
-> [Q Match]
parseProduct jc tvMap argTys tName conName numArgs =
[ do arr <- newName "arr"
let x:xs = [ dispatchParseJSON jc conName tvMap argTy
`appE`
infixApp (varE arr)
[|V.unsafeIndex|]
(litE $ integerL ix)
| (argTy, ix) <- zip argTys [0 .. numArgs 1]
]
match (conP 'Array [varP arr])
(normalB $ condE ( infixApp ([|V.length|] `appE` varE arr)
[|(==)|]
(litE $ integerL numArgs)
)
( foldl' (\a b -> infixApp a [|(<*>)|] b)
(infixApp (conE conName) [|(<$>)|] x)
xs
)
( parseTypeMismatch tName conName
(litE $ stringL $ "Array of length " ++ show numArgs)
( infixApp (litE $ stringL "Array of length ")
[|(++)|]
([|show . V.length|] `appE` varE arr)
)
)
)
[]
, matchFailed tName conName "Array"
]
matchFailed :: Name -> Name -> String -> MatchQ
matchFailed tName conName expected = do
other <- newName "other"
match (varP other)
( normalB $ parseTypeMismatch tName conName
(litE $ stringL expected)
([|valueConName|] `appE` varE other)
)
[]
parseTypeMismatch :: Name -> Name -> ExpQ -> ExpQ -> ExpQ
parseTypeMismatch tName conName expected actual =
foldl appE
[|parseTypeMismatch'|]
[ litE $ stringL $ nameBase conName
, litE $ stringL $ show tName
, expected
, actual
]
class LookupField a where
lookupField :: (Value -> Parser a) -> String -> String
-> Object -> T.Text -> Parser a
instance OVERLAPPABLE_ LookupField a where
lookupField = lookupFieldWith
instance INCOHERENT_ LookupField (Maybe a) where
lookupField pj _ _ = parseOptionalFieldWith pj
instance INCOHERENT_ LookupField (Semigroup.Option a) where
lookupField pj tName rec obj key =
fmap Semigroup.Option
(lookupField (fmap Semigroup.getOption . pj) tName rec obj key)
lookupFieldWith :: (Value -> Parser a) -> String -> String
-> Object -> T.Text -> Parser a
lookupFieldWith pj tName rec obj key =
case H.lookup key obj of
Nothing -> unknownFieldFail tName rec (T.unpack key)
Just v -> pj v <?> Key key
unknownFieldFail :: String -> String -> String -> Parser fail
unknownFieldFail tName rec key =
fail $ printf "When parsing the record %s of type %s the key %s was not present."
rec tName key
noArrayFail :: String -> String -> Parser fail
noArrayFail t o = fail $ printf "When parsing %s expected Array but got %s." t o
noObjectFail :: String -> String -> Parser fail
noObjectFail t o = fail $ printf "When parsing %s expected Object but got %s." t o
firstElemNoStringFail :: String -> String -> Parser fail
firstElemNoStringFail t o = fail $ printf "When parsing %s expected an Array of 2 elements where the first element is a String but got %s at the first element." t o
wrongPairCountFail :: String -> String -> Parser fail
wrongPairCountFail t n =
fail $ printf "When parsing %s expected an Object with a single tag/contents pair but got %s pairs."
t n
noStringFail :: String -> String -> Parser fail
noStringFail t o = fail $ printf "When parsing %s expected String but got %s." t o
noMatchFail :: String -> String -> Parser fail
noMatchFail t o =
fail $ printf "When parsing %s expected a String with the tag of a constructor but got %s." t o
not2ElemArray :: String -> Int -> Parser fail
not2ElemArray t i = fail $ printf "When parsing %s expected an Array of 2 elements but got %i elements" t i
conNotFoundFail2ElemArray :: String -> [String] -> String -> Parser fail
conNotFoundFail2ElemArray t cs o =
fail $ printf "When parsing %s expected a 2-element Array with a tag and contents element where the tag is one of [%s], but got %s."
t (intercalate ", " cs) o
conNotFoundFailObjectSingleField :: String -> [String] -> String -> Parser fail
conNotFoundFailObjectSingleField t cs o =
fail $ printf "When parsing %s expected an Object with a single tag/contents pair where the tag is one of [%s], but got %s."
t (intercalate ", " cs) o
conNotFoundFailTaggedObject :: String -> [String] -> String -> Parser fail
conNotFoundFailTaggedObject t cs o =
fail $ printf "When parsing %s expected an Object with a tag field where the value is one of [%s], but got %s."
t (intercalate ", " cs) o
parseTypeMismatch' :: String -> String -> String -> String -> Parser fail
parseTypeMismatch' conName tName expected actual =
fail $ printf "When parsing the constructor %s of type %s expected %s but got %s."
conName tName expected actual
deriveJSONBoth :: (Options -> Name -> Q [Dec])
-> (Options -> Name -> Q [Dec])
-> Options
-> Name
-> Q [Dec]
deriveJSONBoth dtj dfj opts name =
liftM2 (++) (dtj opts name) (dfj opts name)
deriveJSONClass :: [(JSONFun, JSONClass -> Name -> Options -> [Type]
-> [ConstructorInfo] -> Q Exp)]
-> JSONClass
-> Options
-> Name
-> Q [Dec]
deriveJSONClass consFuns jc opts name = do
info <- reifyDatatype name
case info of
DatatypeInfo { datatypeContext = ctxt
, datatypeName = parentName
, datatypeVars = vars
, datatypeVariant = variant
, datatypeCons = cons
} -> do
(instanceCxt, instanceType)
<- buildTypeInstance parentName jc ctxt vars variant
(:[]) <$> instanceD (return instanceCxt)
(return instanceType)
(methodDecs parentName vars cons)
where
methodDecs :: Name -> [Type] -> [ConstructorInfo] -> [Q Dec]
methodDecs parentName vars cons = flip map consFuns $ \(jf, jfMaker) ->
funD (jsonFunValName jf (arity jc))
[ clause []
(normalB $ jfMaker jc parentName opts vars cons)
[]
]
mkFunCommon :: (JSONClass -> Name -> Options -> [Type] -> [ConstructorInfo] -> Q Exp)
-> JSONClass
-> Options
-> Name
-> Q Exp
mkFunCommon consFun jc opts name = do
info <- reifyDatatype name
case info of
DatatypeInfo { datatypeContext = ctxt
, datatypeName = parentName
, datatypeVars = vars
, datatypeVariant = variant
, datatypeCons = cons
} -> do
!_ <- buildTypeInstance parentName jc ctxt vars variant
consFun jc parentName opts vars cons
dispatchFunByType :: JSONClass
-> JSONFun
-> Name
-> TyVarMap
-> Bool
-> Type
-> Q Exp
dispatchFunByType _ jf _ tvMap list (VarT tyName) =
varE $ case M.lookup tyName tvMap of
Just (tfjExp, tfjlExp) -> if list then tfjlExp else tfjExp
Nothing -> jsonFunValOrListName list jf Arity0
dispatchFunByType jc jf conName tvMap list (SigT ty _) =
dispatchFunByType jc jf conName tvMap list ty
dispatchFunByType jc jf conName tvMap list (ForallT _ _ ty) =
dispatchFunByType jc jf conName tvMap list ty
dispatchFunByType jc jf conName tvMap list ty = do
let tyCon :: Type
tyArgs :: [Type]
tyCon :| tyArgs = unapplyTy ty
numLastArgs :: Int
numLastArgs = min (arityInt jc) (length tyArgs)
lhsArgs, rhsArgs :: [Type]
(lhsArgs, rhsArgs) = splitAt (length tyArgs numLastArgs) tyArgs
tyVarNames :: [Name]
tyVarNames = M.keys tvMap
itf <- isTyFamily tyCon
if any (`mentionsName` tyVarNames) lhsArgs
|| itf && any (`mentionsName` tyVarNames) tyArgs
then outOfPlaceTyVarError jc conName
else if any (`mentionsName` tyVarNames) rhsArgs
then appsE $ varE (jsonFunValOrListName list jf $ toEnum numLastArgs)
: zipWith (dispatchFunByType jc jf conName tvMap)
(cycle [False,True])
(interleave rhsArgs rhsArgs)
else varE $ jsonFunValOrListName list jf Arity0
dispatchToJSON
:: ToJSONFun -> JSONClass -> Name -> TyVarMap -> Type -> Q Exp
dispatchToJSON target jc n tvMap =
dispatchFunByType jc (targetToJSONFun target) n tvMap False
dispatchParseJSON
:: JSONClass -> Name -> TyVarMap -> Type -> Q Exp
dispatchParseJSON jc n tvMap = dispatchFunByType jc ParseJSON n tvMap False
buildTypeInstance :: Name
-> JSONClass
-> Cxt
-> [Type]
-> DatatypeVariant
-> Q (Cxt, Type)
buildTypeInstance tyConName jc dataCxt varTysOrig variant = do
varTysExp <- mapM resolveTypeSynonyms varTysOrig
let remainingLength :: Int
remainingLength = length varTysOrig arityInt jc
droppedTysExp :: [Type]
droppedTysExp = drop remainingLength varTysExp
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati = map canRealizeKindStar droppedTysExp
when (remainingLength < 0 || elem NotKindStar droppedStarKindStati) $
derivingKindError jc tyConName
let droppedKindVarNames :: [Name]
droppedKindVarNames = catKindVarNames droppedStarKindStati
varTysExpSubst :: [Type]
varTysExpSubst = map (substNamesWithKindStar droppedKindVarNames) varTysExp
remainingTysExpSubst, droppedTysExpSubst :: [Type]
(remainingTysExpSubst, droppedTysExpSubst) =
splitAt remainingLength varTysExpSubst
droppedTyVarNames :: [Name]
droppedTyVarNames = freeVariables droppedTysExpSubst
unless (all hasKindStar droppedTysExpSubst) $
derivingKindError jc tyConName
let preds :: [Maybe Pred]
kvNames :: [[Name]]
kvNames' :: [Name]
(preds, kvNames) = unzip $ map (deriveConstraint jc) remainingTysExpSubst
kvNames' = concat kvNames
remainingTysExpSubst' :: [Type]
remainingTysExpSubst' =
map (substNamesWithKindStar kvNames') remainingTysExpSubst
remainingTysOrigSubst :: [Type]
remainingTysOrigSubst =
map (substNamesWithKindStar (droppedKindVarNames `union` kvNames'))
$ take remainingLength varTysOrig
isDataFamily :: Bool
isDataFamily = case variant of
Datatype -> False
Newtype -> False
DataInstance -> True
NewtypeInstance -> True
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' =
if isDataFamily
then remainingTysOrigSubst
else map unSigT remainingTysOrigSubst
instanceCxt :: Cxt
instanceCxt = catMaybes preds
instanceType :: Type
instanceType = AppT (ConT $ jsonClassName jc)
$ applyTyCon tyConName remainingTysOrigSubst'
when (any (`predMentionsName` droppedTyVarNames) dataCxt) $
datatypeContextError tyConName instanceType
unless (canEtaReduce remainingTysExpSubst' droppedTysExpSubst) $
etaReductionError instanceType
return (instanceCxt, instanceType)
deriveConstraint :: JSONClass -> Type -> (Maybe Pred, [Name])
deriveConstraint jc t
| not (isTyVar t) = (Nothing, [])
| hasKindStar t = (Just (applyCon (jcConstraint Arity0) tName), [])
| otherwise = case hasKindVarChain 1 t of
Just ns | jcArity >= Arity1
-> (Just (applyCon (jcConstraint Arity1) tName), ns)
_ -> case hasKindVarChain 2 t of
Just ns | jcArity == Arity2
-> (Just (applyCon (jcConstraint Arity2) tName), ns)
_ -> (Nothing, [])
where
tName :: Name
tName = varTToName t
jcArity :: Arity
jcArity = arity jc
jcConstraint :: Arity -> Name
jcConstraint = jsonClassName . JSONClass (direction jc)
checkExistentialContext :: JSONClass -> TyVarMap -> Cxt -> Name
-> Q a -> Q a
checkExistentialContext jc tvMap ctxt conName q =
if (any (`predMentionsName` M.keys tvMap) ctxt
|| M.size tvMap < arityInt jc)
&& not (allowExQuant jc)
then existentialContextError conName
else q
type TyVarMap = Map Name (Name, Name)
hasKindStar :: Type -> Bool
hasKindStar VarT{} = True
#if MIN_VERSION_template_haskell(2,8,0)
hasKindStar (SigT _ StarT) = True
#else
hasKindStar (SigT _ StarK) = True
#endif
hasKindStar _ = False
isStarOrVar :: Kind -> Bool
#if MIN_VERSION_template_haskell(2,8,0)
isStarOrVar StarT = True
isStarOrVar VarT{} = True
#else
isStarOrVar StarK = True
#endif
isStarOrVar _ = False
newNameList :: String -> Int -> Q [Name]
newNameList prefix len = mapM newName [prefix ++ show n | n <- [1..len]]
hasKindVarChain :: Int -> Type -> Maybe [Name]
hasKindVarChain kindArrows t =
let uk = uncurryKind (tyKind t)
in if (NE.length uk 1 == kindArrows) && F.all isStarOrVar uk
then Just (concatMap freeVariables uk)
else Nothing
tyKind :: Type -> Kind
tyKind (SigT _ k) = k
tyKind _ = starK
varTToNameMaybe :: Type -> Maybe Name
varTToNameMaybe (VarT n) = Just n
varTToNameMaybe (SigT t _) = varTToNameMaybe t
varTToNameMaybe _ = Nothing
varTToName :: Type -> Name
varTToName = fromMaybe (error "Not a type variable!") . varTToNameMaybe
interleave :: [a] -> [a] -> [a]
interleave (a1:a1s) (a2:a2s) = a1:a2:interleave a1s a2s
interleave _ _ = []
applyTyCon :: Name -> [Type] -> Type
applyTyCon = foldl' AppT . ConT
isTyVar :: Type -> Bool
isTyVar (VarT _) = True
isTyVar (SigT t _) = isTyVar t
isTyVar _ = False
isTyFamily :: Type -> Q Bool
isTyFamily (ConT n) = do
info <- reify n
return $ case info of
#if MIN_VERSION_template_haskell(2,11,0)
FamilyI OpenTypeFamilyD{} _ -> True
#else
FamilyI (FamilyD TypeFam _ _ _) _ -> True
#endif
#if MIN_VERSION_template_haskell(2,9,0)
FamilyI ClosedTypeFamilyD{} _ -> True
#endif
_ -> False
isTyFamily _ = return False
unSigT :: Type -> Type
unSigT (SigT t _) = t
unSigT t = t
allDistinct :: Ord a => [a] -> Bool
allDistinct = allDistinct' Set.empty
where
allDistinct' :: Ord a => Set a -> [a] -> Bool
allDistinct' uniqs (x:xs)
| x `Set.member` uniqs = False
| otherwise = allDistinct' (Set.insert x uniqs) xs
allDistinct' _ _ = True
mentionsName :: Type -> [Name] -> Bool
mentionsName = go
where
go :: Type -> [Name] -> Bool
go (AppT t1 t2) names = go t1 names || go t2 names
go (SigT t _k) names = go t names
#if MIN_VERSION_template_haskell(2,8,0)
|| go _k names
#endif
go (VarT n) names = n `elem` names
go _ _ = False
predMentionsName :: Pred -> [Name] -> Bool
#if MIN_VERSION_template_haskell(2,10,0)
predMentionsName = mentionsName
#else
predMentionsName (ClassP n tys) names = n `elem` names || any (`mentionsName` names) tys
predMentionsName (EqualP t1 t2) names = mentionsName t1 names || mentionsName t2 names
#endif
unapplyTy :: Type -> NonEmpty Type
unapplyTy = NE.reverse . go
where
go :: Type -> NonEmpty Type
go (AppT t1 t2) = t2 <| go t1
go (SigT t _) = go t
go (ForallT _ _ t) = go t
go t = t :| []
uncurryTy :: Type -> (Cxt, NonEmpty Type)
uncurryTy (AppT (AppT ArrowT t1) t2) =
let (ctxt, tys) = uncurryTy t2
in (ctxt, t1 <| tys)
uncurryTy (SigT t _) = uncurryTy t
uncurryTy (ForallT _ ctxt t) =
let (ctxt', tys) = uncurryTy t
in (ctxt ++ ctxt', tys)
uncurryTy t = ([], t :| [])
uncurryKind :: Kind -> NonEmpty Kind
#if MIN_VERSION_template_haskell(2,8,0)
uncurryKind = snd . uncurryTy
#else
uncurryKind (ArrowK k1 k2) = k1 <| uncurryKind k2
uncurryKind k = k :| []
#endif
createKindChain :: Int -> Kind
createKindChain = go starK
where
go :: Kind -> Int -> Kind
go k 0 = k
#if MIN_VERSION_template_haskell(2,8,0)
go k !n = go (AppT (AppT ArrowT StarT) k) (n 1)
#else
go k !n = go (ArrowK StarK k) (n 1)
#endif
conNameExp :: Options -> ConstructorInfo -> Q Exp
conNameExp opts = litE
. stringL
. constructorTagModifier opts
. nameBase
. constructorName
fieldLabel :: Options
-> Name
-> String
fieldLabel opts = fieldLabelModifier opts . nameBase
valueConName :: Value -> String
valueConName (Object _) = "Object"
valueConName (Array _) = "Array"
valueConName (String _) = "String"
valueConName (Number _) = "Number"
valueConName (Bool _) = "Boolean"
valueConName Null = "Null"
applyCon :: Name -> Name -> Pred
applyCon con t =
#if MIN_VERSION_template_haskell(2,10,0)
AppT (ConT con) (VarT t)
#else
ClassP con [VarT t]
#endif
canEtaReduce :: [Type] -> [Type] -> Bool
canEtaReduce remaining dropped =
all isTyVar dropped
&& allDistinct droppedNames
&& not (any (`mentionsName` droppedNames) remaining)
where
droppedNames :: [Name]
droppedNames = map varTToName dropped
applySubstitutionKind :: Map Name Kind -> Type -> Type
#if MIN_VERSION_template_haskell(2,8,0)
applySubstitutionKind = applySubstitution
#else
applySubstitutionKind _ t = t
#endif
substNameWithKind :: Name -> Kind -> Type -> Type
substNameWithKind n k = applySubstitutionKind (M.singleton n k)
substNamesWithKindStar :: [Name] -> Type -> Type
substNamesWithKindStar ns t = foldr' (`substNameWithKind` starK) t ns
derivingKindError :: JSONClass -> Name -> Q a
derivingKindError jc tyConName = fail
. showString "Cannot derive well-kinded instance of form ‘"
. showString className
. showChar ' '
. showParen True
( showString (nameBase tyConName)
. showString " ..."
)
. showString "‘\n\tClass "
. showString className
. showString " expects an argument of kind "
. showString (pprint . createKindChain $ arityInt jc)
$ ""
where
className :: String
className = nameBase $ jsonClassName jc
etaReductionError :: Type -> Q a
etaReductionError instanceType = fail $
"Cannot eta-reduce to an instance of form \n\tinstance (...) => "
++ pprint instanceType
datatypeContextError :: Name -> Type -> Q a
datatypeContextError dataName instanceType = fail
. showString "Can't make a derived instance of ‘"
. showString (pprint instanceType)
. showString "‘:\n\tData type ‘"
. showString (nameBase dataName)
. showString "‘ must not have a class context involving the last type argument(s)"
$ ""
outOfPlaceTyVarError :: JSONClass -> Name -> a
outOfPlaceTyVarError jc conName = error
. showString "Constructor ‘"
. showString (nameBase conName)
. showString "‘ must only use its last "
. shows n
. showString " type variable(s) within the last "
. shows n
. showString " argument(s) of a data type"
$ ""
where
n :: Int
n = arityInt jc
existentialContextError :: Name -> a
existentialContextError conName = error
. showString "Constructor ‘"
. showString (nameBase conName)
. showString "‘ must be truly polymorphic in the last argument(s) of the data type"
$ ""
data Arity = Arity0 | Arity1 | Arity2
deriving (Enum, Eq, Ord)
data Direction = To | From
data JSONFun = ToJSON | ToEncoding | ParseJSON
data ToJSONFun = Value | Encoding
targetToJSONFun :: ToJSONFun -> JSONFun
targetToJSONFun Value = ToJSON
targetToJSONFun Encoding = ToEncoding
data JSONClass = JSONClass { direction :: Direction, arity :: Arity }
toJSONClass, toJSON1Class, toJSON2Class,
fromJSONClass, fromJSON1Class, fromJSON2Class :: JSONClass
toJSONClass = JSONClass To Arity0
toJSON1Class = JSONClass To Arity1
toJSON2Class = JSONClass To Arity2
fromJSONClass = JSONClass From Arity0
fromJSON1Class = JSONClass From Arity1
fromJSON2Class = JSONClass From Arity2
jsonClassName :: JSONClass -> Name
jsonClassName (JSONClass To Arity0) = ''ToJSON
jsonClassName (JSONClass To Arity1) = ''ToJSON1
jsonClassName (JSONClass To Arity2) = ''ToJSON2
jsonClassName (JSONClass From Arity0) = ''FromJSON
jsonClassName (JSONClass From Arity1) = ''FromJSON1
jsonClassName (JSONClass From Arity2) = ''FromJSON2
jsonFunValName :: JSONFun -> Arity -> Name
jsonFunValName ToJSON Arity0 = 'toJSON
jsonFunValName ToJSON Arity1 = 'liftToJSON
jsonFunValName ToJSON Arity2 = 'liftToJSON2
jsonFunValName ToEncoding Arity0 = 'toEncoding
jsonFunValName ToEncoding Arity1 = 'liftToEncoding
jsonFunValName ToEncoding Arity2 = 'liftToEncoding2
jsonFunValName ParseJSON Arity0 = 'parseJSON
jsonFunValName ParseJSON Arity1 = 'liftParseJSON
jsonFunValName ParseJSON Arity2 = 'liftParseJSON2
jsonFunListName :: JSONFun -> Arity -> Name
jsonFunListName ToJSON Arity0 = 'toJSONList
jsonFunListName ToJSON Arity1 = 'liftToJSONList
jsonFunListName ToJSON Arity2 = 'liftToJSONList2
jsonFunListName ToEncoding Arity0 = 'toEncodingList
jsonFunListName ToEncoding Arity1 = 'liftToEncodingList
jsonFunListName ToEncoding Arity2 = 'liftToEncodingList2
jsonFunListName ParseJSON Arity0 = 'parseJSONList
jsonFunListName ParseJSON Arity1 = 'liftParseJSONList
jsonFunListName ParseJSON Arity2 = 'liftParseJSONList2
jsonFunValOrListName :: Bool
-> JSONFun -> Arity -> Name
jsonFunValOrListName False = jsonFunValName
jsonFunValOrListName True = jsonFunListName
arityInt :: JSONClass -> Int
arityInt = fromEnum . arity
allowExQuant :: JSONClass -> Bool
allowExQuant (JSONClass To _) = True
allowExQuant _ = False
data StarKindStatus = NotKindStar
| KindStar
| IsKindVar Name
deriving Eq
canRealizeKindStar :: Type -> StarKindStatus
canRealizeKindStar t = case t of
_ | hasKindStar t -> KindStar
#if MIN_VERSION_template_haskell(2,8,0)
SigT _ (VarT k) -> IsKindVar k
#endif
_ -> NotKindStar
starKindStatusToName :: StarKindStatus -> Maybe Name
starKindStatusToName (IsKindVar n) = Just n
starKindStatusToName _ = Nothing
catKindVarNames :: [StarKindStatus] -> [Name]
catKindVarNames = mapMaybe starKindStatusToName