#include "Typeable.h"
module Network.BSD (
       
    
    HostName,
    getHostName,	    
    HostEntry(..),
    getHostByName,	    
    getHostByAddr,	    
    hostAddress,	    
    getHostEntries,	    
    
    setHostEntry,	    
    getHostEntry,	    
    endHostEntry,	    
    
    ServiceEntry(..),
    ServiceName,
    getServiceByName,	    
    getServiceByPort,       
    getServicePortNumber,   
    getServiceEntries,	    
    
    getServiceEntry,	    
    setServiceEntry,	    
    endServiceEntry,	    
    
    ProtocolName,
    ProtocolNumber,
    ProtocolEntry(..),
    getProtocolByName,	    
    getProtocolByNumber,    
    getProtocolNumber,	    
    defaultProtocol,        
    getProtocolEntries,	    
    
    setProtocolEntry,	    
    getProtocolEntry,	    
    endProtocolEntry,	    
    
    PortNumber,
    
    NetworkName,
    NetworkAddr,
    NetworkEntry(..)
    , getNetworkByName	    
    , getNetworkByAddr      
    , getNetworkEntries     
    
    , setNetworkEntry	    
    , getNetworkEntry	    
    , endNetworkEntry	    
    ) where
import Network.Socket
import Control.Concurrent 	( MVar, newMVar, withMVar )
import Foreign.C.Error ( throwErrnoIfMinus1, throwErrnoIfMinus1_ )
import Foreign.C.String ( CString, peekCString, peekCStringLen, withCString )
import Foreign.C.Types ( CInt, CULong, CChar, CSize, CShort )
import Foreign.Ptr ( Ptr, nullPtr )
import Foreign.Storable ( Storable(..) )
import Foreign.Marshal.Array ( allocaArray0, peekArray0 )
import Foreign.Marshal.Utils ( with, fromBool )
import Data.Typeable
import System.IO.Error
import System.IO.Unsafe ( unsafePerformIO )
import GHC.IO.Exception
import Control.Monad ( liftM )
type ProtocolName = String
data ServiceEntry  = 
  ServiceEntry  {
     serviceName     :: ServiceName,	
     serviceAliases  :: [ServiceName],	
     servicePort     :: PortNumber,	
     serviceProtocol :: ProtocolName	
  } deriving (Show)
INSTANCE_TYPEABLE0(ServiceEntry,serviceEntryTc,"ServiceEntry")
instance Storable ServiceEntry where
   sizeOf    _ = 16
   alignment _ = alignment (undefined :: CInt) 
   peek p = do
        s_name    <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p >>= peekCString
        s_aliases <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p
                           >>= peekArray0 nullPtr
                           >>= mapM peekCString
        s_port    <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p
        s_proto   <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p >>= peekCString
        return (ServiceEntry {
                        serviceName     = s_name,
                        serviceAliases  = s_aliases,
                           
                           
                        servicePort     = PortNum (fromIntegral (s_port :: CInt)),
                        serviceProtocol = s_proto
                })
   poke p = error "Storable.poke(BSD.ServiceEntry) not implemented"
getServiceByName :: ServiceName 	
		 -> ProtocolName 	
		 -> IO ServiceEntry	
getServiceByName name proto = withLock $ do
 withCString name  $ \ cstr_name  -> do
 withCString proto $ \ cstr_proto -> do
 throwNoSuchThingIfNull "getServiceByName" "no such service entry"
   $ (trySysCall (c_getservbyname cstr_name cstr_proto))
 >>= peek
foreign import CALLCONV unsafe "getservbyname" 
  c_getservbyname :: CString -> CString -> IO (Ptr ServiceEntry)
getServiceByPort :: PortNumber -> ProtocolName -> IO ServiceEntry
getServiceByPort (PortNum port) proto = withLock $ do
 withCString proto $ \ cstr_proto -> do
 throwNoSuchThingIfNull "getServiceByPort" "no such service entry"
   $ (trySysCall (c_getservbyport (fromIntegral port) cstr_proto))
 >>= peek
