mirror of
https://github.com/ilyakooo0/vty.git
synced 2024-12-12 15:23:31 +03:00
yet more optimization of serialize_cap_op
Ignore-this: d8e926915c354cd50f7fd201484d4125 darcs-hash:20100114040815-f0a0d-b30bdbbfdf0c11ed8cc661a46f92ca95ece1a2b6.gz
This commit is contained in:
parent
4907481768
commit
b13ca4dacb
@ -61,11 +61,6 @@ apply_param_ops cap params = foldl apply_param_op params (param_ops cap)
|
|||||||
apply_param_op :: [CapParam] -> ParamOp -> [CapParam]
|
apply_param_op :: [CapParam] -> ParamOp -> [CapParam]
|
||||||
apply_param_op params IncFirstTwo = map (+ 1) params
|
apply_param_op params IncFirstTwo = map (+ 1) params
|
||||||
|
|
||||||
-- | range is 0-based offset into cap_bytes and count
|
|
||||||
{-# INLINE ptr_at_offset #-}
|
|
||||||
ptr_at_offset :: CapExpression -> Word8 -> Ptr Word8
|
|
||||||
ptr_at_offset cap !offset = fst ( cap_bytes cap ) `plusPtr` ( fromEnum offset )
|
|
||||||
|
|
||||||
cap_expression_required_bytes :: CapExpression -> [CapParam] -> Word
|
cap_expression_required_bytes :: CapExpression -> [CapParam] -> Word
|
||||||
cap_expression_required_bytes cap params =
|
cap_expression_required_bytes cap params =
|
||||||
let params' = apply_param_ops cap params
|
let params' = apply_param_ops cap params
|
||||||
@ -77,7 +72,7 @@ cap_ops_required_bytes ops = do
|
|||||||
return $ sum counts
|
return $ sum counts
|
||||||
|
|
||||||
cap_op_required_bytes :: CapOp -> Eval Word
|
cap_op_required_bytes :: CapOp -> Eval Word
|
||||||
cap_op_required_bytes (Bytes _ c) = return $ toEnum $ fromEnum c
|
cap_op_required_bytes (Bytes _ _ c) = return $ toEnum c
|
||||||
cap_op_required_bytes DecOut = do
|
cap_op_required_bytes DecOut = do
|
||||||
p <- pop
|
p <- pop
|
||||||
return $ toEnum $ length $ show p
|
return $ toEnum $ length $ show p
|
||||||
@ -160,12 +155,13 @@ serialize_cap_ops :: MonadIO m => OutputBuffer -> CapOps -> EvalT m OutputBuffer
|
|||||||
serialize_cap_ops out_ptr ops = foldM serialize_cap_op out_ptr ops
|
serialize_cap_ops out_ptr ops = foldM serialize_cap_op out_ptr ops
|
||||||
|
|
||||||
serialize_cap_op :: MonadIO m => OutputBuffer -> CapOp -> EvalT m OutputBuffer
|
serialize_cap_op :: MonadIO m => OutputBuffer -> CapOp -> EvalT m OutputBuffer
|
||||||
serialize_cap_op out_ptr ( Bytes offset ( W8# byte_count ) ) = do
|
serialize_cap_op out_ptr ( Bytes !offset !byte_count !next_offset ) = do
|
||||||
(cap, _) <- ask
|
(cap, _) <- ask
|
||||||
let src_ptr = ptr_at_offset cap offset
|
let ( !start_ptr, _ ) = cap_bytes cap
|
||||||
let !i = I# ( word2Int# byte_count )
|
!src_ptr = start_ptr `plusPtr` offset
|
||||||
liftIO $! memcpy out_ptr src_ptr ( toEnum $! i )
|
!out_ptr' = out_ptr `plusPtr` next_offset
|
||||||
return $! out_ptr `plusPtr` i
|
liftIO $! memcpy out_ptr src_ptr byte_count
|
||||||
|
return out_ptr'
|
||||||
serialize_cap_op out_ptr DecOut = do
|
serialize_cap_op out_ptr DecOut = do
|
||||||
p <- pop
|
p <- pop
|
||||||
let out_str = show p
|
let out_str = show p
|
||||||
|
@ -18,14 +18,13 @@ import Data.Array.Unboxed
|
|||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Word
|
import Data.Word
|
||||||
|
|
||||||
|
import Foreign.C.Types
|
||||||
import Foreign.Marshal.Array
|
import Foreign.Marshal.Array
|
||||||
import Foreign.Ptr
|
import Foreign.Ptr
|
||||||
|
|
||||||
import Text.ParserCombinators.Parsec
|
import Text.ParserCombinators.Parsec
|
||||||
|
|
||||||
type BytesLength = Word8
|
type CapBytes = ( Ptr Word8, CSize )
|
||||||
type BytesOffset = Word8
|
|
||||||
type CapBytes = ( Ptr Word8, Word )
|
|
||||||
|
|
||||||
data CapExpression = CapExpression
|
data CapExpression = CapExpression
|
||||||
{ cap_ops :: !CapOps
|
{ cap_ops :: !CapOps
|
||||||
@ -43,7 +42,7 @@ type CapParam = Word
|
|||||||
|
|
||||||
type CapOps = [CapOp]
|
type CapOps = [CapOp]
|
||||||
data CapOp =
|
data CapOp =
|
||||||
Bytes !BytesOffset !BytesLength
|
Bytes !Int !CSize !Int
|
||||||
| DecOut | CharOut
|
| DecOut | CharOut
|
||||||
-- This stores a 0-based index to the parameter. However the operation that implies this op is
|
-- This stores a 0-based index to the parameter. However the operation that implies this op is
|
||||||
-- 1-based
|
-- 1-based
|
||||||
@ -60,7 +59,7 @@ data CapOp =
|
|||||||
deriving ( Show )
|
deriving ( Show )
|
||||||
|
|
||||||
instance NFData CapOp where
|
instance NFData CapOp where
|
||||||
rnf (Bytes offset c) = rnf offset >| rnf c
|
rnf ( Bytes offset count next_offset ) = rnf offset
|
||||||
rnf (PushParam !_pn) = ()
|
rnf (PushParam !_pn) = ()
|
||||||
rnf (PushValue !_v) = ()
|
rnf (PushValue !_v) = ()
|
||||||
rnf (Conditional c_expr c_parts) = rnf c_expr >| rnf c_parts
|
rnf (Conditional c_expr c_parts) = rnf c_expr >| rnf c_parts
|
||||||
@ -116,7 +115,7 @@ literal_percent_parser = do
|
|||||||
_ <- char '%'
|
_ <- char '%'
|
||||||
start_offset <- getState >>= return . next_offset
|
start_offset <- getState >>= return . next_offset
|
||||||
inc_offset 1
|
inc_offset 1
|
||||||
return $ BuildResults 0 [Bytes start_offset 1] []
|
return $ BuildResults 0 [Bytes start_offset 1 1] []
|
||||||
|
|
||||||
param_op_parser :: CapParser BuildResults
|
param_op_parser :: CapParser BuildResults
|
||||||
param_op_parser
|
param_op_parser
|
||||||
@ -286,11 +285,11 @@ bytes_op_parser :: CapParser BuildResults
|
|||||||
bytes_op_parser = do
|
bytes_op_parser = do
|
||||||
bytes <- many1 $ satisfy (/= '%')
|
bytes <- many1 $ satisfy (/= '%')
|
||||||
start_offset <- getState >>= return . next_offset
|
start_offset <- getState >>= return . next_offset
|
||||||
let !c = toEnum $ length bytes
|
let !c = length bytes
|
||||||
!s <- getState
|
!s <- getState
|
||||||
let s' = s { next_offset = start_offset + c }
|
let s' = s { next_offset = start_offset + c }
|
||||||
setState s'
|
setState s'
|
||||||
return $ BuildResults 0 [Bytes start_offset c] []
|
return $ BuildResults 0 [Bytes start_offset ( toEnum c ) c ] []
|
||||||
|
|
||||||
char_const_parser :: CapParser BuildResults
|
char_const_parser :: CapParser BuildResults
|
||||||
char_const_parser = do
|
char_const_parser = do
|
||||||
@ -301,10 +300,10 @@ char_const_parser = do
|
|||||||
return $ BuildResults 0 [ PushValue char_value ] [ ]
|
return $ BuildResults 0 [ PushValue char_value ] [ ]
|
||||||
|
|
||||||
data BuildState = BuildState
|
data BuildState = BuildState
|
||||||
{ next_offset :: Word8
|
{ next_offset :: Int
|
||||||
}
|
}
|
||||||
|
|
||||||
inc_offset :: Word8 -> CapParser ()
|
inc_offset :: Int -> CapParser ()
|
||||||
inc_offset n = do
|
inc_offset n = do
|
||||||
s <- getState
|
s <- getState
|
||||||
let s' = s { next_offset = next_offset s + n }
|
let s' = s { next_offset = next_offset s + n }
|
||||||
|
Loading…
Reference in New Issue
Block a user