Safe Haskell | None |
---|---|
Language | Haskell2010 |
System.OsPath.Types
Contents
Synopsis
- type OsPath = OsString
- type WindowsPath = WindowsString
- type PosixPath = PosixString
- type PlatformPath = PosixPath
- data WindowsString
- data PosixString
- data WindowsChar
- data PosixChar
- data OsString
- data OsChar
FilePath types
type OsPath = OsString Source #
Type representing filenames/pathnames.
This type doesn't add any guarantees over OsString
.
type WindowsPath = WindowsString Source #
Filepaths are wchar_t*
data on windows as passed to syscalls.
type PosixPath = PosixString Source #
Filepaths are char[]
data on unix as passed to syscalls.
type PlatformPath = PosixPath Source #
Ifdef around current platform (either WindowsPath
or PosixPath
).
OsString reexports
data WindowsString Source #
Commonly used windows string as wide character bytes.
Instances
data PosixString Source #
Commonly used Posix string as uninterpreted char[]
array.
Instances
NFData PosixString Source # | |||||
Defined in System.OsString.Internal.Types Methods rnf :: PosixString -> () Source # | |||||
Monoid PosixString Source # | |||||
Defined in System.OsString.Internal.Types Methods mempty :: PosixString # mappend :: PosixString -> PosixString -> PosixString # mconcat :: [PosixString] -> PosixString # | |||||
Semigroup PosixString Source # | |||||
Defined in System.OsString.Internal.Types Methods (<>) :: PosixString -> PosixString -> PosixString # sconcat :: NonEmpty PosixString -> PosixString # stimes :: Integral b => b -> PosixString -> PosixString # | |||||
Generic PosixString Source # | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Show PosixString Source # | Prints the raw bytes without decoding. | ||||
Defined in System.OsString.Internal.Types Methods showsPrec :: Int -> PosixString -> ShowS # show :: PosixString -> String # showList :: [PosixString] -> ShowS # | |||||
Eq PosixString Source # | |||||
Defined in System.OsString.Internal.Types | |||||
Ord PosixString Source # | |||||
Defined in System.OsString.Internal.Types Methods compare :: PosixString -> PosixString -> Ordering # (<) :: PosixString -> PosixString -> Bool # (<=) :: PosixString -> PosixString -> Bool # (>) :: PosixString -> PosixString -> Bool # (>=) :: PosixString -> PosixString -> Bool # max :: PosixString -> PosixString -> PosixString # min :: PosixString -> PosixString -> PosixString # | |||||
Lift PosixString Source # | |||||
Defined in System.OsString.Internal.Types Methods lift :: Quote m => PosixString -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PosixString -> Code m PosixString # | |||||
type Rep PosixString Source # | |||||
Defined in System.OsString.Internal.Types type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types" "os-string-2.0.7-3f43" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString))) |
data WindowsChar Source #
Instances
NFData WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types Methods rnf :: WindowsChar -> () Source # | |||||
Generic WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Show WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types Methods showsPrec :: Int -> WindowsChar -> ShowS # show :: WindowsChar -> String # showList :: [WindowsChar] -> ShowS # | |||||
Eq WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types | |||||
Ord WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types Methods compare :: WindowsChar -> WindowsChar -> Ordering # (<) :: WindowsChar -> WindowsChar -> Bool # (<=) :: WindowsChar -> WindowsChar -> Bool # (>) :: WindowsChar -> WindowsChar -> Bool # (>=) :: WindowsChar -> WindowsChar -> Bool # max :: WindowsChar -> WindowsChar -> WindowsChar # min :: WindowsChar -> WindowsChar -> WindowsChar # | |||||
type Rep WindowsChar Source # | |||||
Defined in System.OsString.Internal.Types type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types" "os-string-2.0.7-3f43" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) |
Instances
NFData PosixChar Source # | |||||
Defined in System.OsString.Internal.Types | |||||
Generic PosixChar Source # | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Show PosixChar Source # | |||||
Eq PosixChar Source # | |||||
Ord PosixChar Source # | |||||
type Rep PosixChar Source # | |||||
Defined in System.OsString.Internal.Types |
Newtype representing short operating system specific strings.
Internally this is either WindowsString
or PosixString
,
depending on the platform. Both use unpinned
ShortByteString
for efficiency.
The constructor is only exported via System.OsString.Internal.Types, since dealing with the internals isn't generally recommended, but supported in case you need to write platform specific code.
Instances
NFData OsString Source # | |||||
Defined in System.OsString.Internal.Types | |||||
Monoid OsString Source # | "String-Concatenation" for | ||||
Semigroup OsString Source # | |||||
Generic OsString Source # | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Show OsString Source # | On windows, decodes as UCS-2. On unix prints the raw bytes without decoding. | ||||
Eq OsString Source # | Byte equality of the internal representation. | ||||
Ord OsString Source # | Byte ordering of the internal representation. | ||||
Defined in System.OsString.Internal.Types | |||||
Lift OsString Source # | |||||
type Rep OsString Source # | |||||
Defined in System.OsString.Internal.Types type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "os-string-2.0.7-3f43" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString))) |
Newtype representing a code unit.
On Windows, this is restricted to two-octet codepoints Word16
,
on POSIX one-octet (Word8
).
Instances
NFData OsChar Source # | |||||
Defined in System.OsString.Internal.Types | |||||
Generic OsChar Source # | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Show OsChar Source # | |||||
Eq OsChar Source # | Byte equality of the internal representation. | ||||
Ord OsChar Source # | Byte ordering of the internal representation. | ||||
type Rep OsChar Source # | |||||
Defined in System.OsString.Internal.Types type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "os-string-2.0.7-3f43" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar))) |