descriptive: Self-describing consumers/parsers; forms, cmd-line args, JSON, etc.

[ bsd3, library, parsing ] [ Propose Tags ]

Self-describing consumers/parsers. See the README.md for more information. It is currently EXPERIMENTAL.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0.0, 0.0.1, 0.0.2, 0.1.0, 0.1.1, 0.2.0, 0.3.0, 0.3.1, 0.4.0, 0.4.1, 0.4.2, 0.4.3, 0.5.0, 0.6.0, 0.7.0, 0.8.0, 0.9.0, 0.9.1, 0.9.2, 0.9.3, 0.9.4, 0.9.5
Change log CHANGELOG
Dependencies aeson, base (>=4.5 && <4.11), bifunctors, containers (>=0.5), mtl, text, transformers [details]
License BSD-3-Clause
Copyright 2015 Chris Done
Author Chris Done
Maintainer chrisdone@gmail.com
Revised Revision 4 made by HerbertValerioRiedel at 2018-08-31T09:35:28Z
Category Parsing
Home page https://github.com/chrisdone/descriptive
Uploaded by ChrisDone at 2015-01-18T16:29:50Z
Distributions Debian:0.9.5
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 30051 total (52 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-01-18 [all 1 reports]

Readme for descriptive-0.2.0

[back to package description]

descriptive

Self-describing consumers/parsers

Haddocks

There are a variety of Haskell libraries which are implementable through a common interface: self-describing parsers:

  • A formlet is a self-describing parser.
  • A regular old text parser can be self-describing.
  • A command-line options parser is a self-describing parser.
  • A MUD command set is a self-describing parser.
  • A JSON API can be a self-describing parser.

Consumption is done in this data type:

data Consumer s d a

To make a consumer, this combinator is used:

consumer :: (s -> (Description d,s))
         -> (s -> (Result (Description d) a,s))
         -> Consumer s d a

The first argument generates a description based on some state. The state is determined by whatever use-case you have. The second argument parses from the state, which could be a stream of bytes, a list of strings, a Map, a Vector, etc. You may or may not decide to modify the state during generation of the description and during parsing.

To use a consumer or describe what it does, these are used:

consume :: Consumer s d a -> s -> Result (Description d) a
describe :: Consumer s d a -> s -> Description d

A description is like this:

data Description a
  = Unit !a
  | Bounded !Integer !Bound !(Description a)
  | And !(Description a) !(Description a)
  | Sequence [Description a]
  | Wrap a (Description a)
  | None
  deriving (Show)

You configure the a for your use-case, but the rest is generatable by the library. Afterwards, you can make your own pretty printing function, which may be to generate an HTML form, to generate a commandline --help screen, a man page, API docs for your JSON parser, a text parsing grammar, etc. For example:

describeParser :: Description Text -> Text
describeForm :: Description (Html ()) -> Html ()
describeArgs :: Description CmdArgs -> Text

See below for some examples of this library.

Parsing characters

See Descriptive.Char.

λ> describe (many (char 'k') <> string "abc") mempty
And (Bounded 0 UnlimitedBound (Unit "k"))
    (Sequence [Unit "a",Sequence [Unit "b",Sequence [Unit "c",Sequence []]]])
λ> consume (many (char 'k') <> string "abc") "kkkabc"
(Succeeded "kkkabc")
λ> consume (many (char 'k') <> string "abc") "kkkab"
(Failed (Unit "a character"))
λ> consume (many (char 'k') <> string "abc") "kkkabj"
(Failed (Unit "c"))

Validating forms with named inputs

See Descriptive.Form.

λ> describe ((,) <$> input "username" <*> input "password") mempty
(And (Unit (Input "username")) (Unit (Input "password")),fromList [])

λ> consume ((,) <$>
            input "username" <*>
            input "password")
           (M.fromList [("username","chrisdone"),("password","god")])
(Succeeded ("chrisdone","god")
,fromList [("password","god"),("username","chrisdone")])

Conditions on two inputs:

login =
  validate "confirmed password (entered the same twice)"
           (\(x,y) ->
              if x == y
                 then Just y
                 else Nothing)
           ((,) <$>
            input "password" <*>
            input "password2") <|>
  input "token"
λ> consume login (M.fromList [("password2","gob"),("password","gob")])
Succeeded "gob"
λ> consume login (M.fromList [("password2","gob"),("password","go")])
Continued (And (Wrap (Constraint "confirmed password (entered the same twice)")
                     (And (Unit (Input "password"))
                          (Unit (Input "password2"))))
               (Unit (Input "token")))
λ> consume login (M.fromList [("password2","gob"),("password","go"),("token","woot")])
Succeeded "woot"

Validating forms with auto-generated input indexes

See Descriptive.Formlet.

λ> describe ((,) <$> indexed <*> indexed)
            (FormletState mempty 0)
And (Unit (Index 0))
    (Unit (Index 1))
              ,formletIndex = 2})
