Coder Social home page Coder Social logo

Help: Prettier about waargonaut HOT 3 OPEN

treffynnon avatar treffynnon commented on July 3, 2024
Help: Prettier

from waargonaut.

Comments (3)

mankyKitty avatar mankyKitty commented on July 3, 2024

Natural isn't an impediment, I'm using the type system to prevent negative indentation values. The actual issue is that the docs have fallen out of step with the type signature, but that's an easy fix.

If the Waargonaut.Prettier module re-exported the successor' and zero' functions, that might simplify things too.

The Prettier module isn't as well battle-tested as the rest of the library so it may still be a bit gnarly to use. But you're pretty much on the money, the thing I would point out is that you can pass the encodeSchema directly to the simpleEncodePretty function. As it takes an Encoder, it's the prettyJson function that is limited to only Json input.

Also rather than : foldr (const . T.putStr) (pure ()), you can use traverse_:

traverse_ putStr :: Foldable t => t String -> IO ()

foldr (const . putStr) (pure ()) :: Foldable t => t String -> IO ()

I wrote up a small example based on your type:

{-# LANGUAGE OverloadedStrings #-}
module Main where

import           Data.Functor.Identity (runIdentity)

import           Data.Scientific       (Scientific)
import           Natural               (Natural, successor', zero')

import           Data.Text             (Text)
import qualified Data.Text.Lazy.IO     as TIO

import qualified Waargonaut.Encode     as E

import qualified Waargonaut.Prettier   as WEP
import qualified Waargonaut.Types      as WT

data Properties = Properties
  { _propA :: Scientific
  , _propB :: Bool
  }

encodeProperties :: Applicative f => E.Encoder f Properties
encodeProperties = E.mapLikeObj $ \p ->
  E.atKey' "propA" E.scientific (_propA p) .
  E.atKey' "propB" E.bool (_propB p)

data Schema = Schema
  { _id                :: Text
  , _schema            :: Text
  , _schemaDescription :: Text
  , _schemaProperties  :: Properties
  }

encodeSchema :: Monad f => E.Encoder f Schema
encodeSchema = E.keyValuesAsObj
  [ E.encAt E.text "id" _id
  , E.encAt E.text "schema" _schema
  , E.encAt E.text "schemaDescription" _schemaDescription
  , E.encAt encodeProperties  "schemaProperties" _schemaProperties
  ]

main :: IO ()
main =
  let
    aSchema = Schema "raqxpn9rvfsdk" "Fred" "Turtle" (Properties 3.149e-6 False)

    -- It is fun when the type system prevents invalid states!
    two = successor' $ successor' zero'

    makePretty = runIdentity . WEP.simpleEncodePretty
      WEP.ArrayOnly
      (WEP.IndentStep two)
      (WEP.NumSpaces two)
      encodeSchema

  in
    TIO.putStrLn (makePretty aSchema)

This will print this output:

{
  "id":                "TACO",
  "schema":            "Fred",
  "schemaDescription": "Turtle",
  "schemaProperties":  {
    "propA": 3.149e-6,
    "propB": false
  }
}

from waargonaut.

treffynnon avatar treffynnon commented on July 3, 2024

Thank you for the clarification. I understand what the Natural type is there to do now and can see why it is used. I'd just never encountered it before and found it confounding when I was shoving Ints at Prettier - should've just followed the types :) As it seemed a bit convoluted I assumed I was making a rookie mistake by building two that way.

The example code you've included is very informative - I was going to make a pull request adding an example of using atKey' with maybeOrNull and scientific - probably not needed now!

from waargonaut.

mankyKitty avatar mankyKitty commented on July 3, 2024

That's understandable, I think we're all a bit complacent when it comes to use of values that are "just a number", when in fact those numbers have a purpose and often have properties that we should and could enforce!

Please submit that PR! Examples and documentation are always useful and it works best when it's not from only one person. :)

from waargonaut.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.