Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data Compression Source #
Instances
Eq Compression Source # | |
Defined in Darcs.Repository.Flags (==) :: Compression -> Compression -> Bool # (/=) :: Compression -> Compression -> Bool # | |
Show Compression Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # | |
YesNo Compression Source # | |
Defined in Darcs.UI.Options.All yes :: Compression -> Bool Source # no :: Compression -> Bool Source # |
data RemoteDarcs Source #
Instances
Eq RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags (==) :: RemoteDarcs -> RemoteDarcs -> Bool # (/=) :: RemoteDarcs -> RemoteDarcs -> Bool # | |
Show RemoteDarcs Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> RemoteDarcs -> ShowS # show :: RemoteDarcs -> String # showList :: [RemoteDarcs] -> ShowS # |
remoteDarcs :: RemoteDarcs -> String Source #
data UpdatePending Source #
Instances
Eq UpdatePending Source # | |
Defined in Darcs.Repository.Flags (==) :: UpdatePending -> UpdatePending -> Bool # (/=) :: UpdatePending -> UpdatePending -> Bool # | |
Show UpdatePending Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> UpdatePending -> ShowS # show :: UpdatePending -> String # showList :: [UpdatePending] -> ShowS # |
data LookForAdds Source #
Instances
Eq LookForAdds Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForAdds -> LookForAdds -> Bool # (/=) :: LookForAdds -> LookForAdds -> Bool # | |
Show LookForAdds Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForAdds -> ShowS # show :: LookForAdds -> String # showList :: [LookForAdds] -> ShowS # | |
YesNo LookForAdds Source # | |
Defined in Darcs.UI.Options.All yes :: LookForAdds -> Bool Source # no :: LookForAdds -> Bool Source # |
data LookForReplaces Source #
Instances
Eq LookForReplaces Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForReplaces -> LookForReplaces -> Bool # (/=) :: LookForReplaces -> LookForReplaces -> Bool # | |
Show LookForReplaces Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForReplaces -> ShowS # show :: LookForReplaces -> String # showList :: [LookForReplaces] -> ShowS # | |
YesNo LookForReplaces Source # | |
Defined in Darcs.UI.Options.All yes :: LookForReplaces -> Bool Source # no :: LookForReplaces -> Bool Source # |
data DiffAlgorithm Source #
Instances
Eq DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff (==) :: DiffAlgorithm -> DiffAlgorithm -> Bool # (/=) :: DiffAlgorithm -> DiffAlgorithm -> Bool # | |
Show DiffAlgorithm Source # | |
Defined in Darcs.Util.Diff showsPrec :: Int -> DiffAlgorithm -> ShowS # show :: DiffAlgorithm -> String # showList :: [DiffAlgorithm] -> ShowS # |
data LookForMoves Source #
Instances
Eq LookForMoves Source # | |
Defined in Darcs.Repository.Flags (==) :: LookForMoves -> LookForMoves -> Bool # (/=) :: LookForMoves -> LookForMoves -> Bool # | |
Show LookForMoves Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LookForMoves -> ShowS # show :: LookForMoves -> String # showList :: [LookForMoves] -> ShowS # | |
YesNo LookForMoves Source # | |
Defined in Darcs.UI.Options.All yes :: LookForMoves -> Bool Source # no :: LookForMoves -> Bool Source # |
data SetScriptsExecutable Source #
Instances
Eq SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags (==) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # (/=) :: SetScriptsExecutable -> SetScriptsExecutable -> Bool # | |
Show SetScriptsExecutable Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> SetScriptsExecutable -> ShowS # show :: SetScriptsExecutable -> String # showList :: [SetScriptsExecutable] -> ShowS # | |
YesNo SetScriptsExecutable Source # | |
Defined in Darcs.UI.Options.All yes :: SetScriptsExecutable -> Bool Source # no :: SetScriptsExecutable -> Bool Source # |
data LeaveTestDir Source #
Instances
Eq LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags (==) :: LeaveTestDir -> LeaveTestDir -> Bool # (/=) :: LeaveTestDir -> LeaveTestDir -> Bool # | |
Show LeaveTestDir Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> LeaveTestDir -> ShowS # show :: LeaveTestDir -> String # showList :: [LeaveTestDir] -> ShowS # | |
YesNo LeaveTestDir Source # | |
Defined in Darcs.UI.Options.All yes :: LeaveTestDir -> Bool Source # no :: LeaveTestDir -> Bool Source # |
data RemoteRepos Source #
Instances
Eq RemoteRepos Source # | |
Defined in Darcs.Repository.Flags (==) :: RemoteRepos -> RemoteRepos -> Bool # (/=) :: RemoteRepos -> RemoteRepos -> Bool # | |
Show RemoteRepos Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> RemoteRepos -> ShowS # show :: RemoteRepos -> String # showList :: [RemoteRepos] -> ShowS # |
data SetDefault Source #
Instances
Eq SetDefault Source # | |
Defined in Darcs.Repository.Flags (==) :: SetDefault -> SetDefault -> Bool # (/=) :: SetDefault -> SetDefault -> Bool # | |
Show SetDefault Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> SetDefault -> ShowS # show :: SetDefault -> String # showList :: [SetDefault] -> ShowS # |
data InheritDefault Source #
Instances
Eq InheritDefault Source # | |
Defined in Darcs.Repository.Flags (==) :: InheritDefault -> InheritDefault -> Bool # (/=) :: InheritDefault -> InheritDefault -> Bool # | |
Show InheritDefault Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> InheritDefault -> ShowS # show :: InheritDefault -> String # showList :: [InheritDefault] -> ShowS # | |
YesNo InheritDefault Source # | |
Defined in Darcs.UI.Options.All yes :: InheritDefault -> Bool Source # no :: InheritDefault -> Bool Source # |
ScanKnown | Just files already known to darcs |
ScanAll | All files, i.e. look for new ones |
ScanBoring | All files, even boring ones |
LazyClone | Just copy pristine and inventories |
NormalClone | First do a lazy clone then copy everything |
CompleteClone | Same as Normal but omit telling user they can interrumpt |
data AllowConflicts Source #
Instances
Eq AllowConflicts Source # | |
Defined in Darcs.Repository.Flags (==) :: AllowConflicts -> AllowConflicts -> Bool # (/=) :: AllowConflicts -> AllowConflicts -> Bool # | |
Show AllowConflicts Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> AllowConflicts -> ShowS # show :: AllowConflicts -> String # showList :: [AllowConflicts] -> ShowS # |
data ExternalMerge Source #
Instances
Eq ExternalMerge Source # | |
Defined in Darcs.Repository.Flags (==) :: ExternalMerge -> ExternalMerge -> Bool # (/=) :: ExternalMerge -> ExternalMerge -> Bool # | |
Show ExternalMerge Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> ExternalMerge -> ShowS # show :: ExternalMerge -> String # showList :: [ExternalMerge] -> ShowS # |
data WantGuiPause Source #
Instances
Eq WantGuiPause Source # | |
Defined in Darcs.Repository.Flags (==) :: WantGuiPause -> WantGuiPause -> Bool # (/=) :: WantGuiPause -> WantGuiPause -> Bool # | |
Show WantGuiPause Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WantGuiPause -> ShowS # show :: WantGuiPause -> String # showList :: [WantGuiPause] -> ShowS # | |
YesNo WantGuiPause Source # | |
Defined in Darcs.UI.Options.All yes :: WantGuiPause -> Bool Source # no :: WantGuiPause -> Bool Source # |
data WithPatchIndex Source #
Instances
Eq WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags (==) :: WithPatchIndex -> WithPatchIndex -> Bool # (/=) :: WithPatchIndex -> WithPatchIndex -> Bool # | |
Show WithPatchIndex Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WithPatchIndex -> ShowS # show :: WithPatchIndex -> String # showList :: [WithPatchIndex] -> ShowS # | |
YesNo WithPatchIndex Source # | |
Defined in Darcs.UI.Options.All yes :: WithPatchIndex -> Bool Source # no :: WithPatchIndex -> Bool Source # |
data WithWorkingDir Source #
Instances
Eq WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags (==) :: WithWorkingDir -> WithWorkingDir -> Bool # (/=) :: WithWorkingDir -> WithWorkingDir -> Bool # | |
Show WithWorkingDir Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> WithWorkingDir -> ShowS # show :: WithWorkingDir -> String # showList :: [WithWorkingDir] -> ShowS # | |
YesNo WithWorkingDir Source # | |
Defined in Darcs.UI.Options.All yes :: WithWorkingDir -> Bool Source # no :: WithWorkingDir -> Bool Source # |
data ForgetParent Source #
Instances
Eq ForgetParent Source # | |
Defined in Darcs.Repository.Flags (==) :: ForgetParent -> ForgetParent -> Bool # (/=) :: ForgetParent -> ForgetParent -> Bool # | |
Show ForgetParent Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> ForgetParent -> ShowS # show :: ForgetParent -> String # showList :: [ForgetParent] -> ShowS # |
data PatchFormat Source #
Instances
Eq PatchFormat Source # | |
Defined in Darcs.Repository.Flags (==) :: PatchFormat -> PatchFormat -> Bool # (/=) :: PatchFormat -> PatchFormat -> Bool # | |
Show PatchFormat Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> PatchFormat -> ShowS # show :: PatchFormat -> String # showList :: [PatchFormat] -> ShowS # |
data IncludeBoring Source #
Instances
Eq IncludeBoring Source # | |
Defined in Darcs.Repository.Flags (==) :: IncludeBoring -> IncludeBoring -> Bool # (/=) :: IncludeBoring -> IncludeBoring -> Bool # | |
Show IncludeBoring Source # | |
Defined in Darcs.Repository.Flags showsPrec :: Int -> IncludeBoring -> ShowS # show :: IncludeBoring -> String # showList :: [IncludeBoring] -> ShowS # | |
YesNo IncludeBoring Source # | |
Defined in Darcs.UI.Options.All yes :: IncludeBoring -> Bool Source # no :: IncludeBoring -> Bool Source # |
data HooksConfig Source #
HooksConfig | |
|
data HookConfig Source #