filepath-1.4.100.0: Library for manipulating FilePaths in a cross platform way.
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.OsString.Internal.Types

Synopsis

Documentation

newtype WindowsString Source #

Commonly used windows string as wide character bytes.

Instances

Instances details
Monoid WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Semigroup WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Generic WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsString :: Type -> Type Source #

Show WindowsString Source #

Decodes as UCS-2.

Instance details

Defined in System.OsString.Internal.Types

NFData WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: WindowsString -> () Source #

Eq WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Lift WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: Quote m => WindowsString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => WindowsString -> Code m WindowsString Source #

type Rep WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsString = D1 ('MetaData "WindowsString" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "WindowsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

pattern WS :: ShortByteString -> WindowsString Source #

Just a short bidirectional synonym for WindowsString constructor.

newtype PosixString Source #

Commonly used Posix string as uninterpreted char[] array.

Instances

Instances details
Monoid PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Semigroup PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Generic PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixString :: Type -> Type Source #

Show PosixString Source #

Prints the raw bytes without decoding.

Instance details

Defined in System.OsString.Internal.Types

NFData PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: PosixString -> () Source #

Eq PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Lift PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: Quote m => PosixString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => PosixString -> Code m PosixString Source #

type Rep PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

pattern PS :: ShortByteString -> PosixString Source #

Just a short bidirectional synonym for PosixString constructor.

newtype WindowsChar Source #

Constructors

WindowsChar 

Instances

Instances details
Generic WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsChar :: Type -> Type Source #

Show WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: WindowsChar -> () Source #

Eq WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

pattern WW :: Word16 -> WindowsChar Source #

Just a short bidirectional synonym for WindowsChar constructor.

newtype PosixChar Source #

Constructors

PosixChar 

Fields

Instances

Instances details
Generic PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixChar :: Type -> Type Source #

Show PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: PosixChar -> () Source #

Eq PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

pattern PW :: Word8 -> PosixChar Source #

Just a short bidirectional synonym for PosixChar constructor.

newtype OsString Source #

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.

Constructors

OsString 

Instances

Instances details
Monoid OsString Source #

"String-Concatenation" for OsString. This is not the same as (</>).

Instance details

Defined in System.OsString.Internal.Types

Semigroup OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Generic OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString :: Type -> Type Source #

Show OsString Source #

On windows, decodes as UCS-2. On unix prints the raw bytes without decoding.

Instance details

Defined in System.OsString.Internal.Types

NFData OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsString -> () Source #

Eq OsString Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Ord OsString Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Lift OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: Quote m => OsString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => OsString -> Code m OsString Source #

type Rep OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

newtype OsChar Source #

Newtype representing a code unit.

On Windows, this is restricted to two-octet codepoints Word16, on POSIX one-octet (Word8).

Constructors

OsChar 

Instances

Instances details
Generic OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar :: Type -> Type Source #

Show OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsChar -> () Source #

Eq OsChar Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: OsChar -> OsChar -> Bool #

(/=) :: OsChar -> OsChar -> Bool #

Ord OsChar Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar)))