{-|
  Copyright   :  (C) 2017, Google Inc.
  License     :  BSD2 (see the file LICENSE)
  Maintainer  :  Christiaan Baaij <christiaan.baaij@gmail.com>
-}

{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell    #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

module GHC.SrcLoc.Extra where

import Data.Binary
import Data.Hashable                        (Hashable (..))
import GHC.Generics
import SrcLoc
  (SrcSpan (..), RealSrcLoc, RealSrcSpan,
   mkRealSrcLoc, mkRealSrcSpan,
   realSrcSpanStart, realSrcSpanEnd,
   srcLocFile, srcLocLine, srcLocCol,
   srcSpanFile, srcSpanStartLine, srcSpanEndLine, srcSpanStartCol, srcSpanEndCol)
import FastString                           (FastString (..), bytesFS, mkFastStringByteList)

deriving instance Generic SrcSpan
instance Hashable SrcSpan

instance Hashable RealSrcSpan where
  hashWithSalt :: Int -> RealSrcSpan -> Int
hashWithSalt salt :: Int
salt rss :: RealSrcSpan
rss =
    Int -> (FastString, Int, Int, Int, Int) -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
rss,RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
rss, RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
rss
                      ,RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
rss, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
rss)

instance Hashable FastString where
  hashWithSalt :: Int -> FastString -> Int
hashWithSalt salt :: Int
salt fs :: FastString
fs = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (FastString -> Int
uniq FastString
fs)

instance Binary SrcSpan
instance Binary RealSrcSpan where
  put :: RealSrcSpan -> Put
put r :: RealSrcSpan
r = (RealSrcLoc, RealSrcLoc) -> Put
forall t. Binary t => t -> Put
put (RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
r, RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
r)
  get :: Get RealSrcSpan
get = (RealSrcLoc -> RealSrcLoc -> RealSrcSpan)
-> (RealSrcLoc, RealSrcLoc) -> RealSrcSpan
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan ((RealSrcLoc, RealSrcLoc) -> RealSrcSpan)
-> Get (RealSrcLoc, RealSrcLoc) -> Get RealSrcSpan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (RealSrcLoc, RealSrcLoc)
forall t. Binary t => Get t
get

instance Binary RealSrcLoc where
  put :: RealSrcLoc -> Put
put r :: RealSrcLoc
r = (FastString, Int, Int) -> Put
forall t. Binary t => t -> Put
put (RealSrcLoc -> FastString
srcLocFile RealSrcLoc
r, RealSrcLoc -> Int
srcLocLine RealSrcLoc
r, RealSrcLoc -> Int
srcLocCol RealSrcLoc
r)
  get :: Get RealSrcLoc
get = (\(file :: FastString
file,line :: Int
line,col :: Int
col) -> FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
file Int
line Int
col) ((FastString, Int, Int) -> RealSrcLoc)
-> Get (FastString, Int, Int) -> Get RealSrcLoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (FastString, Int, Int)
forall t. Binary t => Get t
get

instance Binary FastString where
  put :: FastString -> Put
put str :: FastString
str = [Word8] -> Put
forall t. Binary t => t -> Put
put ([Word8] -> Put) -> [Word8] -> Put
forall a b. (a -> b) -> a -> b
$ FastString -> [Word8]
bytesFS FastString
str
  get :: Get FastString
get = [Word8] -> FastString
mkFastStringByteList ([Word8] -> FastString) -> Get [Word8] -> Get FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Word8]
forall t. Binary t => Get t
get