urlpath: Painfully simple URL deployment.

[ bsd3, data, library, web ] [ Propose Tags ]

Please see the README on Github at https://github.com/githubuser/urlpath#readme


[Skip to Readme]

Modules

[Last Documentation]

  • Data
    • Data.Url

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.0.1, 0.0.2, 0.0.3, 0.0.4, 0.0.5, 0.0.6, 0.1, 0.1.0.1, 0.2, 1.0.0, 1.1.0, 2.0.0, 2.1.0, 3.0.0, 3.1.0, 3.1.1, 3.2.0, 3.2.1, 3.2.1.1, 3.3.0, 4.0.0, 4.0.0.1, 4.1.0, 4.2.0, 5.0.0, 5.0.0.1, 6.0.0, 6.0.1, 6.0.2, 6.0.3, 6.0.4, 7.0.0, 7.0.1, 7.0.2, 7.1.0, 8.0.0, 8.0.1, 8.1.0, 8.2.0, 9.0.0, 9.0.0.1, 9.0.1, 10.0.0, 11.0.0, 11.0.1, 11.0.2 (info)
Dependencies attoparsec-uri (>=0.0.4), base (>=4.8 && <5), exceptions, mmorph, monad-control, monad-control-aligned, monad-logger, mtl, path-extra (>=0.0.6), resourcet, split, strict, text, transformers, transformers-base, vector [details]
License BSD-3-Clause
Copyright Copyright (c) 2018 Athan Clark
Author Athan Clark
Maintainer athan.clark@localcooking.com
Category Web, Data
Home page https://github.com/athanclark/urlpath#readme
Bug tracker https://github.com/athanclark/urlpath/issues
Source repo head: git clone https://github.com/athanclark/urlpath
Uploaded by athanclark at 2018-04-11T04:42:14Z
Distributions LTSHaskell:11.0.2, Stackage:11.0.2
Reverse Dependencies 4 direct, 1 indirect [details]
Downloads 20703 total (102 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2021-06-02 [all 2 reports]

Readme for urlpath-8.1.0

[back to package description]

urlpath

Build Status Coverage Status Chat Room MIT License Hackage Waffle Issues

Dirt-simple, embarrassing, horribly unimaginative URL combinator library for Haskell.

Installation

λ> cabal install urlpath

Usage

You can use the combinators purely, if you're into that:

λ> expandRelative $ "foo.php" <?> ("key1","bar") <&> ("key2","baz")

↪ "foo.asp?key1=bar&key2=baz"

Or you can use them with a configurable root, via the Reader monad:

λ> runReader
     (runAbsoluteUrl $ url $ "foo.asp" <?> ("key1","bar") <&> ("key2","baz"))
     "http://example.com"

↪ "http://example.com/foo.asp?key1=bar&key2=baz"

url puts the UrlString in a MonadReader that we can use for applying our⋅ host. We use different monads for different deployment schemes (currently we⋅ have 3 - RelativeUrlT, GroundedUrlT, and AbsoluteUrlT), which we can⋅ integrate in different libraries, like Lucid:

λ> (runAbsoluteUrl $ renderTextT $ do
     foo <- lift $ url $ "foo" <?> ("bar","baz")
     script_ [src_ foo] "" )
   ) "example.com"

↪ "<script src=\"example.com/foo?bar=baz\"></script>"

and, in Scotty:

main :: IO ()
main = scottyT 3000
    rootConf
    rootConf
    run

  where
    rootConf = flip runAbsoluteT "http://example.com"

    run :: ( MonadIO m
           , MonadReader T.Text m
           , Url T.Text m ) =>
           ScottyT LT.Text m ()
    run = get "/" $ do
      path <- lift $ url $ "foo" <?> ("bar","baz")
      text $ LT.fromStrict path
λ> curl localhost:3000/
↪ "http://example.com/foo?bar=baz"

How to run tests

λ> cabal install hspec --enable-tests && cabal test --show-details=always

Contributing

I would prefer it that any inquiries and questions go to the Gitter Chat room, while any suggestions, complaints, or requests go in the GitHub Issues / Waffle Dashboard. All ideas are welcome! (Except really gross ones. I've got limits.)