Using Aeson generics to construct JSON with a value as key holding another value - haskell

Toying a bit with the github gist API while trying to get down with the Aeson JSON library. I've run into a problem with the generated ToJSON instance, and I don't know exactly how to solve it.
I need to contain a value inside and the key that is associated to the value also needs to be a value and not a predefined key name. It's a bit easier to show. The desired output is,
{
"public": true,
"description": "Something..",
"files": {"This Thing.md": {"content": "Here we go!"}}
}
where the value of the filename is holding the content, but currently I get,
{
"public": true,
"description": "Something..",
"files": {"filename": "This Thing.md", "content": "Here we go!"}
}
Which isn't really what I need. The current code is,
{-# LANGUAGE OverloadedStrings, DeriveGeneric #-}
import Data.Text (Text)
import Data.Aeson
import GHC.Generics
data GistContent = GistContent
{ filename :: Text
, content :: Text
} deriving (Show, Generic)
instance ToJSON GistContent
data Gist = Gist
{ description :: Text
, public :: Bool
, files :: GistContent
} deriving (Show, Generic)
instance ToJSON Gist
Under the assumption that it is possible, how would my datastructure need to look to get the desired output?.. And if that's not possible using the generics, how'd I got about it using the ToJSON instance (I can't quite figure out the structure there either)?

Your problem stems from an incorrect schema. files can currently only contain one GistContent, which is unnecessarily limiting. Instead, you'd want to have a list of GistContents:
data Gist = Gist
{ description :: Text
, public :: Bool
, files :: [GistContent]
} deriving (Show, Generic)
Now consider another constraint on Gist: each GistContent must have a different filename. A data structure that would enforce this would be Data.HashMap.Strict.HashMap. Taking the filename out of GistContent and using the filename as a key:
data GistContent = GistContent
{ content :: Text
} deriving (Show, Generic)
data Gist = Gist
{ description :: Text
, public :: Bool
, files :: HashMap Text GistContent
} deriving (Show, Generic)
Everything works out.

Here's the manually written instance (see the documentation for the class):
instance ToJSON GistContent where
toJSON (GistContent { filename = f, content = c }) = object [f .= c]
I doubt if there would be any way to get this with your existing datatype with the automatically generated instances because all they can do is to follow the datatype using a standard scheme. Note that you can still use the generic instance for Gist because that will call the (non-generic) instance for GistContent.

Related

Multiple declaration error in data type declaration

I'm currently building a a Twitter CLI client in Haskell, and I have a data type that represents a DM and one that represents a tweet. However, I get a multiple declaration error because I have to use the same name for both:
data Users = Users { screen_name :: String } deriving(Show, Generic)
data Tweet = Tweet { text :: !Text,
retweeted :: Bool,
user :: Users
} deriving (Show, Generic)
data DM = DM { text :: !Text,
sender_screen_name :: String
} deriving (Show, Generic)
Does someone know a solution for this particular problem?
As defined here, the named members are just functions that are used to call the values in your data structure.
So, if you really want to use them, you can do so by using the language extension. You can do that by declaring this in your file:
{-# LANGUAGE DuplicateRecordFields #-}

Prefix lenses for a type

I have the following data declared:
data Something = Something
{ self :: String
, id :: String
, description :: Maybe String
, name :: String
} deriving (Generic, Show)
instance FromJSON Something
makeLensesFor
[ ("self", "somethingSelf")
, ("id", "somethingId")
, ("description", "somethingDescription")
, ("name", "somethingName")
]
''Something
Is it possible to automate the lenses creation as the naming convention is following really simple rules.
After a peek at the source code, I can see there's a LensRules instance, called abbreviatedFields, but, sadly, using it with makeLensesWith abbreviatedFields ''Something generates no lenses at all. Am I doing something wrong?
Here's the source code: https://hackage.haskell.org/package/lens-4.14/docs/src/Control.Lens.TH.html#abbreviatedFields

Using type safe routes with persistent datatypes in snap

I have a Snap application using Persistent for storage and I'm trying to generate type safe routes for data types defined in Persistent. I'm using the snap-web-routes package:.
I have the following Template Haskell function that creates the data type of Group and GroupId:
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Group
name T.Text
deriving Show
|]
In my Application.hs I have:
data AppUrl = AddLink GroupId deriving (Eq, Show, Read, Generic)
The doc's suggest that:
instance PathInfo AppUrl
is all i need to do given the Generic derivation above however this blows up with
No instance for (PathInfo (KeyBackend SqlBackend Group))
arising from a use of ‘Web.Routes.PathInfo.$gdmtoPathSegments’
My assumption is that this error indicates that Haskell does not know how to auto create the instance definition with Persistent's data types.
My next attempt was to manually define the instance:
instance PathInfo AppUrl where
toPathSegments (AddLink groupId) = "add-link" : toPathPiece groupId : []
fromPathSegments (x:y:[]) = ????
I can't seem to figure out how to construct the GroupId data type.
From Yesod's excellent Persistent tutorial I know that the datatype is defined as:
type GroupId = Key Group
newtype Key Group = GroupKey (BackendKey SqlBackend)
But then I run into a problem because BackendKey is not exposed so I can't import it and create my own instance. I can't seem to find a public API to create this data type in Persistent.
The documentation for SqlBackend shows that the associated datatype BackendKey is instanciated for SqlBackend as
data BackendKey SqlBackend = SqlBackendKey {
unSqlBackendKey :: Int64
}
Which should be enough information to write your own PathInfo instance, along the lines of the following example:
{-# LANGUAGE TypeFamilies #-}
import Database.Persist.Sql
import Data.Int (Int64)
foo :: BackendKey SqlBackend -> Int64
foo (SqlBackendKey key) = key
bar :: Int64 -> BackendKey SqlBackend
bar = SqlBackendKey

how to handle capital case in JSON?

This is a stupid question, and I have tried to understand from different tutorials. When having a JSON with capital case Haskell crashes as explained by others (https://mail.haskell.org/pipermail/beginners/2013-October/012865.html). As suggested it could be solved with deriving from deriveFromJSON. DeriveJSON requires a function input, how should I write the derive statement in the below code? I am missing something in my understanding, and would appreciate any help.
import Data.Aeson.TH
data Person = Person {
Foo :: String
, bar :: String
} deriving (Eq, Show, deriveJSON)
main = do
let b = Person "t" "x"
print b
deriveJSON and friends are Template Haskell functions which will generate instances for you. As such, you should not try to list them in the deriving clause. Instead, call them in a splice at the top level like this:
{-# LANGUAGE TemplateHaskell #-}
import Data.Aeson.TH
data Person = Person {
foo :: String,
bar :: String
} deriving (Eq, Show)
$(deriveJSON defaultOptions ''Person)
As mentioned in the mailing list, you can customize the field names by overriding the fieldLabelModifier function of the defaultOptions record, for example this will change the JSON name of foo to Foo:
$(deriveFromJSON defaultOptions {
fieldLabelModifier = let f "foo" = "Foo"
f other = other
in f
} ''Person)
Do you have any control of the instance being generated? If so, don't emit keys starting with capital letters.
If not: Just define the instance yourself instead of deriving it. It's just a couple lines of code.

Haskell -- any way to qualify or disambiguate record names?

I have two data types, which are used for hastache templates. It makes sense in my code to have two different types, both with a field named "name". This, of course, causes a conflict. It seems that there's a mechanism to disambiguate any calls to "name", but the actual definition causes problems. Is there any workaround, say letting the record field name be qualified?
data DeviceArray = DeviceArray
{ name :: String,
bytes :: Int }
deriving (Eq, Show, Data, Typeable)
data TemplateParams = TemplateParams
{ arrays :: [DeviceArray],
input :: DeviceArray }
deriving (Eq, Show, Data, Typeable)
data MakefileParams = MakefileParams
{ name :: String }
deriving (Eq, Show, Data, Typeable)
i.e. if the fields are now used in code, they will be "DeviceArray.name" and "MakefileParams.name"?
As already noted, this isn't directly possible, but I'd like to say a couple things about proposed solutions:
If the two fields are clearly distinct, you'll want to always know which you're using anyway. By "clearly distinct" here I mean that there would never be a circumstance where it would make sense to do the same thing with either field. Given this, excess disambiguity isn't really unwelcome, so you'd want either qualified imports as the standard approach, or the field disambiguation extension if that's more to your taste. Or, as a very simplistic (and slightly ugly) option, just manually prefix the fields, e.g. deviceArrayName instead of just name.
If the two fields are in some sense the same thing, it makes sense to be able to treat them in a homogeneous way; ideally you could write a function polymorphic in choice of name field. In this case, one option is using a type class for "named things", with functions that let you access the name field on any appropriate type. A major downside here, besides a proliferation of trivial type constraints and possible headaches from the Dreaded Monomorphism Restriction, is that you also lose the ability to use the record syntax, which begins to defeat the whole point.
The other major option for similar fields, which I didn't see suggested yet, is to extract the name field out into a single parameterized type, e.g. data Named a = Named { name :: String, item :: a }. GHC itself uses this approach for source locations in syntax trees, and while it doesn't use record syntax the idea is the same. The downside here is that if you have a Named DeviceArray, accessing the bytes field now requires going through two layers of records. If you want to update the bytes field with a function, you're stuck with something like this:
addBytes b na = na { item = (item na) { bytes = b + bytes (item na) } }
Ugh. There are ways to mitigate the issue a bit, but they're still not idea, to my mind. Cases like this are why I don't like record syntax in general. So, as a final option, some Template Haskell magic and the fclabels package:
{-# LANGUAGE TemplateHaskell #-}
import Control.Category
import Data.Record.Label
data Named a = Named
{ _name :: String,
_namedItem :: a }
deriving (Eq, Show, Data, Typeable)
data DeviceArray = DeviceArray { _bytes :: Int }
deriving (Eq, Show, Data, Typeable)
data MakefileParams = MakefileParams { _makefileParams :: [MakeParam] }
deriving (Eq, Show, Data, Typeable)
data MakeParam = MakeParam { paramText :: String }
deriving (Eq, Show, Data, Typeable)
$(mkLabels [''Named, ''DeviceArray, ''MakefileParams, ''MakeParam])
Don't mind the MakeParam business, I just needed a field on there to do something with. Anyway, now you can modify fields like this:
addBytes b = modL (namedItem >>> bytes) (b +)
nubParams = modL (namedItem >>> makefileParams) nub
You could also name bytes something like bytesInternal and then export an accessor bytes = namedItem >>> bytesInternal if you like.
Record field names are in the same scope as the data type, so you cannot do this directly.
The common ways to work around this is to either add prefixes to the field names, e.g. daName, mpName, or put them in separate modules which you then import qualified.
What you can do is to put each data type in its own module, then you can used qualified imports to disambiguate. It's a little clunky, but it works.
There are several GHC extensions which may help. The linked one is applicable in your case.
Or, you could refactor your code and use typeclasses for the common fields in records. Or, you should manually prefix each record selector with a prefix.
If you want to use the name in both, you can use a Class that define the name funcion. E.g:
Class Named a where
name :: a -> String
data DeviceArray = DeviceArray
{ deviceArrayName :: String,
bytes :: Int }
deriving (Eq, Show, Data, Typeable)
instance Named DeviceArray where
name = deviceArrayName
data MakefileParams = MakefileParams
{ makefileParamsName :: String }
deriving (Eq, Show, Data, Typeable)
instance Named MakefileParams where
name = makefileParamsName
And then you can use name on both classes.

Resources