How do I derive PersistField for a custom newtype? - haskell

This is a Yesod-specific question, but even without knowing Yesod you might be able to help me, it has to do with newtypes.
Say I have the following simplified model in my config/models
Value
userId UserId
weight Weight
deriving (Show)
I will be using both kilograms and pounds in my webapp, but I decided that the DB should store things in kilograms. To get the type-system to protect me from confusing the two, I define the following:
newtype Weight = Kilograms Int
deriving (Read, Show, Eq, PersistField, PersistFieldSql)
That compiled fine, but how can I use this from a form?
logForm :: UserId -> Form Value
logForm uid = renderDivs $ Value <$>
pure uid <*>
areq intField "Weight" Nothing
I get the error
No instance for (Integral ModelTypes.Weight)
arising from a use of `intField'
I tried deriving Integral but then it complains I don't have Real Weight. On and on, I end up with:
newtype Weight = Grams Int
deriving (Read, Show, Eq, Enum, Ord, Num, Integral, Real, PersistField, PersistFieldSql)
Is this the correct way to do it? It seems like a lot of repetition. What's a better way to do it?
In general, if I have in Haskell a
newtype N = T a
for a concrete type a, how can I have N re-derive everything that a is in instance of, and also get N to derive some other typeclasses (in my example PersistField and PersistFieldSql). Thanks a lot.

A PersistField isn't the same as a Field. You want to make a custom field by importing Yesod.Forms. Here's an example, for a MathJax type ;)
newtype MathJax = MathJax { unMathJax :: Markdown }
deriving (Eq, Ord, Show, Read, PersistField, PersistFieldSql, IsString, Monoid)
unMM :: MathJax -> Text
unMM = unMarkdown . unMathJax
mathJaxField :: (Monad m, RenderMessage (HandlerSite m) FormMessage) => Field m MathJax
mathJaxField = Field
{ fieldParse = parseHelper $ Right . MathJax . Markdown . Text.filter (/= '\r')
, fieldView = \theId name attrs val _isReq -> toWidget
[hamlet|$newline never
<textarea id="#{theId}" name="#{name}" *{attrs}>#{either id unMM val}
|]
, fieldEnctype = UrlEncoded
}

Related

How to create an instance of Arbitrary for parametric types in Haskell

I'm following haskellbook.com and there is an exercise for QuickCheck, long history short I can't figure out how to implement a instance for arbitrary for my type because it has a parametric type
Here is the code
module First where
import Test.QuickCheck
-- I have this type that has a type parameter, it's a Maybe like
data Optional a = Some a | None deriving (Show, Eq)
-- I want to check that this is monoidal, but that is not the problem yet
newtype First' a =
First' { getFirst' :: Optional a }
deriving (Eq, Show)
-- Here I have an undefined. I simply cant do `instance Arbitrary (First String)`
-- And I cant place a concrete type on the undefined place. How can I implement
-- this type class for First' a?
instance (Arbitrary a) => Arbitrary (First' a) where
arbitrary = frequency [ (1, return (First' (Some undefined))) --- how I get rid of this undefined ?????
, (1, return (First' None))
]
I would like to have something like Some "foo" in place of Some undefined, but I cant
make a a concrete type, I'm struggling with this for some hours and just cant
come up with a solution.
What you want to do is use the Arbitrary instance for a. I can tell you know you need to do this because you already added Arbitrary a as a constraint to the instance, but you need to actually use it. For instance:
instance Arbitrary a => Arbitrary (First' a) where
arbitrary = frequency [ (1, First' . Some <$> arbitrary) -- here we have `arbitrary :: Gen a`
, (1, return (First' None))
]
But really, you should go one step further. Rather than just making an instance for First' a, you can first make an instance for Optional a that will make your First' instance even easier. Consider:
instance Arbitrary a => Arbitrary (Optional a) where
arbitrary = oneof [ Some <$> arbitrary -- here we have `arbitrary :: Gen a`
, return None
]
instance Arbitrary a => Arbitrary (First' a) where
arbitrary = First' <$> arbitrary -- this one is `arbitrary :: Gen (Optional a)`
(Note that oneof is like frequency where all the frequency numbers are the same.)

Deriving Eq and Show for an ADT that contains fields that can't have Eq or Show

I'd like to be able to derive Eq and Show for an ADT that contains multiple fields. One of them is a function field. When doing Show, I'd like it to display something bogus, like e.g. "<function>"; when doing Eq, I'd like it to ignore that field. How can I best do this without hand-writing a full instance for Show and Eq?
I don't want to wrap the function field inside a newtype and write my own Eq and Show for that - it would be too bothersome to use like that.
One way you can get proper Eq and Show instances is to, instead of hard-coding that function field, make it a type parameter and provide a function that just “erases” that field. I.e., if you have
data Foo = Foo
{ fooI :: Int
, fooF :: Int -> Int }
you change it to
data Foo' f = Foo
{ _fooI :: Int
, _fooF :: f }
deriving (Eq, Show)
type Foo = Foo' (Int -> Int)
eraseFn :: Foo -> Foo' ()
eraseFn foo = foo{ fooF = () }
Then, Foo will still not be Eq- or Showable (which after all it shouldn't be), but to make a Foo value showable you can just wrap it in eraseFn.
Typically what I do in this circumstance is exactly what you say you don’t want to do, namely, wrap the function in a newtype and provide a Show for that:
data T1
{ f :: X -> Y
, xs :: [String]
, ys :: [Bool]
}
data T2
{ f :: OpaqueFunction X Y
, xs :: [String]
, ys :: [Bool]
}
deriving (Show)
newtype OpaqueFunction a b = OpaqueFunction (a -> b)
instance Show (OpaqueFunction a b) where
show = const "<function>"
If you don’t want to do that, you can instead make the function a type parameter, and substitute it out when Showing the type:
data T3' a
{ f :: a
, xs :: [String]
, ys :: [Bool]
}
deriving (Functor, Show)
newtype T3 = T3 (T3' (X -> Y))
data Opaque = Opaque
instance Show Opaque where
show = const "..."
instance Show T3 where
show (T3 t) = show (Opaque <$ t)
Or I’ll refactor my data type to derive Show only for the parts I want to be Showable by default, and override the other parts:
data T4 = T4
{ f :: X -> Y
, xys :: T4' -- Move the other fields into another type.
}
instance Show T4 where
show (T4 f xys) = "T4 <function> " <> show xys
data T4' = T4'
{ xs :: [String]
, ys :: [Bool]
}
deriving (Show) -- Derive ‘Show’ for the showable fields.
Or if my type is small, I’ll use a newtype instead of data, and derive Show via something like OpaqueFunction:
{-# LANGUAGE DerivingVia #-}
newtype T5 = T5 (X -> Y, [String], [Bool])
deriving (Show) via (OpaqueFunction X Y, [String], [Bool])
You can use the iso-deriving package to do this for data types using lenses if you care about keeping the field names / record accessors.
As for Eq (or Ord), it’s not a good idea to have an instance that equates values that can be observably distinguished in some way, since some code will treat them as identical and other code will not, and now you’re forced to care about stability: in some circumstance where I have a == b, should I pick a or b? This is why substitutability is a law for Eq: forall x y f. (x == y) ==> (f x == f y) if f is a “public” function that upholds the invariants of the type of x and y (although floating-point also violates this). A better choice is something like T4 above, having equality only for the parts of a type that can satisfy the laws, or explicitly using comparison modulo some function at use sites, e.g., comparing someField.
The module Text.Show.Functions in base provides a show instance for functions that displays <function>. To use it, just:
import Text.Show.Functions
It just defines an instance something like:
instance Show (a -> b) where
show _ = "<function>"
Similarly, you can define your own Eq instance:
import Text.Show.Functions
instance Eq (a -> b) where
-- all functions are equal...
-- ...though some are more equal than others
_ == _ = True
data Foo = Foo Int Double (Int -> Int) deriving (Show, Eq)
main = do
print $ Foo 1 2.0 (+1)
print $ Foo 1 2.0 (+1) == Foo 1 2.0 (+2) -- is True
This will be an orphan instance, so you'll get a warning with -Wall.
Obviously, these instances will apply to all functions. You can write instances for a more specialized function type (e.g., only for Int -> String, if that's the type of the function field in your data type), but there is no way to simultaneously (1) use the built-in Eq and Show deriving mechanisms to derive instances for your datatype, (2) not introduce a newtype wrapper for the function field (or some other type polymorphism as mentioned in the other answers), and (3) only have the function instances apply to the function field of your data type and not other function values of the same type.
If you really want to limit applicability of the custom function instances without a newtype wrapper, you'd probably need to build your own generics-based solution, which wouldn't make much sense unless you wanted to do this for a lot of data types. If you go this route, then the Generics.Deriving.Show and Generics.Deriving.Eq modules in generic-deriving provide templates for these instances which could be modified to treat functions specially, allowing you to derive per-datatype instances using some stub instances something like:
instance Show Foo where showsPrec = myGenericShowsPrec
instance Eq Foo where (==) = myGenericEquality
I proposed an idea for adding annotations to fields via fields, that allows operating on behaviour of individual fields.
data A = A
{ a :: Int
, b :: Int
, c :: Int -> Int via Ignore (Int->Int)
}
deriving
stock GHC.Generic
deriving (Eq, Show)
via Generically A -- assuming Eq (Generically A)
-- Show (Generically A)
But this is already possible with the "microsurgery" library, but you might have to write some boilerplate to get it going. Another solution is to write separate behaviour in "sums-of-products style"
data A = A Int Int (Int->Int)
deriving
stock GHC.Generic
deriving
anyclass SOP.Generic
deriving (Eq, Show)
via A <-𝈖-> '[ '[ Int, Int, Ignore (Int->Int) ] ]

Convert Lens' a b into Lens' a (Maybe b)

I have several data structures like
data Data1 = Data1
{ _data1Field :: Int
-- More fields
} deriving (Eq, Show)
makeLenses ''Data1
data Data2 = Data2
{ _data2Field :: Int
-- More fields
} deriving (Eq, Show)
makeLenses ''Data2
-- More similar data types
So I decided to write a simple type class to make it easier to compose
class HasField a where
field :: Lens' a Int
instance HasField Data1 where
field = data1Field
instance HasField Data2 where
field = data2Field
But then I ran into the problem that some of these structures have the corresponding field as optional
data Data3 = Data3
{ _data3Field :: Maybe Int
-- More fields
} deriving (Eq, Show)
makeLenses ''Data3
And now I can no longer use the type class. Since there are about the same number of data types that have that field optional as not, I decided that it'd be better to change the typeclass:
class HasField a where
field :: Lens' a (Maybe Int)
instance HasField Data3 where
field = data3Field
But since I'm not very experienced with the lens library, I'm stuck figuring out how to make this new lens work with the types for Data1 and Data2. Ideally, I'd like to be able to view it and get a Maybe Int value for any type, and when setting I'd like Just x to set the field to x for Data1 and Data2 and be a no-op for those two types when passed Nothing.
Is this possible using existing combinators or am I going to have to write the lens myself? I'm fine doing so, but the majority of existing tutorials use TH and gloss over the details of writing one by hand.
I'm using GHC 7.6.3 and lens 3.10.
As a follow up to shachaf
class HasFieldA d where
field :: Traversal' d Int
instance HasFieldA Data1 where
field = data1Field -- Lens's are Traversals
instance HasFieldA Data3 where
field = data3Field . _Just
And then the ^? operator or the ^.. operator
getField :: HasFieldA d => d -> Maybe Int
getField = d ^? field -- or preview field d
to get it.
To set optional fields, you'd need another function
class SetFieldA d where
setField :: Setter' d Int
instance SetFieldA Data3 where
setField = set data3Field . Just

How do I handle the Maybe result of at in Control.Lens.Indexed without a Monoid instance

I recently discovered the lens package on Hackage and have been trying to make use of it now in a small test project that might turn into a MUD/MUSH server one very distant day if I keep working on it.
Here is a minimized version of my code illustrating the problem I am facing right now with the at lenses used to access Key/Value containers (Data.Map.Strict in my case)
{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, TemplateHaskell #-}
module World where
import Control.Applicative ((<$>),(<*>), pure)
import Control.Lens
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as DM
import Data.Maybe
import Data.UUID
import Data.Text (Text)
import qualified Data.Text as T
import System.Random (Random, randomIO)
newtype RoomId = RoomId UUID deriving (Eq, Ord, Show, Read, Random)
newtype PlayerId = PlayerId UUID deriving (Eq, Ord, Show, Read, Random)
data Room =
Room { _roomId :: RoomId
, _roomName :: Text
, _roomDescription :: Text
, _roomPlayers :: [PlayerId]
} deriving (Eq, Ord, Show, Read)
makeLenses ''Room
data Player =
Player { _playerId :: PlayerId
, _playerDisplayName :: Text
, _playerLocation :: RoomId
} deriving (Eq, Ord, Show, Read)
makeLenses ''Player
data World =
World { _worldRooms :: Map RoomId Room
, _worldPlayers :: Map PlayerId Player
} deriving (Eq, Ord, Show, Read)
makeLenses ''World
mkWorld :: IO World
mkWorld = do
r1 <- Room <$> randomIO <*> (pure "The Singularity") <*> (pure "You are standing in the only place in the whole world") <*> (pure [])
p1 <- Player <$> randomIO <*> (pure "testplayer1") <*> (pure $ r1^.roomId)
let rooms = at (r1^.roomId) ?~ (set roomPlayers [p1^.playerId] r1) $ DM.empty
players = at (p1^.playerId) ?~ p1 $ DM.empty in do
return $ World rooms players
viewPlayerLocation :: World -> PlayerId -> RoomId
viewPlayerLocation world playerId=
view (worldPlayers.at playerId.traverse.playerLocation) world
Since rooms, players and similar objects are referenced all over the code I store them in my World state type as maps of Ids (newtyped UUIDs) to their data objects.
To retrieve those with lenses I need to handle the Maybe returned by the at lens (in case the key is not in the map this is Nothing) somehow. In my last line I tried to do this via traverse which does typecheck as long as the final result is an instance of Monoid but this is not generally the case. Right here it is not because playerLocation returns a RoomId which has no Monoid instance.
No instance for (Data.Monoid.Monoid RoomId)
arising from a use of `traverse'
Possible fix:
add an instance declaration for (Data.Monoid.Monoid RoomId)
In the first argument of `(.)', namely `traverse'
In the second argument of `(.)', namely `traverse . playerLocation'
In the second argument of `(.)', namely
`at playerId . traverse . playerLocation'
Since the Monoid is required by traverse only because traverse generalizes to containers of sizes greater than one I was now wondering if there is a better way to handle this that does not require semantically nonsensical Monoid instances on all types possibly contained in one my objects I want to store in the map.
Or maybe I misunderstood the issue here completely and I need to use a completely different bit of the rather large lens package?
If you have a Traversal and you want to get a Maybe for the first element, you can just use headOf instead of view, i.e.
viewPlayerLocation :: World -> PlayerId -> Maybe RoomId
viewPlayerLocation world playerId =
headOf (worldPlayers.at playerId.traverse.playerLocation) world
The infix version of headOf is called ^?. You can also use toListOf to get a list of all elements, and other functions depending on what you want to do. See the Control.Lens.Fold documentation.
A quick heuristic for which module to look for your functions in:
A Getter is a read-only view of exactly one value
A Lens is a read-write view of exactly one value
A Traversal is a read-write view of zero-or-more values
A Fold is a read-only view of zero-or-more values
A Setter is a write-only (well, modify-only) view of zero-or-more values (possibly uncountably many values, in fact)
An Iso is, well, an isomorphism -- a Lens that can go in either direction
Presumably you know when you're using an Indexed function, so you can look in the corresponding Indexed module
Think about what you're trying to do and what the most general module to put it in would be. :-) In this case you have a Traversal, but you're only trying to view, not modify, so the function you want is in .Fold. If you also had the guarantee that it was referring to exactly one value, it would be in .Getter.
Short answer: the lens package is not magic.
Without telling me what the error or default is, you want to make:
viewPlayerLocation :: World -> PlayerId -> RoomId
You know two things, that
To retrieve those with lenses I need to handle the Maybe returned by the at lens
and
traverse which does typecheck as long as the final result is an instance of Monoid
With a Monoid you get mempty :: Monoid m => m as the default when the lookup fails.
What can fail: The PlayerId can not be in the _worldPlayers and the _playerLocation can not be in the _worldRooms.
So what should your code do if a lookup fails? Is this "impossible" ? If so, then use fromMaybe (error "impossible") :: Maybe a -> a to crash.
If it possible for the lookup to fail then is there a sane default? Perhaps return Maybe RoomId and let the caller decide?
There is ^?! which frees you from calling fromMaybe.

