module Darcs.Patch.RepoType
( RepoType(..), IsRepoType(..), SRepoType(..)
, RebaseType(..), IsRebaseType, RebaseTypeOf, SRebaseType(..)
) where
data RebaseType = IsRebase | NoRebase
data SRebaseType (rebaseType :: RebaseType) where
SIsRebase :: SRebaseType 'IsRebase
SNoRebase :: SRebaseType 'NoRebase
class IsRebaseType (rebaseType :: RebaseType) where
singletonRebaseType :: SRebaseType rebaseType
instance IsRebaseType 'IsRebase where
singletonRebaseType :: SRebaseType 'IsRebase
singletonRebaseType = SRebaseType 'IsRebase
SIsRebase
instance IsRebaseType 'NoRebase where
singletonRebaseType :: SRebaseType 'NoRebase
singletonRebaseType = SRebaseType 'NoRebase
SNoRebase
data RepoType = RepoType { RepoType -> RebaseType
rebaseType :: RebaseType }
type family RebaseTypeOf (rt :: RepoType) :: RebaseType
type instance RebaseTypeOf ('RepoType rebaseType) = rebaseType
class IsRepoType (rt :: RepoType) where
singletonRepoType :: SRepoType rt
data SRepoType (repoType :: RepoType) where
SRepoType :: SRebaseType rebaseType -> SRepoType ('RepoType rebaseType)
instance IsRebaseType rebaseType => IsRepoType ('RepoType rebaseType) where
singletonRepoType :: SRepoType ('RepoType rebaseType)
singletonRepoType = SRebaseType rebaseType -> SRepoType ('RepoType rebaseType)
forall (rebaseType :: RebaseType).
SRebaseType rebaseType -> SRepoType ('RepoType rebaseType)
SRepoType SRebaseType rebaseType
forall (rebaseType :: RebaseType).
IsRebaseType rebaseType =>
SRebaseType rebaseType
singletonRebaseType