foreign import CALLCONV unsafe "getservbyport" 
  c_getservbyport :: CInt -> CString -> IO (Ptr ServiceEntry)
getServicePortNumber :: ServiceName -> IO PortNumber
getServicePortNumber name = do
    (ServiceEntry _ _ port _) <- getServiceByName name "tcp"
    return port
getServiceEntry	:: IO ServiceEntry
getServiceEntry = withLock $ do
 throwNoSuchThingIfNull "getServiceEntry" "no such service entry"
   $ trySysCall c_getservent
 >>= peek
foreign import ccall unsafe "getservent" c_getservent :: IO (Ptr ServiceEntry)
setServiceEntry	:: Bool -> IO ()
setServiceEntry flg = withLock $ trySysCall $ c_setservent (fromBool flg)
foreign import ccall unsafe  "setservent" c_setservent :: CInt -> IO ()
endServiceEntry	:: IO ()
endServiceEntry = withLock $ trySysCall $ c_endservent
foreign import ccall unsafe  "endservent" c_endservent :: IO ()
getServiceEntries :: Bool -> IO [ServiceEntry]
getServiceEntries stayOpen = do
  setServiceEntry stayOpen
  getEntries (getServiceEntry) (endServiceEntry)
data ProtocolEntry = 
  ProtocolEntry  {
     protoName    :: ProtocolName,	
     protoAliases :: [ProtocolName],	
     protoNumber  :: ProtocolNumber	
  } deriving (Read, Show)
INSTANCE_TYPEABLE0(ProtocolEntry,protocolEntryTc,"ProtocolEntry")
instance Storable ProtocolEntry where
   sizeOf    _ = 12
   alignment _ = alignment (undefined :: CInt) 
   peek p = do
        p_name    <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p >>= peekCString
        p_aliases <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p
                           >>= peekArray0 nullPtr
                           >>= mapM peekCString
        p_proto        <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p 
        return (ProtocolEntry { 
                        protoName    = p_name,
                        protoAliases = p_aliases,
                        protoNumber  = p_proto
                })
   poke p = error "Storable.poke(BSD.ProtocolEntry) not implemented"
getProtocolByName :: ProtocolName -> IO ProtocolEntry
getProtocolByName name = withLock $ do
 withCString name $ \ name_cstr -> do
 throwNoSuchThingIfNull "getProtocolByName" ("no such protocol name: " ++ name)
   $ (trySysCall.c_getprotobyname) name_cstr
 >>= peek
foreign import  CALLCONV unsafe  "getprotobyname" 
   c_getprotobyname :: CString -> IO (Ptr ProtocolEntry)
getProtocolByNumber :: ProtocolNumber -> IO ProtocolEntry
getProtocolByNumber num = withLock $ do
 throwNoSuchThingIfNull "getProtocolByNumber" ("no such protocol number: " ++ show num)
   $ (trySysCall.c_getprotobynumber) (fromIntegral num)
 >>= peek
foreign import CALLCONV unsafe  "getprotobynumber"
   c_getprotobynumber :: CInt -> IO (Ptr ProtocolEntry)
getProtocolNumber :: ProtocolName -> IO ProtocolNumber
getProtocolNumber proto = do
 (ProtocolEntry _ _ num) <- getProtocolByName proto
 return num
getProtocolEntry :: IO ProtocolEntry	
getProtocolEntry = withLock $ do
 ent <- throwNoSuchThingIfNull "getProtocolEntry" "no such protocol entry"
   		$ trySysCall c_getprotoent
 peek ent
