module Data.RefSerialize.Serialize where
import GHC.Exts
import Unsafe.Coerce
import Data.List(isPrefixOf,insertBy,elem,sortBy)
import Data.Char(isAlpha,isAlphaNum,isSpace,isUpper)
import System.Mem.StableName
import System.IO.Unsafe
import Control.Monad (MonadPlus(..))
import Control.Applicative
import Data.ByteString.Lazy.Char8 as B
import Data.ByteString.Lazy.Search
import qualified Data.HashTable.IO as HT
import Data.Ord
import Data.Monoid
import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as S
import qualified Data.ByteString.Unsafe as S
import Data.ByteString.Lazy.Internal
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr
myToStrict :: ByteString -> S.ByteString
myToStrict Empty = S.empty
myToStrict (Chunk c Empty) = c
myToStrict cs0 = S.unsafeCreate totalLen $ \ptr -> go cs0 ptr
where
totalLen = foldlChunks (\a c -> a + S.length c) 0 cs0
go Empty !_ = return ()
go (Chunk (S.PS fp off len) cs) !destptr =
withForeignPtr fp $ \p -> do
S.memcpy destptr (p `plusPtr` off) (fromIntegral len)
go cs (destptr `plusPtr` len)
type MFun= Char
type VarName = String
data ShowF= Expr ByteString | Var Int deriving Show
type Context = HT.BasicHashTable Int ( StableName MFun, MFun,[ShowF],Int)
data Error= Error String
data StatW= StatW (Context, [ShowF], ByteString)
data STW a= STW(StatW-> (StatW , a) )
instance Functor STW where
fmap f (STW stwx)= STW $ \s ->
let (s',x) = stwx s
in (s', f x)
instance Applicative STW where
pure x = STW (\s -> (s, x))
STW g <*> STW f = STW (\s ->
let (s', x)= g s
(s'',y)= f s'
in (s'', x y)
)
instance Monad STW where
return x = STW (\s -> (s, x))
STW g >>= f = STW (\s ->
let (s', x)= g s
STW fun = f x
in fun s'
)
empty = HT.new
assocs = sortBy (comparing fst) . unsafePerformIO . HT.toList
insert k v ht= unsafePerformIO $! HT.insert ht k v >> return ht
delete k ht= unsafePerformIO $! HT.delete ht k >> return ht
lookup k ht= unsafePerformIO $! HT.lookup ht k
toList = unsafePerformIO . HT.toList
fromList = unsafePerformIO . HT.fromList
addrHash :: Context -> a -> IO (Either Int Int)
addrHash c x =
case Data.RefSerialize.Serialize.lookup hash c of
Nothing -> addc [Var hash] c >> return (Left hash)
Just (x,y,z,n) -> HT.insert c hash (x,y,z,n+1) >> return (Right hash)
where
addc str c= HT.insert c hash (st,unsafeCoerce x, str,1)
(hash,st) = hasht x
readContext :: ByteString -> ByteString -> (ByteString, ByteString)
readContext pattern str=
let (s1,s2)= breakOn (myToStrict pattern) str
in (s1, B.drop (fromIntegral $ B.length pattern) s2)
hasht x= unsafePerformIO $ do
st <- makeStableName $! x
return (hashStableName st,unsafeCoerce st)
varName x= "v"++ (show . hash) x
where hash x= let (ht,_)= hasht x in ht
numVar :: String -> Maybe Int
numVar ('v':var)= Just $ read var
numVar _ = Nothing