{-# LANGUAGE CPP #-}
{- |
   Module      :  System.Win32.HardLink
   Copyright   :  2013 shelarcy
   License     :  BSD-style

   Maintainer  :  shelarcy@gmail.com
   Stability   :  Provisional
   Portability :  Non-portable (Win32 API)

   Handling hard link using Win32 API. [NTFS only]

   Note: You should worry about file system type when use this module's function in your application:

     * NTFS only supprts this functionality.

     * ReFS doesn't support hard link currently.
-}
module System.Win32.WindowsString.HardLink
  ( createHardLink
  , createHardLink'
  ) where

import System.Win32.HardLink.Internal
import System.Win32.WindowsString.File   ( failIfFalseWithRetry_ )
import System.Win32.WindowsString.String ( withTString )
import System.Win32.WindowsString.Types  ( nullPtr )
import System.OsPath.Windows

#include "windows_cconv.h"

-- | NOTE: createHardLink is /flipped arguments/ to provide compatibility for Unix.

-- 

-- If you want to create hard link by Windows way, use 'createHardLink'' instead.

createHardLink :: WindowsPath -- ^ Target file path

               -> WindowsPath -- ^ Hard link name

               -> IO ()
createHardLink :: WindowsPath -> WindowsPath -> IO ()
createHardLink = (WindowsPath -> WindowsPath -> IO ())
-> WindowsPath -> WindowsPath -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip WindowsPath -> WindowsPath -> IO ()
createHardLink'

createHardLink' :: WindowsPath -- ^ Hard link name

                -> WindowsPath -- ^ Target file path

                -> IO ()
createHardLink' :: WindowsPath -> WindowsPath -> IO ()
createHardLink' WindowsPath
link WindowsPath
target =
   WindowsPath -> (LPTSTR -> IO ()) -> IO ()
forall a. WindowsPath -> (LPTSTR -> IO a) -> IO a
withTString WindowsPath
target ((LPTSTR -> IO ()) -> IO ()) -> (LPTSTR -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LPTSTR
c_target ->
   WindowsPath -> (LPTSTR -> IO ()) -> IO ()
forall a. WindowsPath -> (LPTSTR -> IO a) -> IO a
withTString WindowsPath
link   ((LPTSTR -> IO ()) -> IO ()) -> (LPTSTR -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LPTSTR
c_link ->
        String -> IO Bool -> IO ()
failIfFalseWithRetry_ ([String] -> String
unwords [String
"CreateHardLinkW",WindowsPath -> String
forall a. Show a => a -> String
show WindowsPath
link,WindowsPath -> String
forall a. Show a => a -> String
show WindowsPath
target]) (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$
          LPTSTR -> LPTSTR -> LPSECURITY_ATTRIBUTES -> IO Bool
c_CreateHardLink LPTSTR
c_link LPTSTR
c_target LPSECURITY_ATTRIBUTES
forall a. Ptr a
nullPtr