Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Path.Extended
Synopsis
- data Location base = Location {
- locPath :: LocationPath base
- locQueryParams :: [QueryParam]
- locFragment :: Maybe String
- data LocationPath base
- type QueryParam = (String, Maybe String)
- class ToPath sym base type' | sym -> base type' where
- class ToLocation sym base | sym -> base where
- toLocation :: sym -> Location base
- class FromPath sym base type' | sym -> base type' where
- class FromLocation sym base | sym -> base where
- parseLocation :: Location base -> Either String sym
- fromDir :: Path base Dir -> Location base
- fromFile :: Path base File -> Location base
- prependAbs :: Path Abs Dir -> Location Abs -> Location Abs
- prependRel :: Path Rel Dir -> Location Rel -> Location Rel
- setQuery :: [QueryParam] -> Location base -> Location base
- addQuery :: QueryParam -> Location base -> Location base
- (<&>) :: Location base -> QueryParam -> Location base
- addQueries :: [QueryParam] -> Location base -> Location base
- delQuery :: Location base -> Location base
- getQuery :: Location base -> [QueryParam]
- setFragment :: Maybe String -> Location base -> Location base
- addFragment :: String -> Location base -> Location base
- (<#>) :: Location base -> String -> Location base
- delFragment :: Location base -> Location base
- getFragment :: Location base -> Maybe String
- locationAbsParser :: Parser (Location Abs)
- locationRelParser :: Parser (Location Rel)
- printLocation :: Location base -> Text
Types
A location for some base and type - internally uses Path
.
Constructors
Location | |
Fields
|
Instances
Generic (Location base) Source # | |
Show (Location base) Source # | |
Eq (Location base) Source # | |
Ord (Location base) Source # | |
Defined in Path.Extended Methods compare :: Location base -> Location base -> Ordering # (<) :: Location base -> Location base -> Bool # (<=) :: Location base -> Location base -> Bool # (>) :: Location base -> Location base -> Bool # (>=) :: Location base -> Location base -> Bool # | |
type Rep (Location base) Source # | |
Defined in Path.Extended type Rep (Location base) = D1 ('MetaData "Location" "Path.Extended" "path-extra-0.3.1-Ao34vTbjrES4HuXcyPNMTw" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) (S1 ('MetaSel ('Just "locPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LocationPath base)) :*: (S1 ('MetaSel ('Just "locQueryParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QueryParam]) :*: S1 ('MetaSel ('Just "locFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) |
data LocationPath base Source #
Instances
Classes
class ToPath sym base type' | sym -> base type' where Source #
Convenience typeclass for symbolic, stringless routes - make an instance for your own data type to use your constructors as route-referencing symbols.
class ToLocation sym base | sym -> base where Source #
Convenience typeclass for symbolic, stringless routes - make an instance for your own data type to use your constructors as route-referencing symbols.
Methods
toLocation :: sym -> Location base Source #
class FromLocation sym base | sym -> base where Source #
Combinators
Path
Query Parameters
addQueries :: [QueryParam] -> Location base -> Location base Source #
getQuery :: Location base -> [QueryParam] Source #
Fragment
delFragment :: Location base -> Location base Source #
Parser & Printer
printLocation :: Location base -> Text Source #