You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
Crucible has many datatypes and classes that have many type variables. These variables are infrequently documented, and there is a wide variety in when their kinds are provided in a kind signature. When they are, these kind signatures are generally inline, rather than standalone. Furthermore, I suspect that some of these type variables may be too polymorphic, as they occur in modules with PolyKinds, which will allow GHC to infer polymorphic kinds when possible.
For a demonstration of all of the above issues, consider the ExecutionTree module:
rg '(^data|PolyKinds)' crucible/src/Lang/Crucible/Simulator/ExecutionTree.hs
30:{-# LANGUAGE PolyKinds #-}
178:data GlobalPair sym (v :: Type) =
225:data AbortedResult sym ext where
251:data SomeFrame (f :: fk -> argk -> Type) = forall l a . SomeFrame !(f l a)
292:data PartialResult sym ext (v :: Type)
321:data ResolvedCall p sym ext ret where
344:data ExecResult p sym ext (r :: Type)
398:data ExecState p sym ext (rtp :: Type)
540:data RunningStateInfo blocks args
557:data ResolvedJump sym blocks
567:data ControlResumption p sym ext rtp f where
606:data PausedFrame p sym ext rtp f
622:data VFFOtherPath p sym ext ret f args
655:data ValueFromFrame p sym ext (ret :: Type) (f :: Type)
718:data PendingPartialMerges =
743:data ValueFromValue p sym ext (ret :: Type) (top_return :: CrucibleType)
870:data ReturnHandler (ret :: CrucibleType) p sym ext root f args where
908:data ActiveTree p sym ext root (f :: Type) args
963:data Override p sym ext (args :: Ctx CrucibleType) ret
971:data FnState p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType)
990:data ExtensionImpl p sym ext
1024:data SimContext (personality :: Type) (sym :: Type) (ext :: Type)
1126:data SimState p sym ext rtp f (args :: Maybe (Ctx.Ctx CrucibleType))
1132:data SomeSimState p sym ext rtp =
Providing standalone kind signatures could solve all of these issues and many more besides, and be a significant boon to readability.
While adding such kind signatures, we should consider adding Haddocks that document the various type parameters, as can be seen on OverrideSim and ValueFromValue.
GHC 9.8 and above have a -Wmissing-poly-kind-signatures flag that could be helpful in tracking down especially high-priority instances.
Note that SAKS were added in GHC 8.10. This is outside of our support window, so shouldn't be a problem.
The text was updated successfully, but these errors were encountered:
Ah, one disadvantage: SAKS are not rendered by Haddock (that issue is on an archived repository, but AFAICT applies to at least Haddock 2.30), whereas inline kind signatures are rendered.
Perhaps we could even consider just explictly calling out the kinds of variables in their Haddocks...? It would be an unfortunate duplication, but this is an unfortunate limitation for Haddock...
Personally, I'd argue that the benefits of adding standalone kind signatures would outweigh their drawbacks.
It would also be nice to fix haskell/haddock#1178, of course. I have been meaning to look into this myself, but I haven't found the time to do so. This would be a fun project for someone who is looking to get involved with Haddock development—I'm happy to advise to the extent that I can.
Crucible has many datatypes and classes that have many type variables. These variables are infrequently documented, and there is a wide variety in when their kinds are provided in a kind signature. When they are, these kind signatures are generally inline, rather than standalone. Furthermore, I suspect that some of these type variables may be too polymorphic, as they occur in modules with
PolyKinds
, which will allow GHC to infer polymorphic kinds when possible.For a demonstration of all of the above issues, consider the
ExecutionTree
module:Providing standalone kind signatures could solve all of these issues and many more besides, and be a significant boon to readability.
While adding such kind signatures, we should consider adding Haddocks that document the various type parameters, as can be seen on
OverrideSim
andValueFromValue
.GHC 9.8 and above have a
-Wmissing-poly-kind-signatures
flag that could be helpful in tracking down especially high-priority instances.Note that SAKS were added in GHC 8.10. This is outside of our support window, so shouldn't be a problem.
The text was updated successfully, but these errors were encountered: