Statically enforcing that two objects were created from the same (Int) "seed" - haskell

In a library I'm working on, I have an API similar to the following:
data Collection a = Collection Seed {-etc...-}
type Seed = Int
newCollection :: Seed -> IO (Collection a)
newCollection = undefined
insert :: a -> Collection a -> IO () -- ...and other mutable set-like functions
insert = undefined
mergeCollections :: Collection a -> Collection a -> IO (Collection a)
mergeCollections (Collection s0 {-etc...-}) (Collection s1 {-etc...-})
| s0 /= s1 = error "This is invalid; how can we make it statically unreachable?"
| otherwise = undefined
I'd like to be able to enforce that the user cannot call mergeCollections on Collections created with different Seed values.
I thought of trying to tag Collection with a type-level natural: I think this would mean that the Seed would have to be statically known at compile time, but my users might be getting it from an environment variable or user input, so I don't think that would work.
I also hoped I might be able to do something like:
newtype Seed u = Seed Int
newSeed :: Int -> Seed u
newCollection :: Seed u -> IO (Collection u a)
mergeCollections :: Collection u a -> Collection u a -> IO (Collection u a)
Where somehow a Seed is tagged with a unique type in some way, such that the type system could track that both arguments to merge were created from the seed returned by the same invocation of newSeed. To be clear in this (hand-wavy) scheme a and b here would somehow not unify: let a = newSeed 1; b = newSeed 1;.
Is something like this possible?
Examples
Here are some examples of ways I can imagine users creating Seeds and Collections. Users would like to use the other operations (inserting, merging, etc) as freely as they could with any other IO mutable collection:
We only need one seed for all Collections (dynamically) created during the program, but the user must be able to specify in some way how the seed should be determined from the environment at runtime.
One or more static keys gathered from environment vars (or command line args):
main = do
s1 <- getEnv "SEED1"
s2 <- getEnv "SEED2"
-- ... many Collections may be created dynamically from these seeds
-- and dynamically merged later

Probably not in a convenient way. For handling seeds that are known only at runtime, you can use existential types; but then you cannot statically check that two of these existentially wrapped collections match up. The much simpler solution is simply this:
merge :: Collection a -> Collection a -> IO (Maybe (Collection a))
On the other hand, if it is okay to force all operations to be done "together", in a sense, then you can do something like what the ST monad does: group all the operations together, then supply an operation for "running" all the operations that only works if the operations don't leak collections by demanding they be perfectly polymorphic over a phantom variable, hence that the return type doesn't mention the phantom variable. (Tikhon Jelvis also suggests this in his comments.) Here's how that might look:
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Collection (Collection, COp, newCollection, merge, inspect, runCOp) where
import Control.Monad.Reader
type Seed = Int
data Collection s a = Collection Seed
newtype COp s a = COp (Seed -> a) deriving (Functor, Applicative, Monad, MonadReader Seed)
newCollection :: COp s (Collection s a)
newCollection = Collection <$> ask
merge :: Collection s a -> Collection s a -> COp s (Collection s a)
merge l r = return (whatever l r) where
whatever = const
-- just an example; substitute whatever functions you want to have for
-- consuming Collections
inspect :: Collection s a -> COp s Int
inspect (Collection seed) = return seed
runCOp :: (forall s. COp s a) -> Seed -> a
runCOp (COp f) = f
Note in particular that the COp and Collection constructors are not exported. Consequently we need never fear that a Collection will escape its COp; runCOp newCollection is not well-typed (and any other operation that tries to "leak" the collection to the outside world will have the same property). Therefore it will not be possible to pass a Collection constructed with one seed to a merge operating in the context of another seed.

I believe this is impossible with the constraint that the seeds come from runtime values, like user input. The typechecker as a tool can only reject invalid programs if we can determine the program is invalid at compiletime. Supposing there is a type such that the typechecker is able to reject programs based on user input, we could deduce that the typechecker is doing some sort of time travel or is able to wholly simulate our deterministic universe. The best you can do as a library author is to smuggle your types into something like ExceptT, which documents the seed precondition and exports awareness for it.

