diff --git a/src/Data/Binary.hs b/src/Data/Binary.hs
index 4a9ff2329146d754cf4b257f7e2023a45963dbdd..07970a3e756ef23bd49d22c9725896976cd6d6a4 100644
--- a/src/Data/Binary.hs
+++ b/src/Data/Binary.hs
@@ -132,7 +132,7 @@ import System.IO ( withBinaryFile, IOMode(ReadMode) )
 -- > > let e = OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))
 -- > > let v = encode e
 --
--- Where 'v' is a binary encoded data structure. To reconstruct the
+-- Where @v@ is a binary encoded data structure. To reconstruct the
 -- original data, we use 'decode'
 --
 -- > > decode v :: Exp
@@ -177,7 +177,7 @@ decode = runGet get
 -- consumed bytes is returned. In case of failure, a human-readable error
 -- message will be returned as well.
 --
--- /Since: 0.7.0.0/
+-- @since 0.7.0.0
 decodeOrFail :: Binary a => L.ByteString
              -> Either (L.ByteString, ByteOffset, String)
                        (L.ByteString, ByteOffset, a)
@@ -203,7 +203,7 @@ encodeFile f v = L.writeFile f (encode v)
 -- | Decode a value from a file. In case of errors, 'error' will
 -- be called with the error message.
 --
--- /Since: 0.7.0.0/
+-- @since 0.7.0.0
 decodeFile :: Binary a => FilePath -> IO a
 decodeFile f = do
   result <- decodeFileOrFail f
diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index 93fa452257ca7db97005ac8c820c814fe0c86f71..064b744af65b3a346ca81a1c04f01d8fc90fdc45 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -174,7 +174,7 @@ defaultPutList xs = put (length xs) <> mapM_ put xs
 -- Void never gets written nor reconstructed since it's impossible to have a
 -- value of that type
 
--- | /Since: 0.8.0.0/
+-- | @since 0.8.0.0
 instance Binary Void where
     put     = absurd
     get     = mzero
@@ -339,7 +339,7 @@ instance Binary Integer where
                     let v = roll bytes
                     return $! if sign == (1 :: Word8) then v else - v
 
--- | /Since: 0.8.0.0/
+-- | @since 0.8.0.0
 #ifdef HAS_FIXED_CONSTRUCTOR
 instance Binary (Fixed.Fixed a) where
   put (Fixed.MkFixed a) = put a
@@ -369,7 +369,7 @@ roll   = foldl' unstep 0 . reverse
 -- Fixed-size type for a subset of Natural
 type NaturalWord = Word64
 
--- | /Since: 0.7.3.0/
+-- | @since 0.7.3.0
 instance Binary Natural where
     {-# INLINE put #-}
     put n | n <= hi =
@@ -582,7 +582,7 @@ instance Binary a => Binary [a] where
     get = do n <- get :: Get Int
              getMany n
 
--- | 'getMany n' get 'n' elements in order, without blowing the stack.
+-- | @'getMany' n@ get @n@ elements in order, without blowing the stack.
 getMany :: Binary a => Int -> Get [a]
 getMany n = go [] n
  where
@@ -727,7 +727,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher
 ------------------------------------------------------------------------
 -- Fingerprints
 
--- | /Since: 0.7.6.0/
+-- | @since 0.7.6.0
 instance Binary Fingerprint where
     put (Fingerprint x1 x2) = put x1 <> put x2
     get = do
@@ -738,7 +738,7 @@ instance Binary Fingerprint where
 ------------------------------------------------------------------------
 -- Version
 
--- | /Since: 0.8.0.0/
+-- | @since 0.8.0.0
 instance Binary Version where
     put (Version br tags) = put br <> put tags
     get = Version <$> get <*> get
@@ -746,43 +746,43 @@ instance Binary Version where
 ------------------------------------------------------------------------
 -- Data.Monoid datatypes
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Monoid.Dual a) where
   get = fmap Monoid.Dual get
   put = put . Monoid.getDual
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary Monoid.All where
   get = fmap Monoid.All get
   put = put . Monoid.getAll
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary Monoid.Any where
   get = fmap Monoid.Any get
   put = put . Monoid.getAny
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Monoid.Sum a) where
   get = fmap Monoid.Sum get
   put = put . Monoid.getSum
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Monoid.Product a) where
   get = fmap Monoid.Product get
   put = put . Monoid.getProduct
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Monoid.First a) where
   get = fmap Monoid.First get
   put = put . Monoid.getFirst
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Monoid.Last a) where
   get = fmap Monoid.Last get
   put = put . Monoid.getLast
 
 #if MIN_VERSION_base(4,8,0)
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary (f a) => Binary (Monoid.Alt f a) where
   get = fmap Monoid.Alt get
   put = put . Monoid.getAlt
