Browse Source

Got Gtk working, started Xl parsing implementation

master
Denis Tereshkin 9 years ago
parent
commit
27327cf1d5
  1. 19
      app/Main.hs
  2. 5
      quik-connector.cabal
  3. 35
      src/QuoteSource/DDE.hs
  4. 20
      src/QuoteSource/DataImport.hs
  5. 4
      src/QuoteSource/TableParser.hs
  6. 39
      src/QuoteSource/XlParser.hs

19
app/Main.hs

@ -5,9 +5,10 @@ import QuoteSource.DDE
import QuoteSource.DataImport import QuoteSource.DataImport
import Control.Concurrent import Control.Concurrent
import Control.Monad import Control.Monad
import Control.Monad.IO.Class
import Data.IORef
import Graphics.UI.Gtk hiding (Action, backspace)
import Graphics.UI.FLTK.LowLevel.FL
import Graphics.UI.FLTK.LowLevel.FLTKHS
callback :: DdeCallback callback :: DdeCallback
callback = undefined callback = undefined
@ -15,11 +16,11 @@ callback = undefined
main :: IO () main :: IO ()
main = do main = do
dis <- initDataImportServer "atrade" dis <- initDataImportServer "atrade"
forever $ threadDelay 1000 void initGUI
window <- windowNew (Size (Width 320) (Height 170)) window <- windowNew
Nothing Nothing window `on` deleteEvent $ do
end window liftIO mainQuit
showWidget window return False
_ <- run widgetShowAll window
return () mainGUI

5
quik-connector.cabal

@ -20,7 +20,9 @@ library
, QuoteSource.DataImport , QuoteSource.DataImport
build-depends: base >= 4.7 && < 5 build-depends: base >= 4.7 && < 5
, Win32 , Win32
, fltkhs , gtk
, binary
, bytestring
default-language: Haskell2010 default-language: Haskell2010
extra-libraries: "user32" extra-libraries: "user32"
@ -31,6 +33,7 @@ executable quik-connector-exe
build-depends: base build-depends: base
, quik-connector , quik-connector
, Win32 , Win32
, gtk
default-language: Haskell2010 default-language: Haskell2010
extra-libraries: "user32" extra-libraries: "user32"

35
src/QuoteSource/DDE.hs