foreign import ccall unsafe  "getprotoent" c_getprotoent :: IO (Ptr ProtocolEntry)
setProtocolEntry :: Bool -> IO ()	
setProtocolEntry flg = withLock $ trySysCall $ c_setprotoent (fromBool flg)
foreign import ccall unsafe "setprotoent" c_setprotoent :: CInt -> IO ()
endProtocolEntry :: IO ()
endProtocolEntry = withLock $ trySysCall $ c_endprotoent
foreign import ccall unsafe "endprotoent" c_endprotoent :: IO ()
getProtocolEntries :: Bool -> IO [ProtocolEntry]
getProtocolEntries stayOpen = withLock $ do
  setProtocolEntry stayOpen
  getEntries (getProtocolEntry) (endProtocolEntry)
data HostEntry = 
  HostEntry  {
     hostName      :: HostName,  	
     hostAliases   :: [HostName],	
     hostFamily    :: Family,	        
     hostAddresses :: [HostAddress]	
  } deriving (Read, Show)
INSTANCE_TYPEABLE0(HostEntry,hostEntryTc,"hostEntry")
instance Storable HostEntry where
   sizeOf    _ = 20
   alignment _ = alignment (undefined :: CInt) 
   peek p = do
        h_name       <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p >>= peekCString
        h_aliases    <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p
                                >>= peekArray0 nullPtr
                                >>= mapM peekCString
        h_addrtype   <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p
        
        h_addr_list  <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p
                                >>= peekArray0 nullPtr
                                >>= mapM peek
        return (HostEntry {
                        hostName       = h_name,
                        hostAliases    = h_aliases,
                        hostFamily     = unpackFamily h_addrtype,
                        hostAddresses  = h_addr_list
                })
   poke p = error "Storable.poke(BSD.ServiceEntry) not implemented"
hostAddress :: HostEntry -> HostAddress
hostAddress (HostEntry nm _ _ ls) =
 case ls of
   []    -> error ("BSD.hostAddress: empty network address list for " ++ nm)
   (x:_) -> x
getHostByName :: HostName -> IO HostEntry
getHostByName name = withLock $ do
  withCString name $ \ name_cstr -> do
   ent <- throwNoSuchThingIfNull "getHostByName" "no such host entry"
    		$ trySysCall $ c_gethostbyname name_cstr
   peek ent
foreign import CALLCONV safe "gethostbyname" 
   c_gethostbyname :: CString -> IO (Ptr HostEntry)
getHostByAddr :: Family -> HostAddress -> IO HostEntry
getHostByAddr family addr = do
 with addr $ \ ptr_addr -> withLock $ do
 throwNoSuchThingIfNull 	"getHostByAddr" "no such host entry"
   $ trySysCall $ c_gethostbyaddr ptr_addr (fromIntegral (sizeOf addr)) (packFamily family)
 >>= peek
foreign import CALLCONV safe "gethostbyaddr"
   c_gethostbyaddr :: Ptr HostAddress -> CInt -> CInt -> IO (Ptr HostEntry)
getHostEntry :: IO HostEntry
getHostEntry = withLock $ do
 throwNoSuchThingIfNull 	"getHostEntry" "unable to retrieve host entry"
   $ trySysCall $ c_gethostent
 >>= peek
foreign import ccall unsafe "gethostent" c_gethostent :: IO (Ptr HostEntry)
setHostEntry :: Bool -> IO ()
setHostEntry flg = withLock $ trySysCall $ c_sethostent (fromBool flg)
foreign import ccall unsafe "sethostent" c_sethostent :: CInt -> IO ()
endHostEntry :: IO ()
endHostEntry = withLock $ c_endhostent
foreign import ccall unsafe "endhostent" c_endhostent :: IO ()
getHostEntries :: Bool -> IO [HostEntry]
getHostEntries stayOpen = do
  setHostEntry stayOpen
  getEntries (getHostEntry) (endHostEntry)
type NetworkAddr = CULong
type NetworkName = String
data NetworkEntry =
  NetworkEntry {
     networkName	:: NetworkName,   
     networkAliases	:: [NetworkName], 
     networkFamily	:: Family,	   
     networkAddress	:: NetworkAddr
   } deriving (Read, Show)