@@ -792,37 +792,37 @@ instance Binary (f a) => Binary (Monoid.Alt f a) where
 ------------------------------------------------------------------------
 -- Data.Semigroup datatypes
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Semigroup.Min a) where
   get = fmap Semigroup.Min get
   put = put . Semigroup.getMin
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Semigroup.Max a) where
   get = fmap Semigroup.Max get
   put = put . Semigroup.getMax
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Semigroup.First a) where
   get = fmap Semigroup.First get
   put = put . Semigroup.getFirst
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Semigroup.Last a) where
   get = fmap Semigroup.Last get
   put = put . Semigroup.getLast
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (Semigroup.Option a) where
   get = fmap Semigroup.Option get
   put = put . Semigroup.getOption
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary m => Binary (Semigroup.WrappedMonoid m) where
   get = fmap Semigroup.WrapMonoid get
   put = put . Semigroup.unwrapMonoid
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance (Binary a, Binary b) => Binary (Semigroup.Arg a b) where
   get                     = liftM2 Semigroup.Arg get get
   put (Semigroup.Arg a b) = put a <> put b
@@ -830,7 +830,7 @@ instance (Binary a, Binary b) => Binary (Semigroup.Arg a b) where
 ------------------------------------------------------------------------
 -- Non-empty lists
 
--- | /Since: 0.8.4.0/
+-- | @since 0.8.4.0
 instance Binary a => Binary (NE.NonEmpty a) where
   get = do
       list <- get
@@ -864,17 +864,17 @@ instance Binary a => Binary (NE.NonEmpty a) where
 -- * 'SomeTypeRep' (also known as 'Data.Typeable.TypeRep')
 --
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary VecCount where
     put = putWord8 . fromIntegral . fromEnum
     get = toEnum . fromIntegral <$> getWord8
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary VecElem where
     put = putWord8 . fromIntegral . fromEnum
     get = toEnum . fromIntegral <$> getWord8
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary RuntimeRep where
     put (VecRep a b)    = putWord8 0 >> put a >> put b
     put (TupleRep reps) = putWord8 1 >> put reps
@@ -918,7 +918,7 @@ instance Binary RuntimeRep where
 #endif
           _  -> fail "GHCi.TH.Binary.putRuntimeRep: invalid tag"
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary TyCon where
     put tc = do
         put (tyConPackage tc)
@@ -928,7 +928,7 @@ instance Binary TyCon where
         put (tyConKindRep tc)
     get = mkTyCon <$> get <*> get <*> get <*> get <*> get
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary KindRep where
     put (KindRepTyConApp tc k) = putWord8 0 >> put tc >> put k
     put (KindRepVar bndr) = putWord8 1 >> put bndr
@@ -948,7 +948,7 @@ instance Binary KindRep where
           5 -> KindRepTypeLit <$> get <*> get
           _ -> fail "GHCi.TH.Binary.putKindRep: invalid tag"
 
--- | @since 0.8.5.0. See #typeable-instances#
+-- | @since 0.8.5.0
 instance Binary TypeLitSort where
     put TypeLitSymbol = putWord8 0
     put TypeLitNat = putWord8 1
diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs
index 166b21155baa0910aa0b0fa9fd1b90cb680cf8fb..65f7c754354775e507d6ab9e8a0352ca84b533e1 100644
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@ -126,7 +126,7 @@
 -- from a socket which has higher likelihood to fail. To address these needs,
 -- use the incremental input method like in @incrementalExample@.
 -- For an example of how to read incrementally from a Handle,
