bpath-0.1.0: A minimal typed unix path library
Safe HaskellNone
LanguageHaskell2010

Path.Internal

Synopsis

Documentation

data PathSeg Source #

Constructors

Parent 
PathSeg !ByteString 

Instances

Instances details
Eq PathSeg Source # 
Instance details

Defined in Path.Internal

Methods

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

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

Show PathSeg Source # 
Instance details

Defined in Path.Internal

Generic PathSeg Source # 
Instance details

Defined in Path.Internal

Associated Types

type Rep PathSeg :: Type -> Type #

Methods

from :: PathSeg -> Rep PathSeg x #

to :: Rep PathSeg x -> PathSeg #

Lift PathSeg Source # 
Instance details

Defined in Path.Internal

Methods

lift :: PathSeg -> Q Exp #

liftTyped :: PathSeg -> Q (TExp PathSeg) #

type Rep PathSeg Source # 
Instance details

Defined in Path.Internal

type Rep PathSeg = D1 ('MetaData "PathSeg" "Path.Internal" "bpath-0.1.0-inplace" 'False) (C1 ('MetaCons "Parent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PathSeg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

data PathType Source #

Constructors

Abs 
Rel 

Instances

Instances details
Eq PathType Source # 
Instance details

Defined in Path.Internal

Show PathType Source # 
Instance details

Defined in Path.Internal

newtype Path (t :: PathType) Source #

A canonicalized file path

Constructors

Path 

Fields

Instances

Instances details
Lift (Path t :: Type) Source # 
Instance details

Defined in Path.Internal

Methods

lift :: Path t -> Q Exp #

liftTyped :: Path t -> Q (TExp (Path t)) #

Eq (Path t) Source # 
Instance details

Defined in Path.Internal

Methods

(==) :: Path t -> Path t -> Bool #

(/=) :: Path t -> Path t -> Bool #

Show (Path t) Source # 
Instance details

Defined in Path.Internal

Methods

showsPrec :: Int -> Path t -> ShowS #

show :: Path t -> String #

showList :: [Path t] -> ShowS #

Generic (Path t) Source # 
Instance details

Defined in Path.Internal

Associated Types

type Rep (Path t) :: Type -> Type #

Methods

from :: Path t -> Rep (Path t) x #

to :: Rep (Path t) x -> Path t #

type Rep (Path t) Source # 
Instance details

Defined in Path.Internal

type Rep (Path t) = D1 ('MetaData "Path" "Path.Internal" "bpath-0.1.0-inplace" 'True) (C1 ('MetaCons "Path" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq PathSeg))))

hush :: Either a b -> Maybe b Source #

(</>) :: Path t -> Path 'Rel -> Path t Source #

parent :: Path t -> Path t Source #