INSTANCE_TYPEABLE0(NetworkEntry,networkEntryTc,"NetworkEntry")
instance Storable NetworkEntry where
   sizeOf    _ = 20
   alignment _ = alignment (undefined :: CInt) 
   peek p = do
        n_name         <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p >>= peekCString
        n_aliases      <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p
                                >>= peekArray0 nullPtr
                                >>= mapM peekCString
        n_addrtype     <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p
        n_net          <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p
        return (NetworkEntry {
                        networkName      = n_name,
                        networkAliases   = n_aliases,
                        networkFamily    = unpackFamily (fromIntegral 
                                                        (n_addrtype :: CInt)),
                        networkAddress   = n_net
                })
   poke p = error "Storable.poke(BSD.NetEntry) not implemented"
getNetworkByName :: NetworkName -> IO NetworkEntry
getNetworkByName name = withLock $ do
 withCString name $ \ name_cstr -> do
  throwNoSuchThingIfNull "getNetworkByName" "no such network entry"
    $ trySysCall $ c_getnetbyname name_cstr
  >>= peek
foreign import ccall unsafe "getnetbyname" 
   c_getnetbyname  :: CString -> IO (Ptr NetworkEntry)
getNetworkByAddr :: NetworkAddr -> Family -> IO NetworkEntry
getNetworkByAddr addr family = withLock $ do
 throwNoSuchThingIfNull "getNetworkByAddr" "no such network entry"
   $ trySysCall $ c_getnetbyaddr addr (packFamily family)
 >>= peek
foreign import ccall unsafe "getnetbyaddr" 
   c_getnetbyaddr  :: NetworkAddr -> CInt -> IO (Ptr NetworkEntry)
getNetworkEntry :: IO NetworkEntry
getNetworkEntry = withLock $ do
 throwNoSuchThingIfNull "getNetworkEntry" "no more network entries"
          $ trySysCall $ c_getnetent
 >>= peek
foreign import ccall unsafe "getnetent" c_getnetent :: IO (Ptr NetworkEntry)
setNetworkEntry :: Bool -> IO ()
setNetworkEntry flg = withLock $ trySysCall $ c_setnetent (fromBool flg)
foreign import ccall unsafe "setnetent" c_setnetent :: CInt -> IO ()
endNetworkEntry :: IO ()
endNetworkEntry = withLock $ trySysCall $ c_endnetent
foreign import ccall unsafe "endnetent" c_endnetent :: IO ()
getNetworkEntries :: Bool -> IO [NetworkEntry]
getNetworkEntries stayOpen = do
  setNetworkEntry stayOpen
  getEntries (getNetworkEntry) (endNetworkEntry)
lock :: MVar ()
lock = unsafePerformIO $ newMVar ()
withLock :: IO a -> IO a
withLock act = withMVar lock (\_ -> act)
getHostName :: IO HostName
getHostName = do
  let size = 256
  allocaArray0 size $ \ cstr -> do
    throwSocketErrorIfMinus1_ "getHostName" $ c_gethostname cstr (fromIntegral size)
    peekCString cstr
foreign import CALLCONV unsafe "gethostname" 
   c_gethostname :: CString -> CSize -> IO CInt
getEntries :: IO a  
           -> IO () 
	   -> IO [a]
getEntries getOne atEnd = loop
  where
    loop = do
      vv <- catch (liftM Just getOne) ((const.return) Nothing)
      case vv of
        Nothing -> return []
        Just v  -> loop >>= \ vs -> atEnd >> return (v:vs)
trySysCall act = act
throwNoSuchThingIfNull :: String -> String -> IO (Ptr a) -> IO (Ptr a)
throwNoSuchThingIfNull loc desc act = do
  ptr <- act
  if (ptr == nullPtr)
   then ioError (ioeSetErrorString (mkIOError NoSuchThing loc Nothing Nothing) desc)
   else return ptr