{-# LANGUAGE ForeignFunctionInterface #-} module Web.Harp.Foreign where import Foreign.C.String import Foreign.C.Types import Foreign.Ptr import Web.Harp.Types foreign import ccall unsafe "harp_read_configs" readConfigsC :: CString -> CString -> IO (Ptr [Config]) foreign import ccall unsafe "harp_write_configs" writeConfigsC :: Ptr [Config] -> CString -> IO CInt foreign import ccall unsafe "&harp_errno" harpErrnoPtr :: Ptr CInt foreign import ccall unsafe "harp_strerror" harpStrerrorC :: CInt -> IO CString foreign import ccall unsafe "harp_make_empty_config" makeEmptyConfigC :: IO (Ptr Config) -- | See 'makeList' to understand the signature here. foreign import ccall unsafe "harp_make_hostnames_filter" makeHostnamesFilterC :: Ptr [CChar] -> IO (Ptr Filter) foreign import ccall unsafe "harp_make_ports_filter" makePortsFilterC :: Ptr [Int] -> IO (Ptr Filter) foreign import ccall unsafe "harp_make_static_path_resolver" makeStaticPathResolverC :: CString -> IO (Ptr Resolver) foreign import ccall unsafe "harp_make_server_resolver" makeServerResolverC :: CString -> CInt -> IO (Ptr Resolver) foreign import ccall unsafe "harp_make_choice" makeChoiceC :: CUShort -> Ptr Config -> IO (Ptr Choice) foreign import ccall unsafe "harp_cons" consC :: Ptr a -> Ptr [a] -> IO (Ptr [a]) foreign import ccall unsafe "&harp_free_config" freeConfigPtr :: FunPtr (Ptr Config -> IO ()) foreign import ccall unsafe "harp_free_list" freeListC :: Ptr [a] -> FunPtr (Ptr a -> IO ()) -> IO ()