Template Haskell data declarations that derive Show

The following doesn't compile:
import Language.Haskell.TH
makeAlpha n = [d| data Alpha = Alpha $(conT n) deriving (Show, Read) |]
I can't make out what the error means at all:
Can't derive instances where the instance context mentions
type variables that are not data type parameters
Offending constraint: Show t_d
When deriving the instance for (Show Alpha)
In the Template Haskell quotation
[d| data Alpha = Alpha $(conT n) deriving (Show, Read) |]
In the expression:
[d| data Alpha = Alpha $(conT n) deriving (Show, Read) |]
Is it possible to do derivations like this?
This problem arises because TH quotes are type checked when they are compiled, with splices replaced by variables. This is usually a good idea, because it allows many kinds of problems to be detected before the splice is run, but in some cases this can make the compiler wrongfully reject a splice that would generate valid code.
In this case, this means that the compiler tries to check this code:
data Alpha = Alpha t deriving (Show, Read)
This doesn't work because the derived Show and Read instances need to use Show and Read for t, but since t is not a type parameter of Alpha, it cannot add the necessary constraints. Of course, when this splice is run, t is replaced by a concrete type, so the appropriate instances will be available without the need for any constraints, so this is one of the cases where the compiler is being over-cautious.
The workaround is to not use quoting, but instead use TH combinators, which are not subject to these extra checks. It's messy, but it works:
makeAlpha n = sequence [dataD (cxt []) alpha []
[normalC alpha [strictType notStrict (conT n)]] [''Show, ''Read]]
where alpha = mkName "Alpha"
There has been some talk about relaxing the checks done on quotes, but for now you'll just have to deal with it.

Resources