--- see the implementation of 'decodeFileOrFail' in "Data.Binary".
+-- see the implementation of 'Data.Binary.decodeFileOrFail'.
 -----------------------------------------------------------------------------
 
 
@@ -328,7 +328,7 @@ dropHeadChunk lbs =
 -- consumed is returned. In the case of failure, a human-readable
 -- error message is included as well.
 --
--- /Since: 0.6.4.0/
+-- @since 0.6.4.0
 runGetOrFail :: Get a -> L.ByteString
              -> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a)
 runGetOrFail g lbs0 = feedAll (runGetIncremental g) lbs0
@@ -366,7 +366,7 @@ pushChunk r inp =
 
 
 -- | Feed a 'Decoder' with more input. If the 'Decoder' is 'Done' or 'Fail' it
--- will add the input to 'ByteString' of unconsumed input.
+-- will add the input to 'L.ByteString' of unconsumed input.
 --
 -- @
 --    'runGetIncremental' myParser \`pushChunks\` myLazyByteString
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index a469cbe8c2406e6398c390a25e4458f71d7cd25e..7dd436f94b6c710b818f46991659e693dfedd622 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -130,7 +130,7 @@ instance Applicative Get where
   (<*>) = apG
   {-# INLINE (<*>) #-}
 
--- | /Since: 0.7.1.0/
+-- | @since 0.7.1.0
 instance MonadPlus Get where
   mzero = empty
   mplus = (<|>)
@@ -201,7 +201,7 @@ bytesRead = C $ \inp k -> BytesRead (fromIntegral $ B.length inp) (k inp)
 -- Offset from 'bytesRead' will be relative to the start of 'isolate', not the
 -- absolute of the input.
 --
--- /Since: 0.7.2.0/
+-- @since 0.7.2.0
 isolate :: Int   -- ^ The number of bytes that must be consumed
         -> Get a -- ^ The decoder to isolate
         -> Get a
@@ -264,7 +264,7 @@ getBytes :: Int -> Get B.ByteString
 getBytes = getByteString
 {-# INLINE getBytes #-}
 
--- | /Since: 0.7.0.0/
+-- | @since 0.7.0.0
 instance Alternative Get where
   empty = C $ \inp _ks -> Fail inp "Data.Binary.Get(Alternative).empty"
   {-# INLINE empty #-}
@@ -312,7 +312,7 @@ pushFront bs = C $ \ inp ks -> ks (B.append bs inp) ()
 -- | Run the given decoder, but without consuming its input. If the given
 -- decoder fails, then so will this function.
 --
--- /Since: 0.7.0.0/
+-- @since 0.7.0.0
 lookAhead :: Get a -> Get a
 lookAhead g = do
   (decoder, bs) <- runAndKeepTrack g
@@ -325,7 +325,7 @@ lookAhead g = do
 -- If 'Nothing' is returned, the input will be unconsumed.
 -- If the given decoder fails, then so will this function.
 --
--- /Since: 0.7.0.0/
+-- @since 0.7.0.0
 lookAheadM :: Get (Maybe a) -> Get (Maybe a)
 lookAheadM g = do
   let g' = maybe (Left ()) Right <$> g
@@ -335,7 +335,7 @@ lookAheadM g = do
 -- If 'Left' is returned, the input will be unconsumed.
 -- If the given decoder fails, then so will this function.
 --
--- /Since: 0.7.1.0/
+-- @since 0.7.1.0
 lookAheadE :: Get (Either a b) -> Get (Either a b)
 lookAheadE g = do
   (decoder, bs) <- runAndKeepTrack g
@@ -348,7 +348,7 @@ lookAheadE g = do
 -- | Label a decoder. If the decoder fails, the label will be appended on
 -- a new line to the error message string.
 --
--- /Since: 0.7.2.0/
+-- @since 0.7.2.0
 label :: String -> Get a -> Get a
 label msg decoder = C $ \inp ks ->
   let r0 = runCont decoder inp (\inp' a -> Done inp' a)