Haskell Export Record for Read Access Only - haskell

I have a Haskell type that uses record syntax.
data Foo a = Foo { getDims :: (Int, Int), getData :: [a] }
I don't want to export the Foo value constructor, so that the user can't construct invalid objects. However, I would like to export getDims, so that the user can get the dimensions of the data structure. If I do this
module Data.ModuleName(Foo(getDims)) where
then the user can use getDims to get the dimensions, but the problem is that they can also use record update syntax to update the field.
getDims foo -- This is allowed (as intended)
foo { getDims = (999, 999) } -- But this is also allowed (not intended)
I would like to prevent the latter, as it would put the data in an invalid state. I realize that I could simply not use records.
data Foo a = Foo { getDims_ :: (Int, Int), getData :: [a] }
getDims :: Foo a -> (Int, Int)
getDims = getDims_
But this seems like a rather roundabout way to work around the problem. Is there a way to continue using record syntax while only exporting the record name for read access, not for write access?

Hiding the constructor and then defining new accessor functions for each field is a solution, but it can get tedious for records with a large number of fields.
Here's a solution with the new HasField typeclass in GHC 8.2.1 that avoids having to define functions for each field.
The idea is to define an auxiliary newtype like this:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PolyKinds #-} -- Important, obscure errors happen without this.
import GHC.Records (HasField(..))
-- Do NOT export the actual constructor!
newtype Moat r = Moat r
-- Export this instead.
moat :: r -> Moat r
moat = Moat
-- If r has a field, Moat r also has that field
instance HasField s r v => HasField s (Moat r) v where
getField (Moat r) = getField #s r
Every field in a record r will be accesible from Moat r, with the following syntax:
λ :set -XDataKinds
λ :set -XTypeApplications
λ getField #"getDims" $ moat (Foo (5,5) ['s'])
(5,5)
The Foo constructor should be hidden from clients. However, the field accessors for Foo should not be hidden; they must be in scope for the HasField instances of Moat to kick in.
Every function in your public-facing api should return and receive Moat Foos instead of Foos.
To make the accessor syntax slightly less verbose, we can turn to OverloadedLabels:
import GHC.OverloadedLabels
newtype Label r v = Label { field :: r -> v }
instance HasField l r v => IsLabel l (Label r v) where
fromLabel = Label (getField #l)
In ghci:
λ :set -XOverloadedLabels
λ field #getDims $ moat (Foo (5,5) ['s'])
(5,5)
Instead of hiding the Foo constructor, another option would be to make Foo completely public and define Moat inside your library, hiding any Moat constructors from clients.

Related

Is there a way to show "showable" stuff [duplicate]

Suppose I have a simple data type in Haskell for storing a value:
data V a = V a
I want to make V an instance of Show, regardless of a's type. If a is an instance of Show, then show (V a) should return show a otherwise an error message should be returned. Or in Pseudo-Haskell:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
How could this behaviour be implemented in Haskell?
As I said in a comment, the runtime objects allocated in memory don't have type tags in a Haskell program. There is therefore no universal instanceof operation like in, say, Java.
It's also important to consider the implications of the following. In Haskell, to a first approximation (i.e., ignoring some fancy stuff that beginners shouldn't tackle too soon), all runtime function calls are monomorphic. I.e., the compiler knows, directly or indirectly, the monomorphic (non-generic) type of every function call in an executable program. Even though your V type's show function has a generic type:
-- Specialized to `V a`
show :: V a -> String -- generic; has variable `a`
...you can't actually write a program that calls the function at runtime without, directly or indirectly, telling the compiler exactly what type a will be in every single call. So for example:
-- Here you tell it directly that `a := Int`
example1 = show (V (1 :: Int))
-- Here you're not saying which type `a` is, but this just "puts off"
-- the decision—for `example2` to be called, *something* in the call
-- graph will have to pick a monomorphic type for `a`.
example2 :: a -> String
example2 x = show (V x) ++ example1
Seen in this light, hopefully you can spot the problem with what you're asking:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
Basically, since the type for the a parameter will be known at compilation time for any actual call to your show function, there's no point to testing for this type at runtime—you can test for it at compilation time! Once you grasp this, you're led to Will Sewell's suggestion:
-- No call to `show (V x)` will compile unless `x` is of a `Show` type.
instance Show a => Show (V a) where ...
EDIT: A more constructive answer perhaps might be this: your V type needs to be a tagged union of multiple cases. This does require using the GADTs extension:
{-# LANGUAGE GADTs #-}
-- This definition requires `GADTs`. It has two constructors:
data V a where
-- The `Showable` constructor can only be used with `Show` types.
Showable :: Show a => a -> V a
-- The `Unshowable` constructor can be used with any type.
Unshowable :: a -> V a
instance Show (V a) where
show (Showable a) = show a
show (Unshowable a) = "Some Error."
But this isn't a runtime check of whether a type is a Show instance—your code is responsible for knowing at compilation time where the Showable constructor is to be used.
You can with this library: https://github.com/mikeizbicki/ifcxt. Being able to call show on a value that may or may not have a Show instance is one of the first examples it gives. This is how you could adapt that for V a:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
import IfCxt
import Data.Typeable
mkIfCxtInstances ''Show
data V a = V a
instance forall a. IfCxt (Show a) => Show (V a) where
show (V a) = ifCxt (Proxy::Proxy (Show a))
(show a)
"<<unshowable>>"
This is the essence of this library:
class IfCxt cxt where
ifCxt :: proxy cxt -> (cxt => a) -> a -> a
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
I don't fully understand it, but this is how I think it works:
It doesn't violate the "open world" assumption any more than
instance {-# OVERLAPPABLE #-} Show a where
show _ = "<<unshowable>>"
does. The approach is actually pretty similar to that: adding a default case to fall back on for all types that do not have an instance in scope. However, it adds some indirection to not make a mess of the existing instances (and to allow different functions to specify different defaults). IfCxt works as a a "meta-class", a class on constraints, that indicates whether those instances exist, with a default case that indicates "false.":
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
It uses TemplateHaskell to generate a long list of instances for that class:
instance {-# OVERLAPS #-} IfCxt (Show Int) where ifCxt _ t f = t
instance {-# OVERLAPS #-} IfCxt (Show Char) where ifCxt _ t f = t
which also implies that any instances that were not in scope when mkIfCxtInstances was called will be considered non-existing.
The proxy cxt argument is used to pass a Constraint to the function, the (cxt => a) argument (I had no idea RankNTypes allowed that) is an argument that can use the constraint cxt, but as long as that argument is unused, the constraint doesn't need to be solved. This is similar to:
f :: (Show (a -> a) => a) -> a -> a
f _ x = x
The proxy argument supplies the constraint, then the IfCxt constraint is solved to either the t or f argument, if it's t then there is some IfCxt instance where this constraint is supplied which means it can be solved directly, if it's f then the constraint is never demanded so it gets dropped.
This solution is imperfect (as new modules can define new Show instances which won't work unless it also calls mkIfCxtInstances), but being able to do that would violate the open world assumption.
Even if you could do this, it would be a bad design. I would recommend adding a Show constraint to a:
instance Show a => Show (V a) where ...
If you want to store members in a container data type that are not an instance of Show, then you should create a new data type fore them.

Haskell instance signatures

I'm a complete newbie in Haskell so please be patient.
Let's say I've got this class
class Indexable i where
at :: i a p -> p -> a
Now let's say I want to implement that typeclass for this data type:
data Test a p = Test [a]
What I tried is:
instance Indexable Test where
at (Test l) p = l `genericIndex` p
However it didn't compile, because p needs to be an Integral, however as far as I understand, it's impossibile to add the type signature to instances. I tried to use InstanceSigs, but failed.
Any ideas?
here is a version where you add the index-type to the class using MultiParamTypeClasses
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
module Index where
import Data.List (genericIndex)
class Indexable i f where
at :: forall a . f a -> i -> a
data Test a = Test [a]
instance Integral i => Indexable i Test where
at (Test as) i = as `genericIndex` i
here I need the FlexibleInstances because of the way the instance is declared and RankNTypes for the forall a . ;)
assuming this is your expected behavior:
λ> let test = Test [1..5]
λ> test `at` 3
4
λ> test `at` 0
1
λ> test `at` (0 :: Int)
1
λ> test `at` (1 :: Integer)
2
Just for fun, here's a very different solution which doesn't require any changes to your class declaration. (N.B. This answer is for fun only! I do not advocate keeping your class as-is; it seems a strange class definition to me.) The idea here is to push the burden of proof off from the class instance to the person constructing a value of type Test p a; we will demand that constructing such a value will require an Integral p instance in scope.
All this code stays exactly the same (but with a new extension turned on):
{-# LANGUAGE GADTs #-}
import Data.List
class Indexable i where
at :: i a p -> p -> a
instance Indexable Test where
at (Test l) p = l `genericIndex` p
But the declaration of your data type changes just slightly to demand an Integral p instance:
data Test a p where
Test :: Integral p => [a] -> Test a p
You are actually trying to do something fairly advanced. If I understand what you want, you actually need a multiparameter typeclass here, because your type parameter "p" depends on "i": for a list indexed by integer you need "p" to be integral, but for a table indexed by strings you need it to be "String", or at least an instance of "Ord".
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-} -- Enable the language extensions.
class Indexable i p | i -> p where
at :: i a -> p -> a
This says that the class is for two types, "i" and "p", and if you know "i" then "p" follows automatically. So if "i" is a list the "p" has to be Int, and if "i" is a "Map String a" then "p" has to be "String".
instance Indexable [a] Int where
at = (!!)
This declares the combination of [a] and Int as being an instance of Indexable.
user2407038 has provided an alternative approach using "type families", which is a more recent and sophisticated version of multiparameter type classes.
You can use associated type families and constraint kinds:
import GHC.Exts(Constraint)
class Indexable i where
type IndexableCtr i :: * -> Constraint
at :: IndexableCtr i p => i a p -> p -> a
instance Indexable Test where
type IndexableCtr Test = Integral
at (Test l) p = l `genericIndex` p
This defines the class Indexable with an associated type IndexableCtr which
is used to constraint the type of at.

How can I deal with “typedef”-style data types with a minimum of boilerplate?

I defined a custom data type that contains a single field:
import Data.Set (Set)
data GraphEdge a = GraphEdge (Set a)
Defining my own type feels more semantically correct but it leads to a lot of boilerplate in my functions. Any time I want to use the built-in Set functions I have to unwrap the inner set and later rewrap it:
import Data.Set (map)
modifyItemsSomehow :: Ord a => GraphEdge a -> GraphEdge a
modifyItemsSomehow (GraphEdge items) = GraphEdge $ Set.map someFunction items
This could be improved slightly by making it a record, like
import Data.Set (Set, map)
data GraphEdge a = GraphEdge { unGraphEdge :: Set a }
modifyItemsSomehow = GraphEdge . map someFunction . unGraphEdge
but this still feels far from ideal. What is the most idiomatic way to handle this kind of boilerplate when dealing with a user-defined data type that consists of a single field?
Before anything else, you should make sure to use newtype for single-field single-constructor types. data introduces runtime overhead and extra laziness, and prevents us from using the first two of the following techniques.
First, you can use GeneralizedNewtypeDeriving when possible:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Foo a = Foo a deriving (Eq, Show, Ord, Num)
foo :: Foo Int
foo = 0
bar :: Foo Int
bar = foo * 120
Second, you can use coerce to generally convert between newtype wrappings:
import Data.Coerce
newtype Foo a = Foo a
newtype Bar a = Bar a
a :: [(Foo (Bar Int), Foo ())]
a = [(Foo (Bar 0), Foo ())]
b :: [(Int, ())]
b = coerce a
Third, you can use iso-s from lens to concisely move operations over/under newtype constructors.
{-# LANGUAGE TemplateHaskell #-}
import Data.Set (Set)
import qualified Data.Set as Set
import Control.Lens
newtype GraphEdge a = GraphEdge (Set a)
makePrisms ''GraphEdge
modifyItemsSomehow :: Ord a => GraphEdge a -> GraphEdge a
modifyItemsSomehow = _GraphEdge %~ Set.map someFunction

Name conflicts in Haskell records

Haskell doesn't have dot notation for record members. For each record member a compiler creates a function with the same name with a type RecType -> FieldType. This leads to name conflicts. Are there any ways to work around this, i.e. how can I have several records with the same field names?
For large projects, I prefer to keep each type in its own module and use Haskell's module system to namespace accessors for each type.
For example, I might have some type A in module A:
-- A.hs
data A = A
{ field1 :: String
, field2 :: Double
}
... and another type B with similarly-named fields in module B:
-- B.hs
data B = B
{ field1 :: Char
, field2 :: Int
}
Then if I want to use both types in some other module C I can import them qualified to distinguish which accessor I mean:
-- C.hs
import A as A
import B as B
f :: A -> B -> (Double, Int)
f a b = (A.field2 a, B.field2 b)
Unfortunately, Haskell does not have a way to define multiple name-spaces within the same module, otherwise there would be no need to split each type in a separate module to do this.
Another way to avoid this problem is to use the lens package. It provides a makeFields template haskell function, which you can use like this:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeSynonymInstances #-}
import Control.Lens
data A = A
{ _aText :: String
}
makeFields ''A -- Creates a lens x for each record accessor with the name _aX
data B = B
{ _bText :: Int
, _bValue :: Int
}
-- Creates a lens x for each record accessor with the name _bX
makeFields ''B
main = do
let a = A "hello"
let b = B 42 1
-- (^.) is a function of lens which accesses a field (text) of some value (a)
putStrLn $ "Text of a: " ++ a ^. text
putStrLn $ "Text of b: " ++ show (b ^. text)
If you don't want to use TemplateHaskell and lens, you can also do manually what lens automates using TemplateHaskell:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
data A = A
{ aText :: String
}
data B = B
{ bText :: Int
, bValue :: Int
}
-- A class for types a that have a "text" field of type t
class HasText a t | a -> t where
-- An accessor for the text value
text :: a -> t
-- Make our two types instances of those
instance HasText A String where text = aText
instance HasText B Int where text = bText
main = do
let a = A "hello"
let b = B 42 1
putStrLn $ "Text of a: " ++ text a
putStrLn $ "Text of b: " ++ show (text b)
But I can really recommend learning lens, as it also provides lots of other utilities, like modifying or setting a field.
The GHC developers developed a couple of extensions to help with this issue . Check out this ghc wiki page. Initially a single OverloadedRecordFields extension was planned, but instead two extensions were developed. The extensions are OverloadedLabels and DuplicateRecordFields. Also see that reddit discussion.
The DuplicateRecordFields extensions makes this code legal in a single module:
data Person = MkPerson { personId :: Int, name :: String }
data Address = MkAddress { personId :: Int, address :: String }
As of 2019, I'd say these two extensions didn't get the adoption I thought they would have (although they did get some adoption) and the status quo is probably still ongoing.

newtype Int -> CInt marshaller

I'm writing FFI to pdflib. Pdflib C API has lots of functions that return and/or take various handles (document, page, image, font) as plain Integer (not pointer).
In order to ensure i do not accidentally pass the wrong param to a function i create a bunch of newtypes in the form of:
newtype PdiDoc = PdiDoc Int
newtype PdiPage = PdiPage Int
newtype PdfImage = PdfImage Int
newtype PdfFont = PdfFont Int
Now i need to provide a marshaller for those types.
image2c (PdfImage i) = fromIntegral i
font2c (PdfFont f) = fromIntegral f
pdipage2c (PdiPage i) = fromIntegral i
As you see the marshallers are exactly the same, just for different types.
So my question is, is there some kind of type magic, SYB vodoo trick that i can use to have just one function to marshall all those types, or do i have to write same functions again and again for different newtypes ?
EDIT: I accepted Don's answer, because it solved my problem.
I switched on
GeneralizedNewtypeDeriving
added
deriving (Eq, Ord, Num, Enum, Real, Integral)
to each of my newtypes, and now i can use standard fromIntegral to marshall all of them.
Nathan Howell's answer is also correct one, i upvoted it. But unfortunately his solution would mean giving up on FFI preprocessors like c2hs i am using.
GHC's FFI extensions allow using newtypes that wrap FFI primitives. You could change the imported function signatures to use the newtypes and (hopefully) avoid having to unwrap them manually.
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
newtype Foo = Foo Int
foreign import ccall someCall :: Foo -> IO Foo
main :: IO ()
main = do
Foo x <- someCall (Foo 1)
print x
Alternatively, the new GHC Generics functionality (available since 7.2.1) allows generic unpacking and repacking of newtypes:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TypeFamilies #-}
module Main where
import GHC.Generics
-- use a regular newtype
newtype Foo1 = Foo1 Int deriving (Generic, Show)
-- or with record syntax
newtype Foo2 = Foo2{foo2 :: Int} deriving (Generic, Show)
unpack :: (Generic a, Rep a ~ D1 dc (C1 cc (S1 sc (K1 R kc)))) => a -> kc
unpack = unK1 . unM1 . unM1 . unM1 . from
pack :: (Generic a, Rep a ~ D1 dc (C1 cc (S1 sc (K1 R kc)))) => kc -> a
pack = to . M1 . M1 . M1 . K1
-- the C import uses Ints
foreign import ccall "someCall" c'someCall :: Int -> IO Int
-- and the typed wrapper packs/unpacks to FFI primitives
someCall :: Foo1 -> IO Foo2
someCall = fmap pack . c'someCall . unpack
main :: IO ()
main = do
Foo2 x <- someCall (Foo1 1)
print x
You can derive 'Num' for your types using GeneralizedNewtypeDeriving, this helps you a bit with literals and operators.
For the marshalling, I'd use a FFI preprocess, such as hsc2hs, which can automate the wrapping and unwrapping of newtypes.
An example from RWH:

Resources