λ> consume ((,) <$> indexed <*> indexed)
           (FormletState (M.fromList [(0,"chrisdone"),(1,"god")]) 0)
Succeeded ("chrisdone","god")
λ> consume ((,) <$> indexed <*> indexed)
           (FormletState (M.fromList [(0,"chrisdone")]) 0)
Failed (Unit (Index 1))

Parsing command-line options

See Descriptive.Options.

server =
  ((,,,) <$>
   constant "start" <*>
   anyString "SERVER_NAME" <*>
   flag "dev" "Enable dev mode?" <*>
   arg "port" "Port to listen on")
λ> describe server []
And (And (And (Unit (Constant "start"))
               (Unit (AnyString "SERVER_NAME")))
          (Unit (Flag "dev" "Enable dev mode?")))
     (Unit (Arg "port" "Port to listen on"))
λ> consume server ["start","any","--port","1234","--dev"]
Succeeded ("start","any",True,"1234")
λ> consume server ["start","any","--port","1234"]
Succeeded ("start","any",False,"1234")
λ>
λ> textDescription (describe server [])
"start SERVER_NAME [--dev] --port <...>"

Self-documenting JSON parser

See Descriptive.JSON.

-- | Submit a URL to reddit.
data Submission =
  Submission {submissionToken :: !Integer
             ,submissionTitle :: !Text
             ,submissionComment :: !Text
             ,submissionSubreddit :: !Integer}
  deriving (Show)

submission :: Consumer Value Doc Submission
submission =
  obj "Submission"
      (Submission
        <$> key "token" (integer "Submission token; see the API docs")
        <*> key "title" (string "Submission title")
        <*> key "comment" (string "Submission comment")
        <*> key "subreddit" (integer "The ID of the subreddit"))

sample :: Value
sample =
  toJSON (object
            ["token" .= 123
            ,"title" .= "Some title"
            ,"comment" .= "This is good"
            ,"subreddit" .= 234214])

badsample :: Value
badsample =
  toJSON (object
            ["token" .= 123
            ,"title" .= "Some title"
            ,"comment" .= 123
            ,"subreddit" .= 234214])
λ> describe submission (toJSON ())
Wrap (Struct "Submission")
      (And (And (And (Wrap (Key "token")
                           (Unit (Integer "Submission token; see the API docs")))
                     (Wrap (Key "title")
                           (Unit (Text "Submission title"))))
                (Wrap (Key "comment")
                      (Unit (Text "Submission comment"))))
           (Wrap (Key "subreddit")
                 (Unit (Integer "The ID of the subreddit"))))


λ> consume submission sample
Succeeded (Submission {submissionToken = 123
                   ,submissionTitle = "Some title"
                   ,submissionComment = "This is good"
                   ,submissionSubreddit = 234214})
λ> consume submission badsample
Failed (Wrap (Struct "Submission")
            (Wrap (Key "comment")
                  (Unit (Text "Submission comment"))))

The bad sample yields an informative message that:

  • The error is in the Submission object.
  • The key "comment".
  • The type of that key should be a String and it should be a Submission comment (or whatever invariants you'd like to mention).

Parsing Attempto Controlled English for MUD commands

TBA. Will use this package.

With ACE you can parse into:

parsed complV "<distrans-verb> a <noun> <prep> a <noun>" ==
Succeeded (ComplVDisV (DistransitiveV "<distrans-verb>")
                  (ComplNP (NPCoordUnmarked (UnmarkedNPCoord anoun Nothing)))
                  (ComplPP (PP (Preposition "<prep>")
                               (NPCoordUnmarked (UnmarkedNPCoord anoun Nothing)))))

Which I can then further parse with descriptive to yield descriptions like:

<verb-phrase> [<noun-phrase> ..]

Or similar. Which would be handy for a MUD so that a user can write:

Put the sword on the table.

Producing questions and consuming the answers in Haskell

TBA. Will be a generalization of this type.

It is a library which I am working on in parallel which will ask the user questions and then validate the answers. Current output is like this:

λ> describe (greaterThan 4 (integerExpr (parse id expr exercise)))
an integer greater than 4
λ> eval (greaterThan 4 (integerExpr (parse id expr exercise))) $(someHaskell "x = 1")
Left expected an expression, but got a declaration
λ> eval (greaterThan 4 (integerExpr (parse id expr exercise))) $(someHaskell "x")
Left expected an integer, but got an expression
λ> eval (greaterThan 4 (integerExpr (parse id expr exercise))) $(someHaskell "3")
Left expected an integer greater than 4
λ> eval (greaterThan 4 (integerExpr (parse id expr exercise))) $(someHaskell "5")
Right 5

This is also couples description with validation, but I will probably rewrite it with this descriptive library.