katydid: A haskell implementation of Katydid

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

A haskell implementation of Katydid

This includes:

  • Relapse, a validation Language

  • Parsers for JSON, XML and an abstraction for trees

You should only need the following modules:

  • The Relapse module is used for validation.

  • The Json and XML modules are used to create Json and XML trees that can be validated.

If you want to implement your own parser then you can look at the Parsers module


[Skip to Readme]

Modules

[Last Documentation]

  • Ast
  • Derive
  • Expr
  • Exprs
    • Exprs.Compare
    • Exprs.Contains
    • Exprs.Elem
    • Exprs.Length
    • Exprs.Logic
    • Exprs.Strings
    • Exprs.Type
    • Exprs.Var
  • IfExprs
  • Json
  • MemDerive
  • Parser
  • Parsers
  • Relapse
  • Simplify
  • Smart
  • VpaDerive
  • Xml
  • Zip

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0, 0.2.0.1, 0.3.0.0, 0.3.0.1, 0.3.1.0, 0.4.0.1, 0.4.0.2
Change log changelog.md
Dependencies base (>=4.7 && <5), bytestring, containers, deepseq, either, extra, hxt, ilist, json, katydid, mtl, parsec, regex-tdfa, text [details]
License BSD-3-Clause
Copyright Walter Schulze
Author Walter Schulze
Maintainer awalterschulze@gmail.com
Category Data
Home page https://github.com/katydid/katydid-haskell
Source repo head: git clone https://github.com/katydid/katydid-haskell
Uploaded by awalterschulze at 2018-05-06T16:37:51Z
Distributions
Executables katydid-exe
Downloads 4246 total (23 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 2018-05-06 [all 3 reports]

Readme for katydid-0.3.0.0

[back to package description]

Katydid

Build Status

A Haskell implementation of Katydid.

Katydid Logo

This includes:

Documentation for katydid

Documentation for katydid-haskell

Documentation for katydid-haskell/Relapse

All JSON and XML tests from the language agnostic test suite [passes].

Hackage

Example

Validating a single structure can be done using the validate function:

validate :: Tree t => Grammar -> [t] -> Bool

, where a tree is a class in the Parsers module:

class Tree a where
    getLabel :: a -> Label
    getChildren :: a -> [a]

Here is an example that validates a single JSON tree:

main = either 
    (\err -> putStrLn $ "error:" ++ err) 
    (\valid -> if valid 
        then putStrLn "dragons exist" 
        else putStrLn "dragons are fictional"
    ) $
    Relapse.validate <$> 
        Relapse.parse ".DragonsExist == true" <*> 
        Json.decodeJSON "{\"DragonsExist\": false}"

Efficiency

If you want to validate multiple trees using the same grammar then the filter function does some internal memoization, which makes a huge difference.

filter :: Tree t => Grammar -> [[t]] -> [[t]]

User Defined Functions

If you want to create your own extra functions for operating on the leaves, then you can inject them into the parse function:

main = either
    (\err -> putStrLn $ "error:" ++ err)
    (\valid -> if valid
        then putStrLn "prime birthday !!!"
        else putStrLn "JOMO"
    ) $
    Relapse.validate <$>
        Relapse.parseWithUDFs userLib ".Survived->isPrime($int)" <*>
        Json.decodeJSON "{\"Survived\": 104743}"

Defining your own user library to inject is easy. The Expr library provides many useful helper functions:

import Data.Numbers.Primes (isPrime)
import Expr

userLib :: String -> [AnyExpr] -> Either String AnyExpr
userLib "isPrime" args = mkIsPrime args
userLib n _ = throwError $ "undefined function: " ++ n

mkIsPrime :: [AnyExpr] -> Either String AnyExpr
mkIsPrime args = do {
    arg <- assertArgs1 "isPrime" args;
    mkBoolExpr . isPrimeExpr <$> assertInt arg;
}

isPrimeExpr :: Integral a => Expr a -> Expr Bool
isPrimeExpr numExpr = trimBool Expr {
    desc = mkDesc "isPrime" [desc numExpr]
    , eval = \fieldValue -> isPrime <$> eval numExpr fieldValue
}

Roadmap

  • Protobuf parser
  • Profile and Optimize (bring up to par with Go version)
  • Typed DSL (Combinator)