Split git repo source handler into sane small functions
This commit is contained in:
parent
2c73158c47
commit
c8c323f695
5 changed files with 149 additions and 115 deletions
|
@ -14,7 +14,7 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Darcs.Local
|
module Darcs.Local
|
||||||
( initRepo
|
( createRepo
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
@ -48,13 +48,13 @@ initialRepoTree repo =
|
||||||
-}
|
-}
|
||||||
|
|
||||||
-- | initialize a new bare repository at a specific location.
|
-- | initialize a new bare repository at a specific location.
|
||||||
initRepo
|
createRepo
|
||||||
:: FilePath
|
:: FilePath
|
||||||
-- ^ Parent directory which already exists
|
-- ^ Parent directory which already exists
|
||||||
-> String
|
-> String
|
||||||
-- ^ Name of new repo, i.e. new directory to create under the parent
|
-- ^ Name of new repo, i.e. new directory to create under the parent
|
||||||
-> IO ()
|
-> IO ()
|
||||||
initRepo parent name = do
|
createRepo parent name = do
|
||||||
let path = parent </> name
|
let path = parent </> name
|
||||||
createDirectory path
|
createDirectory path
|
||||||
let settings = proc "darcs" ["init", "--no-working-dir", path]
|
let settings = proc "darcs" ["init", "--no-working-dir", path]
|
||||||
|
|
|
@ -14,44 +14,45 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Data.Git.Local
|
module Data.Git.Local
|
||||||
( initRepo
|
( -- * Initialize repo
|
||||||
|
createRepo
|
||||||
|
-- * View repo content
|
||||||
|
, EntObjType (..)
|
||||||
|
, TreeRows
|
||||||
|
, PathView (..)
|
||||||
|
, viewPath
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
|
import Data.Byteable (toBytes)
|
||||||
|
import Data.Git
|
||||||
|
import Data.Git.Harder
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Data.Text.Encoding (decodeUtf8With)
|
||||||
|
import Data.Text.Encoding.Error (lenientDecode)
|
||||||
import System.Directory.Tree
|
import System.Directory.Tree
|
||||||
|
|
||||||
import qualified Data.ByteString as B (ByteString, writeFile)
|
import qualified Data.ByteString as B (ByteString, writeFile)
|
||||||
|
import qualified Data.ByteString.Lazy as BL (ByteString)
|
||||||
initialConfig :: B.ByteString
|
|
||||||
initialConfig =
|
|
||||||
"[core]\n\
|
|
||||||
\ repositoryformatversion = 0\n\
|
|
||||||
\ filemode = true\n\
|
|
||||||
\ bare = true"
|
|
||||||
|
|
||||||
initialDescription :: B.ByteString
|
|
||||||
initialDescription =
|
|
||||||
"Unnamed repository; edit this file to name the repository."
|
|
||||||
|
|
||||||
initialHead :: B.ByteString
|
|
||||||
initialHead = "ref: refs/heads/master"
|
|
||||||
|
|
||||||
initialExclude :: B.ByteString
|
|
||||||
initialExclude = ""
|
|
||||||
|
|
||||||
initialRepoTree :: FileName -> DirTree B.ByteString
|
initialRepoTree :: FileName -> DirTree B.ByteString
|
||||||
initialRepoTree repo =
|
initialRepoTree repo =
|
||||||
Dir repo
|
Dir repo
|
||||||
[ Dir "branches" []
|
[ Dir "branches" []
|
||||||
, File "config" initialConfig
|
, File "config"
|
||||||
, File "description" initialDescription
|
"[core]\n\
|
||||||
, File "HEAD" initialHead
|
\ repositoryformatversion = 0\n\
|
||||||
|
\ filemode = true\n\
|
||||||
|
\ bare = true"
|
||||||
|
, File "description"
|
||||||
|
"Unnamed repository; edit this file to name the repository."
|
||||||
|
, File "HEAD" "ref: refs/heads/master"
|
||||||
, Dir "hooks" []
|
, Dir "hooks" []
|
||||||
, Dir "info"
|
, Dir "info"
|
||||||
[ File "exclude" initialExclude
|
[ File "exclude" ""
|
||||||
]
|
]
|
||||||
, Dir "objects"
|
, Dir "objects"
|
||||||
[ Dir "info" []
|
[ Dir "info" []
|
||||||
|
@ -68,14 +69,41 @@ initialRepoTree repo =
|
||||||
-- Currently in the @hit@ package, i.e. version 0.6.3, the initRepo function
|
-- Currently in the @hit@ package, i.e. version 0.6.3, the initRepo function
|
||||||
-- creates a directory which the git executable doesn't recognize as a git
|
-- creates a directory which the git executable doesn't recognize as a git
|
||||||
-- repository. The version here creates a properly initialized repo.
|
-- repository. The version here creates a properly initialized repo.
|
||||||
initRepo
|
createRepo
|
||||||
:: FilePath
|
:: FilePath
|
||||||
-- ^ Parent directory which already exists
|
-- ^ Parent directory which already exists
|
||||||
-> String
|
-> String
|
||||||
-- ^ Name of new repo, i.e. new directory to create under the parent
|
-- ^ Name of new repo, i.e. new directory to create under the parent
|
||||||
-> IO ()
|
-> IO ()
|
||||||
initRepo path name = do
|
createRepo path name = do
|
||||||
let tree = path :/ initialRepoTree name
|
let tree = path :/ initialRepoTree name
|
||||||
result <- writeDirectoryWith B.writeFile tree
|
result <- writeDirectoryWith B.writeFile tree
|
||||||
let errs = failures $ dirTree result
|
let errs = failures $ dirTree result
|
||||||
when (not . null $ errs) $ error $ show errs
|
when (not . null $ errs) $ error $ show errs
|
||||||
|
|
||||||
|
data EntObjType = EntObjBlob | EntObjTree
|
||||||
|
|
||||||
|
type TreeRows = [(ModePerm, ObjId, Text, EntObjType)]
|
||||||
|
|
||||||
|
data PathView
|
||||||
|
= RootView TreeRows
|
||||||
|
| TreeView Text ObjId TreeRows
|
||||||
|
| BlobView Text ObjId BL.ByteString
|
||||||
|
|
||||||
|
viewPath :: Git -> Tree -> EntPath -> IO PathView
|
||||||
|
viewPath git root path = do
|
||||||
|
let toEnt False = EntObjBlob
|
||||||
|
toEnt True = EntObjTree
|
||||||
|
toText = decodeUtf8With lenientDecode . toBytes
|
||||||
|
adapt (perm, oid, name, isTree) =
|
||||||
|
(perm, oid, toText name, toEnt isTree)
|
||||||
|
mkRows t = map adapt <$> viewTree git t
|
||||||
|
mno <- resolveTreePath git root path
|
||||||
|
case mno of
|
||||||
|
Nothing -> RootView <$> mkRows root
|
||||||
|
Just (name, oid) -> do
|
||||||
|
let nameT = toText name
|
||||||
|
target <- getEntryObject_ git oid
|
||||||
|
case target of
|
||||||
|
Left blob -> return $ BlobView nameT oid (blobGetContent blob)
|
||||||
|
Right tree -> TreeView nameT oid <$> mkRows tree
|
||||||
|
|
|
@ -32,20 +32,18 @@ where
|
||||||
-- [x] write the git and mkdir parts that actually create the repo
|
-- [x] write the git and mkdir parts that actually create the repo
|
||||||
-- [x] make repo view that shows a table of commits
|
-- [x] make repo view that shows a table of commits
|
||||||
|
|
||||||
import ClassyPrelude.Conduit hiding (last, toStrict, unpack)
|
import ClassyPrelude.Conduit hiding (last, unpack)
|
||||||
import Yesod hiding (Header, parseTime, (==.))
|
import Yesod hiding (Header, parseTime, (==.))
|
||||||
import Yesod.Auth
|
import Yesod.Auth
|
||||||
|
|
||||||
import Prelude (init, last, tail)
|
import Prelude (init, last, tail)
|
||||||
|
|
||||||
import Data.Byteable (toBytes)
|
|
||||||
import Data.ByteString.Lazy (toStrict)
|
|
||||||
import Data.Git.Graph
|
import Data.Git.Graph
|
||||||
import Data.Git.Harder
|
import Data.Git.Harder
|
||||||
import Data.Git.Named (RefName (..))
|
import Data.Git.Named (RefName (..))
|
||||||
import Data.Git.Ref (toHex)
|
import Data.Git.Ref (toHex)
|
||||||
import Data.Git.Repository
|
import Data.Git.Repository
|
||||||
import Data.Git.Storage (withRepo, getObject_)
|
import Data.Git.Storage (withRepo)
|
||||||
import Data.Git.Storage.Object (Object (..))
|
import Data.Git.Storage.Object (Object (..))
|
||||||
import Data.Git.Types (Blob (..), Commit (..), Person (..), entName)
|
import Data.Git.Types (Blob (..), Commit (..), Person (..), entName)
|
||||||
import Data.Graph.Inductive.Graph (noNodes)
|
import Data.Graph.Inductive.Graph (noNodes)
|
||||||
|
@ -64,6 +62,7 @@ import qualified Data.Set as S (member)
|
||||||
import qualified Data.Text.Lazy.Encoding as L (decodeUtf8With)
|
import qualified Data.Text.Lazy.Encoding as L (decodeUtf8With)
|
||||||
|
|
||||||
import Data.ByteString.Char8.Local (takeLine)
|
import Data.ByteString.Char8.Local (takeLine)
|
||||||
|
import Data.Git.Local
|
||||||
import Text.FilePath.Local (breakExt)
|
import Text.FilePath.Local (breakExt)
|
||||||
import Vervis.Form.Repo
|
import Vervis.Form.Repo
|
||||||
import Vervis.Foundation
|
import Vervis.Foundation
|
||||||
|
@ -77,8 +76,9 @@ import Vervis.Render
|
||||||
import Vervis.Settings
|
import Vervis.Settings
|
||||||
import Vervis.Style
|
import Vervis.Style
|
||||||
|
|
||||||
import qualified Darcs.Local as D (initRepo)
|
import qualified Darcs.Local as D (createRepo)
|
||||||
import qualified Data.Git.Local as G (initRepo)
|
import qualified Data.ByteString.Lazy as BL (ByteString)
|
||||||
|
import qualified Data.Git.Local as G (createRepo)
|
||||||
|
|
||||||
getReposR :: Text -> Handler Html
|
getReposR :: Text -> Handler Html
|
||||||
getReposR user = do
|
getReposR user = do
|
||||||
|
@ -105,8 +105,8 @@ postReposR user = do
|
||||||
createDirectoryIfMissing True parent
|
createDirectoryIfMissing True parent
|
||||||
let repoName = unpack $ repoIdent repo
|
let repoName = unpack $ repoIdent repo
|
||||||
case repoVcs repo of
|
case repoVcs repo of
|
||||||
VCSDarcs -> D.initRepo parent repoName
|
VCSDarcs -> D.createRepo parent repoName
|
||||||
VCSGit -> G.initRepo parent repoName
|
VCSGit -> G.createRepo parent repoName
|
||||||
runDB $ insert_ repo
|
runDB $ insert_ repo
|
||||||
setMessage "Repo added."
|
setMessage "Repo added."
|
||||||
redirect $ ReposR user
|
redirect $ ReposR user
|
||||||
|
@ -138,66 +138,64 @@ getRepoR user repo = do
|
||||||
return r
|
return r
|
||||||
getRepoSource repository user repo (repoMainBranch repository) []
|
getRepoSource repository user repo (repoMainBranch repository) []
|
||||||
|
|
||||||
|
data SourceView a
|
||||||
|
= DirectoryView (Maybe Text) TreeRows (Maybe (Text, a))
|
||||||
|
| FileView Text a
|
||||||
|
|
||||||
|
loadSourceView
|
||||||
|
:: Git
|
||||||
|
-> Text
|
||||||
|
-> [Text]
|
||||||
|
-> IO (Set RefName, Set RefName, Maybe (SourceView BL.ByteString))
|
||||||
|
loadSourceView git refT dir = do
|
||||||
|
branches <- branchList git
|
||||||
|
tags <- tagList git
|
||||||
|
let refS = unpack refT
|
||||||
|
refN = RefName refS
|
||||||
|
msv <- if refN `S.member` branches || refN `S.member` tags
|
||||||
|
then do
|
||||||
|
tipOid <- resolveName git refS
|
||||||
|
mtree <- resolveTreeish git $ unObjId tipOid
|
||||||
|
case mtree of
|
||||||
|
Nothing -> return Nothing
|
||||||
|
Just tree -> do
|
||||||
|
let dir' = map (entName . encodeUtf8) dir
|
||||||
|
view <- viewPath git tree dir'
|
||||||
|
Just <$> case view of
|
||||||
|
RootView rows -> do
|
||||||
|
mreadme <- findReadme git rows
|
||||||
|
return $ DirectoryView Nothing rows mreadme
|
||||||
|
TreeView name _ rows -> do
|
||||||
|
mreadme <- findReadme git rows
|
||||||
|
return $ DirectoryView (Just name) rows mreadme
|
||||||
|
BlobView name _ body -> return $ FileView name body
|
||||||
|
else return Nothing
|
||||||
|
return (branches, tags, msv)
|
||||||
|
|
||||||
|
renderSources :: [Text] -> SourceView BL.ByteString -> SourceView Widget
|
||||||
|
renderSources dir (DirectoryView mname rows mreadme) =
|
||||||
|
case mreadme of
|
||||||
|
Nothing -> DirectoryView mname rows Nothing
|
||||||
|
Just (name, body) ->
|
||||||
|
DirectoryView mname rows $ Just (name, renderReadme dir name body)
|
||||||
|
renderSources dir (FileView name body) =
|
||||||
|
let parent = init dir
|
||||||
|
(base, ext) = breakExt name
|
||||||
|
mediaType = chooseMediaType parent base ext () ()
|
||||||
|
in FileView name $ renderSourceBL mediaType body
|
||||||
|
|
||||||
getRepoSource :: Repo -> Text -> Text -> Text -> [Text] -> Handler Html
|
getRepoSource :: Repo -> Text -> Text -> Text -> [Text] -> Handler Html
|
||||||
getRepoSource repository user repo ref dir = do
|
getRepoSource repository user repo ref dir = do
|
||||||
path <- askRepoDir user repo
|
path <- askRepoDir user repo
|
||||||
let toText = decodeUtf8With lenientDecode
|
let toText = decodeUtf8With lenientDecode
|
||||||
toTextL = L.decodeUtf8With lenientDecode
|
toTextL = L.decodeUtf8With lenientDecode
|
||||||
minfo <- liftIO $ withRepo (fromString path) $ \ git -> do
|
(branches, tags, msv) <- liftIO $ withRepo (fromString path) $ \ git ->
|
||||||
branches <- branchList git
|
loadSourceView git ref dir
|
||||||
tags <- tagList git
|
case renderSources dir <$> msv of
|
||||||
let name = unpack ref
|
Nothing -> notFound
|
||||||
name' = RefName name
|
Just sv -> do
|
||||||
if name' `S.member` branches || name' `S.member` tags
|
|
||||||
then do
|
|
||||||
tipOid <- resolveName git name
|
|
||||||
mtree <- resolveTreeish git $ unObjId tipOid
|
|
||||||
case mtree of
|
|
||||||
Nothing -> return Nothing
|
|
||||||
Just tree -> do
|
|
||||||
let dir' = map (entName . encodeUtf8) dir
|
|
||||||
mTargetOid <- resolveTreePath git tree dir'
|
|
||||||
target <- case mTargetOid of
|
|
||||||
Nothing -> return $ Right tree
|
|
||||||
Just oid -> do
|
|
||||||
obj <- getObject_ git (unObjId oid) True
|
|
||||||
case obj of
|
|
||||||
ObjTree t -> return $ Right t
|
|
||||||
ObjBlob b -> return $ Left b
|
|
||||||
_ -> error "expected tree or blob"
|
|
||||||
view <- case target of
|
|
||||||
Left b -> Left <$> return b
|
|
||||||
Right t -> do
|
|
||||||
v <- viewTree git t
|
|
||||||
mreadme <- findReadme git t
|
|
||||||
let r = case mreadme of
|
|
||||||
Nothing -> Nothing
|
|
||||||
Just (t, b) ->
|
|
||||||
Just (t, renderReadme dir t b)
|
|
||||||
return $ Right (v, r)
|
|
||||||
return $ Just (branches, tags, view)
|
|
||||||
else return Nothing
|
|
||||||
case minfo of
|
|
||||||
Nothing -> notFound
|
|
||||||
Just (branches, tags, view) -> do
|
|
||||||
let mkrow (_perm, name, isTree) =
|
|
||||||
( if isTree then "[D]" else "[F]" :: Text
|
|
||||||
, toText $ toBytes name
|
|
||||||
)
|
|
||||||
display <- case view of
|
|
||||||
Left b -> return $ Left $
|
|
||||||
let name = last dir
|
|
||||||
parent = init dir
|
|
||||||
(base, ext) = breakExt name
|
|
||||||
mediaType = chooseMediaType parent base ext () ()
|
|
||||||
in renderSourceBL mediaType (blobGetContent b)
|
|
||||||
Right (v, mr) -> return $ Right (map mkrow v, mr)
|
|
||||||
let parent = if null dir then [] else init dir
|
let parent = if null dir then [] else init dir
|
||||||
dirs = zip parent (tail $ inits parent)
|
dirs = zip parent (tail $ inits parent)
|
||||||
title = case (dir, display) of
|
|
||||||
([], _) -> "Files"
|
|
||||||
(_, Left _) -> last dir
|
|
||||||
(_, Right _) -> last dir <> "/"
|
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle $ toHtml $ intercalate " > " $
|
setTitle $ toHtml $ intercalate " > " $
|
||||||
["Vervis", "People", user, "Repos", repo]
|
["Vervis", "People", user, "Repos", repo]
|
||||||
|
|
|
@ -22,20 +22,19 @@ where
|
||||||
|
|
||||||
import Prelude hiding (takeWhile)
|
import Prelude hiding (takeWhile)
|
||||||
|
|
||||||
import Data.Byteable (toBytes)
|
|
||||||
import Data.ByteString.Lazy (ByteString)
|
import Data.ByteString.Lazy (ByteString)
|
||||||
|
import Data.Git.Harder (ObjId (..))
|
||||||
import Data.Git.Storage (Git, getObject_)
|
import Data.Git.Storage (Git, getObject_)
|
||||||
import Data.Git.Storage.Object (Object (..))
|
import Data.Git.Storage.Object (Object (..))
|
||||||
import Data.Git.Types (Blob (..), Tree (..))
|
import Data.Git.Types (Blob (..), Tree (..))
|
||||||
import Data.Text (Text, toCaseFold, takeWhile, unpack)
|
import Data.Text (Text, toCaseFold, takeWhile, unpack)
|
||||||
import Data.Text.Encoding (decodeUtf8With)
|
|
||||||
import Data.Text.Encoding.Error (strictDecode)
|
|
||||||
import System.FilePath (isExtSeparator)
|
import System.FilePath (isExtSeparator)
|
||||||
|
|
||||||
|
import Data.Git.Local (TreeRows)
|
||||||
|
import Text.FilePath.Local (breakExt)
|
||||||
import Vervis.Foundation (Widget)
|
import Vervis.Foundation (Widget)
|
||||||
import Vervis.MediaType (chooseMediaType)
|
import Vervis.MediaType (chooseMediaType)
|
||||||
import Vervis.Render (renderSourceBL)
|
import Vervis.Render (renderSourceBL)
|
||||||
import Text.FilePath.Local (breakExt)
|
|
||||||
|
|
||||||
-- | Check if the given filename should be considered as README file. Assumes
|
-- | Check if the given filename should be considered as README file. Assumes
|
||||||
-- a flat filename which doesn't contain a directory part.
|
-- a flat filename which doesn't contain a directory part.
|
||||||
|
@ -46,19 +45,18 @@ isReadme file =
|
||||||
|
|
||||||
-- | Find a README file in a directory. Return the filename and the file
|
-- | Find a README file in a directory. Return the filename and the file
|
||||||
-- content.
|
-- content.
|
||||||
findReadme :: Git -> Tree -> IO (Maybe (Text, ByteString))
|
findReadme :: Git -> TreeRows -> IO (Maybe (Text, ByteString))
|
||||||
findReadme git tree = go $ treeGetEnts tree
|
findReadme git rows = go rows
|
||||||
where
|
where
|
||||||
go [] = return Nothing
|
go [] = return Nothing
|
||||||
go ((_perm, name, ref) : es) =
|
go ((_perm, oid, name, ref) : es) =
|
||||||
let nameT = decodeUtf8With strictDecode $ toBytes name
|
if isReadme name
|
||||||
in if isReadme nameT
|
then do
|
||||||
then do
|
obj <- getObject_ git (unObjId oid) True
|
||||||
obj <- getObject_ git ref True
|
case obj of
|
||||||
case obj of
|
ObjBlob b -> return $ Just (name, blobGetContent b)
|
||||||
ObjBlob b -> return $ Just (nameT, blobGetContent b)
|
_ -> go es
|
||||||
_ -> go es
|
else go es
|
||||||
else go es
|
|
||||||
|
|
||||||
-- | Render README content into a widget for inclusion in a page.
|
-- | Render README content into a widget for inclusion in a page.
|
||||||
renderReadme :: [Text] -> Text -> ByteString -> Widget
|
renderReadme :: [Text] -> Text -> ByteString -> Widget
|
||||||
|
|
|
@ -19,34 +19,44 @@ $maybe desc <- repoDesc repository
|
||||||
<a href=@{RepoCommitsR user repo}>Commits
|
<a href=@{RepoCommitsR user repo}>Commits
|
||||||
|
|
||||||
<h2>Branches
|
<h2>Branches
|
||||||
|
|
||||||
<ul>
|
<ul>
|
||||||
$forall RefName branch <- branches
|
$forall RefName branch <- branches
|
||||||
<li>
|
<li>
|
||||||
<a href=@{RepoSourceR user repo (pack branch) []}>#{branch}
|
<a href=@{RepoSourceR user repo (pack branch) []}>#{branch}
|
||||||
|
|
||||||
<h2>Tags
|
<h2>Tags
|
||||||
|
|
||||||
<ul>
|
<ul>
|
||||||
$forall RefName tag <- tags
|
$forall RefName tag <- tags
|
||||||
<li>
|
<li>
|
||||||
<a href=@{RepoSourceR user repo (pack tag) []}>#{tag}
|
<a href=@{RepoSourceR user repo (pack tag) []}>#{tag}
|
||||||
|
|
||||||
<a href=@{RepoSourceR user repo ref []}>#{ref}
|
<div>
|
||||||
<span>::
|
<a href=@{RepoSourceR user repo ref []}>#{ref}
|
||||||
$forall (piece, piecePath) <- dirs
|
:: #
|
||||||
<a href=@{RepoSourceR user repo ref piecePath}>#{piece}
|
$forall (piece, piecePath) <- dirs
|
||||||
<span>/
|
<a href=@{RepoSourceR user repo ref piecePath}>#{piece}
|
||||||
<h2>#{title}
|
/ #
|
||||||
$case display
|
|
||||||
$of Left source
|
$case sv
|
||||||
^{source}
|
$of FileView name body
|
||||||
$of Right (rows, mreadme)
|
<h2>#{name}
|
||||||
|
^{body}
|
||||||
|
$of DirectoryView mname rows mreadme
|
||||||
|
<h2>#{fromMaybe "Files" mname}
|
||||||
<table>
|
<table>
|
||||||
<tr>
|
<tr>
|
||||||
<th>Type
|
<th>Type
|
||||||
<th>Name
|
<th>Name
|
||||||
$forall (type', name) <- rows
|
$forall (_perm, _oid, name, type') <- rows
|
||||||
<tr>
|
<tr>
|
||||||
<td>#{type'}
|
<td>
|
||||||
|
$case type'
|
||||||
|
$of EntObjBlob
|
||||||
|
[F]
|
||||||
|
$of EntObjTree
|
||||||
|
[D]
|
||||||
<td>
|
<td>
|
||||||
<a href=@{RepoSourceR user repo ref (dir ++ [name])}>
|
<a href=@{RepoSourceR user repo ref (dir ++ [name])}>
|
||||||
#{name}
|
#{name}
|
||||||
|
|
Loading…
Reference in a new issue