module System.Win32.DHCP.Reservation
    ( Mapping (..)
    , Reservation (..)
    , reservation
    ) where
import Data.Ip
import Data.Mac
import Import
import System.Win32.DHCP.CLIENT_UID
import System.Win32.DHCP.DhcpStructure
import System.Win32.DHCP.Types (ClientType)
data Reservation = Reservation
    { reservationMapping :: !Mapping
    , reservationType    :: !ClientType
    } deriving (Eq)
data Mapping = Mapping
    { mappingMac :: !Mac
    , mappingIp  :: !Ip
    } deriving (Eq, Ord)
reservation :: DhcpStructure Reservation
reservation = DhcpStructure
    { peekDhcp = peekReservation
    , freeDhcpChildren = freeReservation
    , withDhcp' = withReservation'
    
    
    , sizeDhcp = 10
    }
peekReservation :: Ptr Reservation -> IO Reservation
peekReservation ptr = do
    pCuid <- peek $ ppCuid ptr
    mac <- macCuidDrop5 <$> peekDhcp clientUid pCuid
    addr <- peek pAddress
    clientType <- peekByteOff (castPtr ptr) 8
    return $ Reservation (Mapping mac addr) clientType
  where
    pAddress = castPtr ptr :: Ptr Ip
freeReservation :: (forall x. Ptr x -> IO ()) -> Ptr Reservation -> IO ()
freeReservation freefunc ptr = do
    freeDhcp clientUid freefunc `scrubbing_` ppCuid ptr
ppCuid :: Ptr Reservation -> Ptr (Ptr CLIENT_UID)
ppCuid p = plusPtr p 4
pClientType :: Ptr Reservation -> Ptr ClientType
pClientType p = plusPtr p 8
withReservation' :: Reservation -> Ptr Reservation
    -> IO r -> IO r
withReservation' (Reservation (Mapping mac address) clientType) ptr f =
    withMac mac $ \pCuid -> do
    poke (castPtr ptr) address
    ppCuid ptr `poke` pCuid
    pClientType ptr `poke` clientType
    f