Related

How to obtain a Data.Data.Constr etc. from a Type Representation?

I'm currently writing a minimalistic Haskell persistence framework that uses Data.Data Generics to provide persistence operations for data types in record syntax (I call them Entities here).
This works quite well overall (see code repo here: https://github.com/thma/generic-persistence), I've got just one ugly spot left.
Currently my function for looking up an entity by primary key has the following signature:
retrieveEntityById
:: forall a conn id. (Data a, IConnection conn, Show id)
=> conn -> TypeInfo -> id -> IO a
This function takes an HDBC database connection, A TypeInfo object and the primary key value id.
The TypeInfo contains data describing the type a. This Info will be used to generate and perform a select statement for primary key lookup and contruct an instance of type a from the HDBC result row.
TypeInfo contains Data.Data.Constr and a description of all constructor fields that are obtained with the following function:
-- | A function that returns a list of FieldInfos representing the
-- name, constructor and type of each field in a data type.
fieldInfo :: (Data a) => a -> [FieldInfo]
fieldInfo x = zipWith3 FieldInfo names constrs types
where
constructor = toConstr x
candidates = constrFields constructor
constrs = gmapQ toConstr x
types = gmapQ typeOf x
names =
if length candidates == length constrs
then map Just candidates
else replicate (length constrs) Nothing
Deriving this kind of information works great when having an actual Data a value at hand (for example in my function for updating an existing entity).
But in the retrieveEntityById case this is not possible, as the object has yet to loaded from the DB. That's why I have to call the function with an extra TypeInfo parameter that I create from a sample entity.
I would like to get rid of this extra parameter, to have a function signature like:
retrieveEntityById
:: forall a conn id. (Data a, IConnection conn, Show id)
=> conn -> id -> IO a
I tried several things like using a Proxy or a TypeRep, but I did not manage to derive my TypeInfo data from them.
Any hints and ideas are most welcome!
You can access metadata from Data a constraints without a value x :: a:
dataTypeOf (undefined :: a) is a representation of the type a. It takes an undefined argument because Data is an old interface from a time when undefined was considered more acceptable.
dataTypeConstrs extracts the list of constructors from that representation.
As you already noted in your code, although there is constrFields to get field names, there isn't an obvious way to get the arity of a non-record constructor. A solution to count the fields of a constructor is to use gunfold with the Const Int functor.
Although your current approach seems specialized to types with a single constructor, this is not a fundamental limitation. For more than one constructor, you could store the constructor name in its persistent encoding, and on decoding, it can be looked up in the list from dataTypeConstrs.

Clarification on Existential Types in Haskell

I am trying to understand Existential types in Haskell and came across a PDF http://www.ii.uni.wroc.pl/~dabi/courses/ZPF15/rlasocha/prezentacja.pdf
Please correct my below understandings that I have till now.
Existential Types not seem to be interested in the type they contain but pattern matching them say that there exists some type we don't know what type it is until & unless we use Typeable or Data.
We use them when we want to Hide types (ex: for Heterogeneous Lists) or we don't really know what the types at Compile Time.
GADT's provide the clear & better syntax to code using Existential Types by providing implicit forall's
My Doubts
In Page 20 of above PDF it is mentioned for below code that it is impossible for a Function to demand specific Buffer. Why is it so? When I am drafting a Function I exactly know what kind of buffer I gonna use eventhough I may not know what data I gonna put into that.
What's wrong in Having :: Worker MemoryBuffer Int If they really want to abstract over Buffer they can have a Sum type data Buffer = MemoryBuffer | NetBuffer | RandomBuffer and have a type like :: Worker Buffer Int
data Worker x = forall b. Buffer b => Worker {buffer :: b, input :: x}
data MemoryBuffer = MemoryBuffer
memoryWorker = Worker MemoryBuffer (1 :: Int)
memoryWorker :: Worker Int
As Haskell is a Full Type Erasure language like C then How does it know at Runtime which function to call. Is it something like we gonna maintain few information and pass in a Huge V-Table of Functions and at runtime it gonna figure out from V-Table? If it is so then what sort of Information it gonna store?
GADT's provide the clear & better syntax to code using Existential Types by providing implicit forall's
I think there's general agreement that the GADT syntax is better. I wouldn't say that it's because GADTs provide implicit foralls, but rather because the original syntax, enabled with the ExistentialQuantification extension, is potentially confusing/misleading. That syntax, of course, looks like:
data SomeType = forall a. SomeType a
or with a constraint:
data SomeShowableType = forall a. Show a => SomeShowableType a
and I think the consensus is that the use of the keyword forall here allows the type to be easily confused with the completely different type:
data AnyType = AnyType (forall a. a) -- need RankNTypes extension
A better syntax might have used a separate exists keyword, so you'd write:
data SomeType = SomeType (exists a. a) -- not valid GHC syntax
The GADT syntax, whether used with implicit or explicit forall, is more uniform across these types, and seems to be easier to understand. Even with an explicit forall, the following definition gets across the idea that you can take a value of any type a and put it inside a monomorphic SomeType':
data SomeType' where
SomeType' :: forall a. (a -> SomeType') -- parentheses optional
and it's easy to see and understand the difference between that type and:
data AnyType' where
AnyType' :: (forall a. a) -> AnyType'
Existential Types not seem to be interested in the type they contain but pattern matching them say that there exists some type we don't know what type it is until & unless we use Typeable or Data.
We use them when we want to Hide types (ex: for Heterogeneous Lists) or we don't really know what the types at Compile Time.
I guess these aren't too far off, though you don't have to use Typeable or Data to use existential types. I think it would be more accurate to say an existential type provides a well-typed "box" around an unspecified type. The box does "hide" the type in a sense, which allows you to make a heterogeneous list of such boxes, ignoring the types they contain. It turns out that an unconstrained existential, like SomeType' above is pretty useless, but a constrained type:
data SomeShowableType' where
SomeShowableType' :: forall a. (Show a) => a -> SomeShowableType'
allows you to pattern match to peek inside the "box" and make the type class facilities available:
showIt :: SomeShowableType' -> String
showIt (SomeShowableType' x) = show x
Note that this works for any type class, not just Typeable or Data.
With regard to your confusion about page 20 of the slide deck, the author is saying that it's impossible for a function that takes an existential Worker to demand a Worker having a particular Buffer instance. You can write a function to create a Worker using a particular type of Buffer, like MemoryBuffer:
class Buffer b where
output :: String -> b -> IO ()
data Worker x = forall b. Buffer b => Worker {buffer :: b, input :: x}
data MemoryBuffer = MemoryBuffer
instance Buffer MemoryBuffer
memoryWorker = Worker MemoryBuffer (1 :: Int)
memoryWorker :: Worker Int
but if you write a function that takes a Worker as argument, it can only use the general Buffer type class facilities (e.g., the function output):
doWork :: Worker Int -> IO ()
doWork (Worker b x) = output (show x) b
It can't try to demand that b be a particular type of buffer, even via pattern matching:
doWorkBroken :: Worker Int -> IO ()
doWorkBroken (Worker b x) = case b of
MemoryBuffer -> error "try this" -- type error
_ -> error "try that"
Finally, runtime information about existential types is made available through implicit "dictionary" arguments for the typeclasses that are involved. The Worker type above, in addtion to having fields for the buffer and input, also has an invisible implicit field that points to the Buffer dictionary (somewhat like v-table, though it's hardly huge, as it just contains a pointer to the appropriate output function).
Internally, the type class Buffer is represented as a data type with function fields, and instances are "dictionaries" of this type:
data Buffer' b = Buffer' { output' :: String -> b -> IO () }
dBuffer_MemoryBuffer :: Buffer' MemoryBuffer
dBuffer_MemoryBuffer = Buffer' { output' = undefined }
The existential type has a hidden field for this dictionary:
data Worker' x = forall b. Worker' { dBuffer :: Buffer' b, buffer' :: b, input' :: x }
and a function like doWork that operates on existential Worker' values is implemented as:
doWork' :: Worker' Int -> IO ()
doWork' (Worker' dBuf b x) = output' dBuf (show x) b
For a type class with only one function, the dictionary is actually optimized to a newtype, so in this example, the existential Worker type includes a hidden field that consists of a function pointer to the output function for the buffer, and that's the only runtime information needed by doWork.
In Page 20 of above PDF it is mentioned for below code that it is impossible for a Function to demand specific Buffer. Why is it so?
Because Worker, as defined, takes only one argument, the type of the "input" field (type variable x). E.g. Worker Int is a type. The type variable b, instead, is not a parameter of Worker, but is a sort of "local variable", so to speak. It can not be passed as in Worker Int String -- that would trigger a type error.
If we instead defined:
data Worker x b = Worker {buffer :: b, input :: x}
then Worker Int String would work, but the type is no longer existential -- we now always have to pass the buffer type as well.
As Haskell is a Full Type Erasure language like C then How does it know at Runtime which function to call. Is it something like we gonna maintain few information and pass in a Huge V-Table of Functions and at runtime it gonna figure out from V-Table? If it is so then what sort of Information it gonna store?
This is roughly correct. Briefly put, each time you apply constructor Worker, GHC infers the b type from the arguments of Worker, and then searches for an instance Buffer b. If that is found, GHC includes an additional pointer to the instance in the object. In its simplest form, this is not too different from the "pointer to vtable" which is added to each object in OOP when virtual functions are present.
In the general case, it can be much more complex, though. The compiler might use a different representation and add more pointers instead of a single one (say, directly adding the pointers to all the instance methods), if that speeds up code. Also, sometimes the compiler needs to use multiple instances to satisfy a constraint. E.g., if we need to store the instance for Eq [Int] ... then there is not one but two: one for Int and one for lists, and the two needs to be combined (at run time, barring optimizations).
It is hard to guess exactly what GHC does in each case: that depends on a ton of optimizations which might or might not trigger.
You could try googling for the "dictionary based" implementation of type classes to see more about what's going on. You can also ask GHC to print the internal optimized Core with -ddump-simpl and observe the dictionaries being constructed, stored, and passed around. I have to warn you: Core is rather low level, and can be hard to read at first.

Is there a canonical way of comparing/changing one/two records in haskell?

I want to compare two records in haskell, without defining each change in the datatype of the record with and each function of 2 datas for all of the elements of the record over and over.
I read about lens, but I could not find an example for that,
and do not know where begin to read in the documentation.
Example, not working:
data TheState = TheState { number :: Int,
truth :: Bool
}
initState = TheState 77 True
-- not working, example:
stateMaybe = fmap Just initState
-- result should be:
-- ANewStateType{ number = Just 77, truth = Just True}
The same way, I want to compare the 2 states:
state2 = TheState 78 True
-- not working, example
stateMaybe2 = someNewCompare initState state2
-- result should be:
-- ANewStateType{ number = Just 78, truth = Nothing}
As others have mentioned in comments, it's most likely easier to create a different record to hold the Maybe version of the fields and do the manual conversion. However there is a way to get the functor like mapping over your fields in a more automated way.
It's probably more involved than what you would want but it's possible to achieve using a pattern called Higher Kinded Data (HKD) and a library called barbies.
Here is a amazing blog post on the subject: https://chrispenner.ca/posts/hkd-options
And here is my attempt at using HKD on your specific example:
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
-- base
import Data.Functor.Identity
import GHC.Generics (Generic)
-- barbie
import Data.Barbie
type TheState = TheState_ Identity
data TheState_ f = TheState
{ number :: f Int
, truth :: f Bool
} deriving (Generic, FunctorB)
initState :: TheState
initState = TheState (pure 77) (pure True)
stateMaybe :: TheState_ Maybe
stateMaybe = bmap (Just . runIdentity) initState
What is happening here, is that we are wrapping every field of the record in a custom f. We now get to choose what to parameterise TheState with in order to wrap every field. A normal record now has all of its fields wrapped in Identity. But you can have other versions of the record easily available as well. The bmap function let's you map your transformation from one type of TheState_ to another.
Honestly, the blog post will do a much better job at explaining this than I would. I find the subject very interesting, but I am still very new to it myself.
Hope this helped! :-)
How to make a Functor out of a record. For that I have an answer: apply the function to > all of the items of the record.
I want to use the record as an heterogenous container / hashmap, where
the names determine the values-types
While there's no "easy", direct way of doing this, it can be accomplished with several existing libraries.
This answer uses red-black-record library, which is itself built over the anonymous products of sop-core. "sop-core" allows each field in a product to be wrapped in a functor like Maybe and provides functions to manipulate fields uniformly. "red-black-record" inherits this, adding named fields and conversions from normal records.
To make TheState compatible with "red-black-record", we need to do the following:
{-# LANGUAGE DataKinds, FlexibleContexts, ScopedTypeVariables,
DeriveGeneric, DeriveAnyClass,
TypeApplications #-}
import GHC.Generics
import Data.SOP
import Data.SOP.NP (NP,cliftA2_NP) -- anonymous n-ary products
import Data.RBR (Record, -- generalized record type with fields wrapped in functors
I(..), -- an identity functor for "simple" cases
Productlike, -- relates a map of types to its flattened list of types
ToRecord, toRecord, -- convert a normal record to its generalized form
RecordCode, -- returns the map of types correspoding to a normal record
toNP, fromNP, -- convert generalized record to and from n-ary product
getField) -- access field from generalized record using TypeApplication
data TheState = TheState { number :: Int,
truth :: Bool
} deriving (Generic,ToRecord)
We auto-derive the Generic instance that allows other code to introspect the structure of the datatype. This is needed by ToRecord, that allows conversion of normal records into their "generalized forms".
Now consider the following function:
compareRecords :: forall r flat. (ToRecord r,
Productlike '[] (RecordCode r) flat,
All Eq flat)
=> r
-> r
-> Record Maybe (RecordCode r)
compareRecords state1 state2 =
let mapIIM :: forall a. Eq a => I a -> I a -> Maybe a
mapIIM (I val1) (I val2) = if val1 /= val2 then Just val2
else Nothing
resultNP :: NP Maybe flat
resultNP = cliftA2_NP (Proxy #Eq)
mapIIM
(toNP (toRecord state1))
(toNP (toRecord state2))
in fromNP resultNP
It compares two records whatsoever that have ToRecord r instances, and also a corresponding flattened list of types that all have Eq instances (the Productlike '[] (RecordCode r) flat and All Eq flat constraints).
First it converts the initial record arguments to their generalized forms with toRecord. These generalized forms are parameterized with an identity functor I because they come from "pure" values and there aren't any effects are play, yet.
The generalized record forms are in turn converted to n-ary products with toNP.
Then we can use the cliftA2_NP function from "sop-core" to compare accross all fields using their respective Eq instances. The function requires specifying the Eq constraint using a Proxy.
The only thing left to do is reconstructing a generalized record (this one parameterized by Maybe) using fromNP.
An example of use:
main :: IO ()
main = do
let comparison = compareRecords (TheState 0 False) (TheState 0 True)
print (getField #"number" comparison)
print (getField #"truth" comparison)
getField is used to extract values from generalized records. The field name is given as a Symbol by way of -XTypeApplications.

Transparently implementing a particular form of dynamic typing

The basic idea is that I have a range of functions that work on any types from a particular class, but at runtime the program is supposed to read a configuration file and extract an element of one of the types in the class.
For instance, I have a 'Coefficient' class, various instances of it, and functions of various types that are polymorphic over types of that class; at runtime one particular type of that class is to be determined, and passed around.
I'm unsure how to properly address this; I tried making up 'compound' types, doing something like:
data CompoundCoeff = CompoundInt Int | CompoundDouble Double | ...
where Int, Double, ... are instances of the class 'Coefficient'.
However, it started to become a big effort to adapt all the functions involved in the code to work with these compound types (and it's not a nice solution either, really). It would be OK if all functions had the same, easy type, e.g.
Coefficient a => a -> (stuff not involving a anymore)
but that's unfortunately not the case.
Another issue I ran into, is that I'm using type families, and have something like
class (Monoid (ColourData c), Coordinate (InputData c)) => ColourScheme c where
type ColourData c :: *
type InputData c :: *
colouriseData :: c -> (ColourData c) -> AlphaColour Double
processInput :: c -> InputData c -> ColourData c
This doesn't go through cleanly if I have to use some sort of compound ColourData datatype, like the previous one; in particular I can no longer guarantee that the data stream gives a consistent type (and not just different 'subtypes' of a compound type), and would (among other things) have to make up a bogus Monoid instance if I did make up a compound ColourData type.
I've also looked into Data.Dynamic, but again I can't see how it would properly address the issues; the exact same problems seem to appear (well, slightly worse even, given that there is only one 'generic' Dynamic type as I understand it).
Question: How can I implement dynamic datatypes subordinate to particular classes, without having to rewrite all the functions involving those data types? It would be best if I didn't have to sacrifice any type safety, but I'm not too optimistic.
The program is supposed to read a configuration file at runtime, and all the requisite functions, polymorphic over the relevant class, are to be applied.
The traditional way to provide an object that guarantees that it is an instance of typeclass Foo, but makes no additional guarantees, is like so:
{-# LANGUAGE ExistentialTypes #-}
data SomeFoo = forall a . Foo a => SomeFoo a
instance Foo SomeFoo where
-- all operations just unwrap the SomeFoo straightforwardly
or, with GADTs, which might be more readable...
data SomeFoo where
SomeFoo :: Foo a => a -> SomeFoo
One proposal would be to write a single top-level function that does all the finishing touches once you've chosen a type:
topLevel :: SomeTypeClass a => a -> IO ()
Your program can then be written something like this:
main = do
config <- readConfig
case config of
UseDouble n -> topLevel n
UseSymbolic x -> topLevel x
UseWidgetFrobnosticator wf -> topLevel wf

Polymorphic Return Types Depending on Context

I'm playing around with implementing a Redis client-library in Haskell and it is my goal to encode, as much as possible, the semantics of the Redis commands in Haskell's type system. Redis, for those who don't know, is a datastore, accessed over the network. I will use it to exemplify my problem, but Redis is not the focus of this question.
An Example Function
Consider the function
get :: (RedisValue a) => Key -> Redis a
get k = decodeValue <$> sendCommand ["GET", key]
It sends a command to the datastore and returns a value stored under the given Key (for this example, you can consider type Key = String). As for the return-type:
Redis is an instance of Monad and MonadIO. It encapsulates information about the network connection. sendCommand sends the request and returns the datastore's reply.
a is polymorphic, for example either Strings or ByteStrings can be returned, depending on the context.
The following code should clarify the text above.
data Redis a = ...
instance MonadIO Redis where ...
instance Monad Redis where ...
sendCommand :: [String] -> Redis String
class RedisValue a where
decodeValue :: String -> a
-- example instances
instance RedisValue String where ...
instance RedisValue ByteString where ...
Different Context, Different Types
Redis supports a simple form of transactions. In a transaction most commands can be sent the same as outside of a transaction. However their execution is delayed until the user sends the commit command (which is called exec in Redis). Inside the transaction, the datastore only returns an acknowledgment that the command is stored for later execution. Upon commit (exec) all results of all stored commands are returned.
This means that the get-function from above looks a bit different in the context of a transaction:
get :: (RedisStatus a) => Key -> RedisTransaction a
get k = decodeStatus <$> sendCommand ["GET", key]
Note that:
The monadic type is now RedisTransaction to indicate the transaction context.
The a return type is now any instance of RedisStatus. There is an overlap between instances of RedisValue and RedisStatus. For example String is in both classes. A specialized Status data type might be only in the RedisStatus class.
The Actual Question
My question is, how can I write a function get that works in both contexts, with context-appropriate return type classes. What I need is
a way to give get a return type "either Redis or RedisTransaction",
The type a to be an instance of RedisValue in the Redis context and an instance of RedisStatus in the RedisTransaction context.
A function decode that automagically does the right thing, depending on the context. I assume this must come from a (multi-param) type class.
If you know how I can do this or have a pointer to some example code or even an article, you will have my thanks!
First, I think that it would be better to have two different get commands. That said, here's an approach.
class RedisGet m a where
get :: Key -> m a
instance (RedisValue a) => RedisGet Redis a where...
instance (RedisStatus a) => RedisGet RedisTransaction a where...
You need
MPTCs, but no FunDeps or Type Families. Every use of get requires that enough information be available to determine both the m and a uniquely.
I agree that multiparameter type classes are a good fit here. Here's an approach:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
newtype Redis a = Redis (IO a) deriving Monad
newtype RedisTransaction a = RedisTransaction (IO a) deriving Monad
newtype Key = Key {unKey :: String}
newtype Value = Value {unValue :: String}
newtype Status = Status {unStatus :: String}
class Monad m => RedisMonad m a | m -> a where
sendCommand :: [String] -> m a
instance RedisMonad Redis Value where
sendCommand = undefined -- TODO: provide implementation
instance RedisMonad RedisTransaction Status where
sendCommand = undefined -- TODO: provide implementation
class Decodable a b where
decode :: a -> b
instance Decodable Status String where
decode = unStatus
instance Decodable Value String where
decode = unValue
get :: (RedisMonad m a, Decodable a b) => Key -> m b
get k = do
response <- sendCommand ["GET", unKey k]
return (decode response)
Note the use of the type isomorphisms for Value and Status: it makes things slightly stronger typed as the Strings you are having produced by your implementations of sendCommand obviously are not just arbitrary sequences of characters but instead adhere to some fixed formats for return values and statuses.
Keep in mind that there's nothing special about a type depending on context--that happens all the time with type inference. The type of [] is [a], but when you use it in something like True : [] the type will be specialized to [Bool] in context.
What changes matters is if you want the implementation of a function, or the definition of a value, to depend on its type. If that type is then inferred from context in the normal way, you end up with a function that does something "different" depending on context. Type-dependent implementation is the main purpose of using type classes.
Now, to answer your specific questions:
a way to give get a return type "either Redis or RedisTransaction",
This requires only a variable in the type signature of get, e.g. get :: Key -> f a. The f will be filled in as either Redis or RedisTransaction depending on context.
The type a to be an instance of RedisValue in the Redis context and an instance of RedisStatus in the RedisTransaction context.
Since both a and the context type will be inferred from use, what you're really after here is restricting the possible types, which amounts to expecting a type-checking error if they don't match up. This is another purpose of type classes, and could be implemented with an appropriate class constraint on the context type variable:
get :: (ContextValue (f a)) => Key -> f a
class ContextValue a
instance (RedisValue a) => ContextValue (Redis a)
instance (RedisStatus a) => ContextValue (RedisTransaction a)
Or something like that. But that alone isn't enough for your purposes, because...
A function decode that automagically does the right thing, depending on the context. I assume this must come from a (multi-param) type class.
This implies selecting an implementation for decode based on the type, which means making it part of a type class such as the above ContextValue. How you handle this depends on what the type for decode needs to be--if the result type needs to be something like f String -> f a where f is the monadic context, then you'll probably need something a bit more elaborate, like in dblhelix's answer. If you only need String -> f a, then you could add it to the above ContextValue class directly.

Resources