Purescript types for buildQueryString function

会有一股神秘感。 提交于 2019-12-22 17:37:13

问题


I am new to Purescript and I am trying to write a function that can take any record value and iterate over the fields and values and build a querystring.

I am thinking something like:

buildQueryString :: forall a. PropertyTraversible r => r -> String

which I want to use like this:

buildQueryString {name: "joe", age: 10}      -- returns: "name=joe&age=10"

Is there a way to write something like that in Purescript with existing idioms or do I have to create my own custom Type Class for this?


回答1:


This is possible with purescript-generics but it only works on nominal types, not on any record. But it saves you boilerplate, since you can just derive the instance for Generic, so it would work with any data or newtype without further modification.

Downside is, you have to make some assumptions about the type: like it only contains one record and the record does not contain arrays or other records.

Here is a hacky demonstration how it would work:

data Person = Person 
            { name   :: String
            , age    :: Int
            }

derive instance genericPerson :: Generic Person

joe = Person { name: "joe", age: 10 }

build :: GenericSpine -> String
build (SRecord arr) = intercalate "&" (map (\x -> x.recLabel <> "=" <> build (x.recValue unit)) arr)
build (SProd _ arr) = fromMaybe "TODO" $ map (\f -> build (f unit)) (head arr)
build (SString s)   = s
build (SInt    i)   = show i
build _             = "TODO"

test = build (toSpine joe)

purescript-generics-rep is newer, so possibly there is a better solution, maybe even on any record. I have not tried that (yet).




回答2:


I'm sure that it can be shorter, but here is my implementation based on purescript-generic-rep (inspired by genericShow). This solution uses typeclasses - it seems to be standard approach with generic-rep:

module Main where

import Prelude

import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Data.Foldable (intercalate)
import Data.Generic.Rep (class Generic, Constructor(..), Field(..), Product(..), Rec(..), from)
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)

class EncodeValue a where
  encodeValue ∷ a → String

instance encodeValueString ∷ EncodeValue String where
  encodeValue = id

instance encodeValueInt ∷ EncodeValue Int where
  encodeValue = show

class EncodeFields a where
  encodeFields :: a -> Array String

instance encodeFieldsProduct
  ∷ (EncodeFields a, EncodeFields b)
  ⇒ EncodeFields (Product a b) where

  encodeFields (Product a b) = encodeFields a <> encodeFields b

instance encodeFieldsField
  ∷ (EncodeValue a, IsSymbol name)
  ⇒ EncodeFields (Field name a) where

  encodeFields (Field a) =
    [reflectSymbol (SProxy :: SProxy name) <> "=" <> encodeValue a]

buildQueryString
  ∷ ∀ a l n.
    Generic n (Constructor l (Rec a))
  ⇒ (EncodeFields a)
  ⇒ n
  → String
buildQueryString n =
  build <<< from $ n
 where
  build (Constructor (Rec fields)) = intercalate "&" <<< encodeFields $ fields

newtype Person =
  Person
    { name   ∷ String
    , age    ∷ Int
    }
derive instance genericPerson ∷ Generic Person _

joe ∷ Person
joe = Person { name: "joe", age: 10 }

main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
  log <<< buildQueryString $ joe

buildQueryString expects value of type with single constructor which contains a record (possibly just newtype) because it is impossible to derive a Generic instance for "unwrapped" Record type.

If you want to handle also Array values etc. then encodeValue should probably return values of type Array String.



来源:https://stackoverflow.com/questions/44758148/purescript-types-for-buildquerystring-function

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!