@ -19,11 +19,13 @@ import Control.Exception
import Control.Monad import Control.Monad
import Data.Bits import Data.Bits
import Data.Typeable import Data.Typeable
import Data.ByteString hiding (map)
import System.Win32.DLL import System.Win32.DLL
import System.Win32.Types import System.Win32.Types
import Foreign import Foreign
import Foreign.C.Types import Foreign.C.Types
import Foreign.C.String import Foreign.C.String
import Foreign.Marshal.Array
data DdeException = ApiError String data DdeException = ApiError String
deriving (Show, Typeable) deriving (Show, Typeable)
@ -47,28 +49,34 @@ ddeCpWinAnsi = 1004
instance Exception DdeException instance Exception DdeException
foreign import stdcall unsafe "windows.h DdeInitializeW" foreign import ccall unsafe "windows.h DdeInitializeW"
ddeInitialize :: LPDWORD -> FunPtr DdeCallback -> DWORD -> DWORD -> IO CUInt ddeInitialize :: LPDWORD -> FunPtr DdeCallback -> DWORD -> DWORD -> IO CUInt
foreign import stdcall unsafe "windows.h DdeUninitialize" foreign import ccall unsafe "windows.h DdeUninitialize"
ddeUninitialize :: DWORD -> IO BOOL ddeUninitialize :: DWORD -> IO BOOL
foreign import stdcall unsafe "windows.h DdeCreateStringHandleW" foreign import ccall unsafe "windows.h DdeCreateStringHandleW"
ddeCreateStringHandle :: DWORD -> LPSTR -> CInt -> IO HANDLE ddeCreateStringHandle :: DWORD -> LPSTR -> CInt -> IO HANDLE
foreign import stdcall unsafe "windows.h DdeFreeStringHandleW" foreign import ccall unsafe "windows.h DdeFreeStringHandleW"
ddeFreeStringHandle :: DWORD -> LPSTR -> IO HANDLE ddeFreeStringHandle :: DWORD -> LPSTR -> IO HANDLE
foreign import stdcall unsafe "windows.h DdeNameService" foreign import ccall unsafe "windows.h DdeNameService"
ddeNameService :: DWORD -> HANDLE -> HANDLE -> CInt -> IO HANDLE ddeNameService :: DWORD -> HANDLE -> HANDLE -> CInt -> IO HANDLE
foreign import stdcall unsafe "windows.h DdeCmpStringHandles" foreign import ccall unsafe "windows.h DdeCmpStringHandles"
ddeCmpStringHandles :: HANDLE -> HANDLE -> IO CInt ddeCmpStringHandles :: HANDLE -> HANDLE -> IO CInt
foreign import stdcall unsafe "windows.h DdeQueryStringW" foreign import ccall unsafe "windows.h DdeQueryStringW"
ddeQueryString :: DWORD -> HANDLE -> CString -> DWORD -> CInt -> IO DWORD ddeQueryString :: DWORD -> HANDLE -> CString -> DWORD -> CInt -> IO DWORD
foreign import stdcall "wrapper" foreign import ccall unsafe "windows.h DdeAccessData"
ddeAccessData :: HANDLE -> LPDWORD -> IO (Ptr CUChar)
foreign import ccall unsafe "windows.h DdeUnaccessData"
ddeUnaccessData :: HANDLE -> IO ()
foreign import ccall "wrapper"
mkCallbackPtr :: DdeCallback -> IO (FunPtr DdeCallback) mkCallbackPtr :: DdeCallback -> IO (FunPtr DdeCallback)
data DdeState = DdeState { data DdeState = DdeState {
@ -90,8 +98,8 @@ initializeDde appName topicName callback = alloca (\instancePtr -> do
when (rc /= CUInt 0) $ throw $ ApiError "Unable to initialize DDE" when (rc /= CUInt 0) $ throw $ ApiError "Unable to initialize DDE"
withCString appName (\appNameRaw -> withCString topicName (\topicNameRaw -> do withCString appName (\appNameRaw -> withCString topicName (\topicNameRaw -> do
appNameHandle <- ddeCreateStringHandle instanceRaw appNameRaw 0 appNameHandle <- ddeCreateStringHandle instanceRaw appNameRaw ddeCpWinAnsi
topicNameHandle <- ddeCreateStringHandle instanceRaw topicNameRaw 0 topicNameHandle <- ddeCreateStringHandle instanceRaw topicNameRaw ddeCpWinAnsi
when (appNameHandle == nullHANDLE || topicNameHandle == nullHANDLE) $ throw $ ApiError "Unable to create strings handles" when (appNameHandle == nullHANDLE || topicNameHandle == nullHANDLE) $ throw $ ApiError "Unable to create strings handles"
rc2 <- ddeNameService instanceRaw appNameHandle nullPtr 1 rc2 <- ddeNameService instanceRaw appNameHandle nullPtr 1
@ -112,3 +120,10 @@ queryString state maxSize handle = allocaBytes maxSize (\x -> do
then return Nothing then return Nothing
else Just <$> peekCAString x) else Just <$> peekCAString x)
accessData :: HANDLE -> IO ByteString
accessData handle = alloca (\dataSizePtr -> do
dataPtr <- ddeAccessData handle dataSizePtr
dataSize <- peek dataSizePtr
pack . (map (toEnum . fromEnum)) <$> peekArray (fromEnum dataSize) dataPtr)

20
src/QuoteSource/DataImport.hs

@ -13,7 +13,10 @@ import Foreign.C.Types
import Foreign.C.String import Foreign.C.String
import QuoteSource.DDE import QuoteSource.DDE
import QuoteSource.XlParser
import Data.IORef import Data.IORef
import Text.Printf
import Data.Binary
data ServerState = ServerState { data ServerState = ServerState {
dde :: DdeState, dde :: DdeState,
@ -21,22 +24,17 @@ data ServerState = ServerState {
} }
ddeCallback :: IORef ServerState -> CUInt -> CUInt -> HANDLE -> HANDLE -> HANDLE -> HANDLE -> LPDWORD -> LPDWORD -> IO HANDLE ddeCallback :: IORef ServerState -> CUInt -> CUInt -> HANDLE -> HANDLE -> HANDLE -> HANDLE -> LPDWORD -> LPDWORD -> IO HANDLE
ddeCallback state msgType format hConv hsz1 hsz2 hData dwData1 dwData2 = do ddeCallback state msgType format hConv hsz1 hsz2 hData dwData1 dwData2
putStrLn "Callback"
return nullHANDLE
{-
| msgType == ddeXtypConnect = handleConnect state hsz1 hsz2 | msgType == ddeXtypConnect = handleConnect state hsz1 hsz2
| msgType == ddeXtypPoke = handlePoke state hsz1 hData | msgType == ddeXtypPoke = handlePoke state hsz1 hData
| otherwise = do | otherwise = do
print msgType putStrLn $ printf "msgtype: %08x" $ toInteger msgType
return nullHANDLE return nullHANDLE
where where
handleConnect state hsz1 hsz2 = do handleConnect state hsz1 hsz2 = do
myAppName <- appName <$> readIORef state myAppName <- appName <$> readIORef state
myDdeState <- dde <$> readIORef state myDdeState <- dde <$> readIORef state
maybeAppName <- queryString myDdeState 256 hsz2 maybeAppName <- queryString myDdeState 256 hsz2
putStrLn "Connect"
case maybeAppName of case maybeAppName of
Just incomingAppName -> do Just incomingAppName -> do
putStrLn incomingAppName putStrLn incomingAppName
@ -46,10 +44,10 @@ ddeCallback state msgType format hConv hsz1 hsz2 hData dwData1 dwData2 = do
Nothing -> return ddeResultFalse Nothing -> return ddeResultFalse
handlePoke state hsz1 hData = do handlePoke state hsz1 hData = do
putStrLn "Poke" myDdeState <- dde <$> readIORef state
return ddeResultAck maybeTopic <- queryString myDdeState 256 hsz1
-} case maybeTopic of
Nothing -> return ddeResultFalse
initDataImportServer :: String -> IO (IORef ServerState) initDataImportServer :: String -> IO (IORef ServerState)
initDataImportServer applicationName = do initDataImportServer applicationName = do

4
src/QuoteSource/TableParser.hs

@ -0,0 +1,4 @@
module QuoteSource.TableParser (
) where

39
src/QuoteSource/XlParser.hs

@ -0,0 +1,39 @@
module QuoteSource.XlParser (
XlData(..),
xlParser
) where
import Control.Applicative
import Control.Monad
import Data.Binary.Get
import Data.ByteString
data XlData = XlInt Int | XlDouble Double | XlString String | XlEmpty
data XlPosition = XlPosition { width :: Int, height :: Int, xPos :: Int, yPos :: Int }
btTable = 16
btFloat = 1
btString = 2
btBlank = 5
btInt = 6
btSkip = 7
incrementPosition :: XlPosition -> Maybe XlPosition
incrementPosition pos = do
if 1 + xPos pos < width pos
then Just pos { xPos = 1 + xPos pos }
else if 1 + yPos pos < height pos
then Just pos { xPos = 0, yPos = 1 + yPos pos }
else Nothing
xlParser :: Get (Int, Int, [XlData])
xlParser = do
datatype <- getWord16le
when (datatype /= btTable) $ fail "First entry should be table"
blocksize <- fromEnum <$> getWord16le
when (blocksize /= 4) $ fail "Table entry should have size 4"
return (0, 0, [])
Loading…
Cancel
Save