{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE CPP #-}
module System.OsString.Internal.Types.Compat
( WindowsString(..)
, pattern WS
, unWS
, PosixString(..)
, unPS
, pattern PS
, PlatformString
, WindowsChar(..)
, unWW
, pattern WW
, PosixChar(..)
, unPW
, pattern PW
, PlatformChar
, OsString(..)
, OsChar(..)
, coercionToPlatformTypes
) where
#if MIN_VERSION_filepath(1,5,0)
import "os-string" System.OsString.Internal.Types
# if MIN_VERSION_os_string(2,0,2)
# else
# define COERCE_MANUAL
# endif
#else
import "filepath" System.OsString.Internal.Types
#define COERCE_MANUAL
#endif
#ifdef COERCE_MANUAL
import Data.Type.Coercion (Coercion(..))
coercionToPlatformTypes
:: Either
(Coercion OsChar WindowsChar, Coercion OsString WindowsString)
(Coercion OsChar PosixChar, Coercion OsString PosixString)
# if defined(mingw32_HOST_OS)
coercionToPlatformTypes :: Either
(Coercion OsChar WindowsChar, Coercion OsString WindowsString)
(Coercion OsChar PosixChar, Coercion OsString PosixString)
coercionToPlatformTypes = (Coercion OsChar WindowsChar, Coercion OsString WindowsString)
-> Either
(Coercion OsChar WindowsChar, Coercion OsString WindowsString)
(Coercion OsChar PosixChar, Coercion OsString PosixString)
forall a b. a -> Either a b
Left (Coercion OsChar WindowsChar
forall {k} (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion, Coercion OsString WindowsString
forall {k} (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion)
# else
coercionToPlatformTypes = Right (Coercion, Coercion)
# endif
#endif