{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UnliftedFFITypes #-}

module System.AbstractFilePath.Internal where

import {-# SOURCE #-} System.AbstractFilePath
    ( isValid )
import System.AbstractFilePath.Types
import System.OsString.Internal
import qualified System.OsString.Internal as OS
import System.OsString.Internal.Types

import Control.Monad.Catch
    ( MonadThrow )
import Data.ByteString
    ( ByteString )
import Language.Haskell.TH
import Language.Haskell.TH.Quote
    ( QuasiQuoter (..) )
import Language.Haskell.TH.Syntax
    ( Lift (..), lift )
import System.IO
    ( TextEncoding )
#ifndef WINDOWS
import System.AbstractFilePath.Data.ByteString.Short.Decode
    (
      UnicodeException (..)
    )
#endif



-- | Total Unicode-friendly encoding.
--
-- On windows this encodes as UTF16, which is expected.
-- On unix this encodes as UTF8, which is a good guess.
toAbstractFilePath :: String -> AbstractFilePath
toAbstractFilePath :: String -> AbstractFilePath
toAbstractFilePath = String -> AbstractFilePath
toOsString


-- | Like 'toAbstractFilePath', except on unix this uses the current
-- locale for encoding instead of always UTF8.
--
-- Looking up the locale requires IO. If you're not worried about calls
-- to 'setFileSystemEncoding', then 'unsafePerformIO' may be feasible.
toAbstractFilePathIO :: String -> IO AbstractFilePath
toAbstractFilePathIO :: String -> IO AbstractFilePath
toAbstractFilePathIO = String -> IO AbstractFilePath
toOsStringIO


-- | Partial unicode friendly decoding.
--
-- On windows this decodes as UTF16 (which is the expected filename encoding).
-- On unix this decodes as UTF8 (which is a good guess). Note that
-- filenames on unix are encoding agnostic char arrays.
--
-- Throws a 'UnicodeException' if decoding fails.
--
-- Note that filenames of different encodings may have the same @String@
-- representation, although they're not the same byte-wise.
fromAbstractFilePath :: MonadThrow m => AbstractFilePath -> m String
fromAbstractFilePath :: AbstractFilePath -> m String
fromAbstractFilePath = AbstractFilePath -> m String
forall (m :: * -> *). MonadThrow m => AbstractFilePath -> m String
fromOsString

-- | Like 'fromAbstractFilePath', except on unix this uses the provided
-- 'TextEncoding' for decoding.
--
-- On windows, the TextEncoding parameter is ignored.
fromAbstractFilePathEnc :: AbstractFilePath -> TextEncoding -> Either UnicodeException String
fromAbstractFilePathEnc :: AbstractFilePath -> TextEncoding -> Either UnicodeException String
fromAbstractFilePathEnc = AbstractFilePath -> TextEncoding -> Either UnicodeException String
fromOsStringEnc

-- | Like 'fromAbstractFilePath', except on unix this uses the current
-- locale for decoding instead of always UTF8.
--
-- Looking up the locale requires IO. If you're not worried about calls
-- to 'setFileSystemEncoding', then 'unsafePerformIO' may be feasible.
--
-- Throws 'UnicodeException' if decoding fails.
fromAbstractFilePathIO :: AbstractFilePath -> IO String
fromAbstractFilePathIO :: AbstractFilePath -> IO String
fromAbstractFilePathIO = AbstractFilePath -> IO String
fromOsStringIO


-- | Constructs an @AbstractFilePath@ from a ByteString.
--
-- On windows, this ensures valid UTF16, on unix it is passed unchanged/unchecked.
--
-- Throws 'UnicodeException' on invalid UTF16 on windows.
bsToAFP :: MonadThrow m
        => ByteString
        -> m AbstractFilePath
bsToAFP :: ByteString -> m AbstractFilePath
bsToAFP = ByteString -> m AbstractFilePath
forall (m :: * -> *).
MonadThrow m =>
ByteString -> m AbstractFilePath
OS.bsToOsString


mkAbstractFilePath :: ByteString -> Q Exp
mkAbstractFilePath :: ByteString -> Q Exp
mkAbstractFilePath ByteString
bs = 
  case ByteString -> Maybe AbstractFilePath
forall (m :: * -> *).
MonadThrow m =>
ByteString -> m AbstractFilePath
bsToAFP ByteString
bs of
    Just AbstractFilePath
afp' ->
      if AbstractFilePath -> Bool
isValid AbstractFilePath
afp'
      then AbstractFilePath -> Q Exp
forall t. Lift t => t -> Q Exp
lift AbstractFilePath
afp'
      else String -> Q Exp
forall a. HasCallStack => String -> a
error String
"invalid filepath"
    Maybe AbstractFilePath
Nothing -> String -> Q Exp
forall a. HasCallStack => String -> a
error String
"invalid encoding"

-- | QuasiQuote an 'AbstractFilePath'. This accepts Unicode characters
-- and encodes as UTF-8 on unix and UTF-16 on windows. Runs 'filepathIsValid'
-- on the input.
afp :: QuasiQuoter
afp :: QuasiQuoter
afp = (ByteString -> Q Exp) -> QuasiQuoter
qq ByteString -> Q Exp
mkAbstractFilePath


unpackAFP :: AbstractFilePath -> [OsChar]
unpackAFP :: AbstractFilePath -> [OsChar]
unpackAFP = AbstractFilePath -> [OsChar]
unpackOsString


packAFP :: [OsChar] -> AbstractFilePath
packAFP :: [OsChar] -> AbstractFilePath
packAFP = [OsChar] -> AbstractFilePath
packOsString