Best practices for talking to an API - haskell

I'm trying to create some bindings for an API in Haskell. I noticed some functions have a tremendous number of arguments, e.g.
myApiFunction :: Key -> Account -> Int -> String -> Int -> Int -> IO (MyType)
It's not necessarily bad, per se, to have this many arguments. But as a user I don't like long argument functions. However, each of these args is absolutely 100% necessary.
Is there a more haskell-ish way to abstract over the common parts of these functions? Everything past account here is used to build a URL, so I would need it available, and what it stands for depends entirely on the function. Certain things are consistent though, like Key and Account, and I'm wondering what the best to abstract over these arguments is.
Thank you!

You can combine these into more descriptive data types:
data Config = Config
{ cKey :: Key
, cAccount :: Account
}
Then maybe have types or newtypes to make the other arguments more descriptive:
-- I have no idea what these actually should be, I'm just making up something
type Count = Int
type Name = String
type Position = (Int, Int)
myApiFunction :: Config -> Count -> Name -> Position -> IO MyType
myApiFunction conf count name (x, y) =
myPreviousApiFunction (cKey conf)
(cAccount conf)
name
name
x
y
If the Config is always needed, then I would recommend working in a Reader monad, which you can easily do as
myApiFunction
:: (MonadReader Config io, MonadIO io)
=> Count -> Name -> Position
-> io MyType
myApiFunction count name (x, y) = do
conf <- ask
liftIO $ myPreviousApiFunction
(cKey conf)
(cAccount conf)
name
name
x
y
This uses the mtl library for monad transformers. If you don't want to have to type that constraint over and over, you can also use the ConstraintKinds extension to alias it:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
...
type ApiCtx io = (MonadReader Config io, MonadIO io)
...
myApiFunction
:: ApiCtx io
=> Count -> Location -> Position
-> io MyType
myApiFunction ...
Depending on your specific application, you could also split it up into multiple function. I've seen plenty of APIs before that had something like
withCount :: ApiCtx io => Count -> io a -> io a
withName :: ApiCtx io => Name -> io a -> io a
withPos :: ApiCtx io => Position -> io a -> io a
(&) :: a -> (a -> b) -> b
request :: ApiCtx io => io MyType
> :set +m -- Multi-line input
> let r = request & withCount 1
| & withName "foo"
| & withPos (1, 2)
> runReaderT r (Config key acct)
These are just a handful of techniques, there are others out there as well but they generally start becoming more complex after this. Others will have different preferences on how to do this, and I'm sure plenty would disagree with me on whether some of these are even good practice (specifically ConstraintKinds, it isn't universally accepted).
If you find yourself having type signatures that are too large a lot, even after applying some of these techniques, then maybe you're approaching the problem from the wrong direction, maybe those functions can be broken down into simpler intermediate steps, maybe some of those arguments can be grouped together logically into more specific data types, maybe you just need a larger record structure to handle setting up complex operations. It's pretty open ended right now.

Related

Haskell: How to write a type of function from a specific type to any type?

In Scala, I could write the following trait:
trait Consumer[A] {
def apply(a: A): Unit
}
And scala would convert whatever I want to Unit, i.e., it would discard the type. Equivalently, I could have said that apply returns Any and ignore the result.
However, in Haskell, if I defined the type as type Consumer = a -> IO (), I wouldn't be able to pass an Int -> IO Int function, as Int isn't ().
There are two ways I know of solving this issue, but none are satisfactory:
Use Data.Functor.void at the call site to manual change IO a to IO (). This is annoying as an API user.
define type Consumer a b = a -> IO b, but then every time I would want to use Consumer in a signature, I would have to carry the useless type b.
Is there any way to define the Consumer type as a function from a to "IO Any"? As far as I know, Haskell does not support something like exists x. a -> IO x.
Using forall results in the opposite of what I want, e.g.,
type Consumer = forall b. a -> IO b
foo :: Int -> IO Int
foo = undefined
bar :: Consumer Int
bar = foo
results in the error:
• Couldn't match type ‘b’ with ‘Int’
‘b’ is a rigid type variable bound by
the type signature for:
bar :: Consumer Int
Expected type: Int -> IO b
Actual type: Int -> IO Int
• In the expression: foo
In an equation for ‘bar’: bar = foo
• Relevant bindings include
bar :: Int -> IO b
Note that I specifically want Consumer to a be type alias, and not a data constructor, as is described here: Haskell function returning existential type. I wouldn't mind if Consumer were a class if anyone knows how to make that work.
To get an existentially-quantified type in Haskell, you need to write down a data declaration (as opposed to a newtype declaration or a type alias declaration, like you used.).
Here's a Consumer type that fits your purposes:
{-# LANGUAGE ExistentialQuantification #-}
data Consumer input = forall output. Consumer { runDiscardingOutput :: input -> IO output }
And, analogously, here is what your example would look like with the new type:
f :: Int -> IO Int
f = undefined
g :: Consumer Int
g = Consumer f
This doesn't really avoid your concerns about client code needing an extra call, though. (I mean, this is no better than exporting a consumer = Data.Functor.void binding from your library.) Also, it complicates how clients will be able to use a consumer, too:
consumer :: Consumer Int
consumer = Consumer (\x -> return [x])
{- This doesn't typecheck -}
main1 :: IO ()
main1 = runIgnoringOutput consumer 4
{- This doesn't typecheck (!!!) -}
main2 :: IO ()
main2 = void (runIgnoringOutput consumer 4)
{- Only this typechecks :( -}
main3 :: IO ()
main3 =
case consumer of
Consumer f -> Data.Functor.void (f 4)
So it would probably make sense to have a apply function in your library that did the dirty work, just as there was an apply function in the Scala library.
apply :: Consumer a -> a -> IO ()
apply (Consumer f) x = void (f x)
I wouldn't mind if Consumer were a class if anyone knows how to make that work.
You can simulate existential types for classes with an associated type family.
But Haskell doesn't allow ambiguous types in classes without using something like a GADT existential wrapper, so you would still have the type information there somewhere.
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses #-}
class Consumer c a where
type Output c
consume :: c -> a -> IO (Output c)
c is necessary here to allow for the reconstruction of the type of Output c, so it is not strictly an existential. But you can now write
{-# LANGUAGE FlexibleInstances, InstanceSigs #-}
instance Consumer (a -> IO b) a where
type Output (a -> IO b) = b
consume :: (a -> IO b) -> a -> IO b
consume = id
This may not fit your use case, because there will not be a type signature that can express Consumer a in a truly existential way. But it is possible to write
... :: (Consumer c a) => c -> ...
(You could also make use of FunctionalDependencies here to clarify the class somewhat.)

Haskell lens: let binding of Traversal'

I'm a bit confused and don't know where to look for the information/explanation of the following "issue" (it's not an issue per se, but more of a situation where I don't understand what is wrong behind the scenes):
I have a monad transformer stack with StateT. At some point in my function I would like to bind a small fraction of my state into the local variable so I can refer to it instead of writing out the whole path to the chunk of the state I'm interested in. Here is what I mean:
{-# LANGUAGE ScopedTypeVariables #-}
...
someFunction :: MyMonad ()
someFunction = do
...
let x :: Traversal' MyState MyDataT = myState.clients.ix clientIdx.someData.ix dataIdx
...
Now this doesn't compile:
Couldn't match type ‘(MyDataT -> f0 MyDataT)
-> MyState -> f0 MyState’
with ‘forall (f :: * -> *).
Control.Applicative.Applicative f =>
(MyDataT -> f MyDataT) -> MyState -> f MyState’
But if I move the referencing of this data chunk into a function then everything compiles ok:
someFunction :: MyMonad ()
someFunction = do
...
let x = clientData clientIdx dataIdx
...
where clientData :: Int -> Int -> Traversal' MyState MyDataT
clientData clientIdx dataIdx = myState.clients.ix clientIdx.someData.ix dataIdx
I'm looking for some kind of information that will help me understand what is going on here, why it happens, so that I'm aware of what I'm doing wrong. Basically I would like to expand my knowledge to understand this use case a bit better.
The key point here is that the annotation should be in a separate line. If we do that, then we have a binding with an explicit type, as far as GHC is concerned.
someFunction :: MyMonad ()
someFunction = do
...
let x :: Traversal' MyState MyDataT
x = myState.clients.ix clientIdx.someData.ix dataIdx
...
What you first tried very rarely works as you intended:
let x :: Traversal' MyState MyDataT = ...
This is a binding without an explicit type; the annotation is inside the left hand side. GHC considers the type of the variable fixed before looking at the right hand side, but the annotation only applies to the left hand side, so GHC just infers a type for the right had side separately, and then tries to match it exactly with the annotation. This makes the type checking fail for all but the simplest non-polymorphic cases.
The right way of putting annotations inside bindings is the following:
let x = ... :: Traversal' MyState MyDataT
Here, GHC first assigns a "malleable" indeterminate type variable to x, then infers a type for the right side informed by the annotation there, then unifies the type of x with it.
This is still a binding without an explicit type, but it works in general if we enable NoMonomorphismRestriction, for reasons detailed in this SO question.

How to store arbitrary values in a recursive structure or how to build a extensible software architecture?

I'm working on a basic UI toolkit and am trying to figure out the overall architecture.
I am considering to use WAI's structure for extensibility. A reduced example of the core structure for my UI:
run :: Application -> IO ()
type Application = Event -> UI -> (Picture, UI)
type Middleware = Application -> Application
In WAI, arbitrary values for Middleware are saved in the vault. I think that this is a bad hack to save arbitary values, because it isn't transparent, but I can't think of a sufficient simple structure to replace this vault to give every Middleware a place to save arbitrary values.
I considered to recursively store tuples in tuples:
run :: (Application, x) -> IO ()
type Application = Event -> UI -> (Picture, UI)
type Middleware y x = (Application, x) -> (Application, (y,x))
Or to only use lazy lists to provide a level on which is no need to separate values (which provides more freedom, but also has more problems):
run :: Application -> IO ()
type Application = [Event -> UI -> (Picture, UI)]
type Middleware = Application -> Application
Actually, I would use a modified lazy list solution. Which other solutions might work?
Note that:
I prefer not to use lens at all.
I know UI -> (Picture, UI) could be defined as State UI Picture .
I'm not aware of a solution regarding monads, transformers or FRP. It would be great to see one.
Lenses provide a general way to reference data type fields so that you can extend or refactor your data set without breaking backwards compatibility. I'll use the lens-family and lens-family-th libraries to illustrate this, since they are lighter dependencies than lens.
Let's begin with a simple record with two fields:
{-# LANGUAGE Template Haskell #-}
import Lens.Family2
import Lens.Family2.TH
data Example = Example
{ _int :: Int
, _str :: String
}
makeLenses ''Example
-- This creates these lenses:
int :: Lens' Example Int
str :: Lens' Example String
Now you can write Stateful code that references fields of your data structure. You can use Lens.Family2.State.Strict for this purpose:
import Lens.Family2.State.Strict
-- Everything here also works for `StateT Example IO`
example :: State Example Bool
example = do
s <- use str -- Read the `String`
str .= s ++ "!" -- Set the `String`
int += 2 -- Modify the `Int`
zoom int $ do -- This sub-`do` block has type: `State Int Int`
m <- get
return (m + 1)
The key thing to note is that I can update my data type, and the above code will still compile. Add a new field to Example and everything will still work:
data Example = Example
{ _int :: Int
, _str :: String
, _char :: Char
}
makeLenses ''Example
int :: Lens' Example Int
str :: Lens' Example String
char :: Lens' Example Char
However, we can actually go a step further and completely refactor our Example type like this:
data Example = Example
{ _example2 :: Example
, _char :: Char
}
data Example2 = Example2
{ _int2 :: Int
, _str2 :: String
}
makeLenses ''Example
char :: Lens' Example Char
example2 :: Lens' Example Example2
makeLenses ''Example2
int2 :: Lens' Example2 Int
str2 :: Lens' Example2 String
Do we have to break our old code? No! All we have to do is add the following two lenses to support backwards compatibility:
int :: Lens' Example Int
int = example2 . int2
str :: Lens' Example Char
str = example2 . str2
Now all the old code still works without any changes, despite the intrusive refactoring of our Example type.
In fact, this works for more than just records. You can do the exact same thing for sum types, too (a.k.a. algebraic data types or enums). For example, suppose we have this type:
data Example3 = A String | B Int
makeTraversals ''Example3
-- This creates these `Traversals'`:
_A :: Traversal' Example3 String
_B :: Traversal' Example3 Int
Many of the things that we did with sum types can similarly be re-expressed in terms of Traversal's. There's a notable exception of pattern matching: it's actually possible to implement pattern matching with totality checking with Traversals, but it's currently verbose.
However, the same point holds: if you express all your sum type operations in terms of Traversal's, then you can greatly refactor your sum type and just update the appropriate Traversal's to preserve backwards compatibility.
Finally: note that the true analog of sum type constructors are Prisms (which let you build values using the constructors in addition to pattern matching). Those are not supported by the lens-family family of libraries, but they are provided by lens and you can implement them yourself using just a profunctors dependency if you want.
Also, if you're wondering what the lens analog of a newtype is, it's an Iso', and that also minimally requires a profunctors dependency.
Also, everything I've said works for reference multiple fields of recursive types (using Folds). Literally anything you can imagine wanting to reference in a data type in a backwards-compatible way is encompassed by the lens library.

Simplest way to join functions of same meaning but different return value type

I'm writing small "hello world" type of program, which groups same files by different "reasons", e.g. same size, same content, same checksum etc.
So, I've got to the point when I want to write a function like this (DuplicateReason is an algebraic type which states the reason why two files are identical):
getDuplicatesByMethods :: (Eq a) => [((FilePath -> a), DuplicateReason)] -> IO [DuplicateGroup]
Where in each tuple, first function would be the one that by file's path returns you some (Eq a) value, like bytestring (with content), or Word32 with checksum, or Int with size.
Clearly, Haskell doesn't like that these functions are of different types, so I need to somehow gather them.
The only way I see it to create a type like
data GroupableValue = GroupString String | GroupInt Int | GroupWord32 Word32
And then to make life easier to make typeclass like
class GroupableValueClass a where
toGroupableValue :: a -> GroupableValue
fromGroupableValue :: GroupableValue -> a
and implement instance for each value I'm going to get.
Question: am I doing it right and (if no) is there a simpler way to solve this task?
Update:
Here's full minimal code that should describe what I want (simplified, with no IO etc.):
data DuplicateGroup = DuplicateGroup
-- method for "same size" -- returns size
m1 :: String -> Int
m1 content = 10
-- method for "same content" -- returns content
m2 :: String -> String
m2 content = "sample content"
groupByMethods :: (Eq a) => [(String -> a)] -> [DuplicateGroup]
groupByMethods predicates = undefined
main :: IO ()
main = do
let groups = (groupByMethods [m1, m2])
return ()
Lists are always homogeneous, so you can't put items with a different a in to the same list (as you noticed). There are several ways to design around this, but I usually prefer using GADTs. For example:
{-# LANGUAGE GADTs #-}
import Data.ByteString (ByteString)
import Data.Word
data DuplicateReason = Size | Checksum | Content
data DuplicateGroup
data DuplicateTest where
DuplicateTest :: Eq a => (FilePath -> IO a) -> DuplicateReason -> DuplicateTest
getSize :: FilePath -> IO Integer
getSize = undefined
getChecksum :: FilePath -> IO Word32
getChecksum = undefined
getContent :: FilePath -> IO ByteString
getContent = undefined
getDuplicatesByMethods :: [DuplicateTest] -> IO [DuplicateGroup]
getDuplicatesByMethods = undefined
This solution still needs a new type, but at least you don't have to specify all cases in advance or create boilerplate type-classes. Now, since the generic type a is essentially "hidden" inside the GADT, you can define a list that contains functions with different return types, wrapped in the DuplicateTest GADT.
getDuplicatesByMethods
[ DuplicateTest getSize Size
, DuplicateTest getChecksum Checksum
, DuplicateTest getContent Content
]
You can also solve this without using any language extensions or introducing new types by simply re-thinking your functions. The main intention is to group files according to some property a, so we could define getDuplicatesByMethods as
getDuplicatesByMethods :: [([FilePath] -> IO [[FilePath]], DuplicateReason)] -> IO [DuplicateGroup]
I.e. we take in a function that groups files according to some criteria. Then we can define a helper function
groupWith :: Eq a => (FilePath -> IO a) -> [FilePath] -> IO [[FilePath]]
and call getDuplicatesByMethods like this
getDuplicatesByMethods
[ (groupWith getSize, Size)
, (groupWith getChecksum, Checksum)
, (groupWith getContent, Content)
]

Haskell data serialization of some data implementing a common type class

Let's start with the following
data A = A String deriving Show
data B = B String deriving Show
class X a where
spooge :: a -> Q
[ Some implementations of X for A and B ]
Now let's say we have custom implementations of show and read, named show' and read' respectively which utilize Show as a serialization mechanism. I want show' and read' to have types
show' :: X a => a -> String
read' :: X a => String -> a
So I can do things like
f :: String -> [Q]
f d = map (\x -> spooge $ read' x) d
Where data could have been
[show' (A "foo"), show' (B "bar")]
In summary, I wanna serialize stuff of various types which share a common typeclass so I can call their separate implementations on the deserialized stuff automatically.
Now, I realize you could write some template haskell which would generate a wrapper type, like
data XWrap = AWrap A | BWrap B deriving (Show)
and serialize the wrapped type which would guarantee that the type info would be stored with it, and that we'd be able to get ourselves back at least an XWrap... but is there a better way using haskell ninja-ery?
EDIT
Okay I need to be more application specific. This is an API. Users will define their As, and Bs and fs as they see fit. I don't ever want them hacking through the rest of the code updating their XWraps, or switches or anything. The most i'm willing to compromise is one list somewhere of all the A, B, etc. in some format. Why?
Here's the application. A is "Download a file from an FTP server." B is "convert from flac to mp3". A contains username, password, port, etc. information. B contains file path information. There could be MANY As and Bs. Hundreds. As many as people are willing to compile into the program. Two was just an example. A and B are Xs, and Xs shall be called "Tickets." Q is IO (). Spooge is runTicket. I want to read the tickets off into their relevant data types and then write generic code that will runTicket on the stuff read' from the stuff on disk. At some point I have to jam type information into the serialized data.
I'd first like to stress for all our happy listeners out there that XWrap is a very good way, and a lot of the time you can write one yourself faster than writing it using Template Haskell.
You say you can get back "at least an XWrap", as if that meant you couldn't recover the types A and B from XWrap or you couldn't use your typeclass on them. Not true! You can even define
separateAB :: [XWrap] -> ([A],[B])
If you didn't want them mixed together, you should serialise them seperately!
This is nicer than haskell ninja-ery; maybe you don't need to handle arbitrary instances, maybe just the ones you made.
Do you really need your original types back? If you feel like using existential types because you just want to spooge your deserialised data, why not either serialise the Q itself, or have some intermediate data type PoisedToSpooge that you serialise, which can deserialise to give you all the data you need for a really good spooging. Why not make it an instance of X too?
You could add a method to your X class that converts to PoisedToSpooge.
You could call it something fun like toPoisedToSpooge, which trips nicely off the tongue, don't you think? :)
Anyway this would remove your typesystem complexity at the same time as resolving the annoying ambiguous type in
f d = map (\x -> spooge $ read' x) d -- oops, the type of read' x depends on the String
You can replace read' with
stringToPoisedToSpoogeToDeserialise :: String -> PoisedToSpooge -- use to deserialise
and define
f d = map (\x -> spooge $ stringToPoisedToSpoogeToDeserialise x) -- no ambiguous type
which we could of course write more succincly as
f = map (spooge.stringToPoisedToSpoogeToDeserialise)
although I recognise the irony here in suggesting making your code more succinct. :)
If what you really want is a heterogeneous list then use existential types. If you want serialization then use Cereal + ByteString. If you want dynamic typing, which is what I think your actual goal is, then use Data.Dynamic. If none of this is what you want, or you want me to expand please press the pound key.
Based on your edit, I don't see any reason a list of thunks won't work. In what way does IO () fail to represent both the operations of "Download a file from an FTP server" and "convert from flac to MP3"?
I'll assume you want to do more things with deserialised Tickets
than run them, because if not you may as well ask the user to supply a bunch of String -> IO()
or similar, nothing clever needed at all.
If so, hooray! It's not often I feel it's appropriate to recommend advanced language features like this.
class Ticketable a where
show' :: a -> String
read' :: String -> Maybe a
runTicket :: a -> IO ()
-- other useful things to do with tickets
This all hinges on the type of read'. read' :: Ticket a => String -> a isn't very useful,
because the only thing it can do with invalid data is crash.
If we change the type to read' :: Ticket a => String -> Maybe a this can allow us to read from disk and
try all the possibilities or fail altogether.
(Alternatively you could use a parser: parse :: Ticket a => String -> Maybe (a,String).)
Let's use a GADT to give us ExistentialQuantification without the syntax and with nicer error messages:
{-# LANGUAGE GADTs #-}
data Ticket where
MkTicket :: Ticketable a => a -> Ticket
showT :: Ticket -> String
showT (MkTicket a) = show' a
runT :: Ticket -> IO()
runT (MkTicket a) = runTicket a
Notice how the MkTicket contstuctor supplies the context Ticketable a for free! GADTs are great.
It would be nice to make Ticket and instance of Ticketable, but that won't work, because there would be
an ambiguous type a hidden in it. Let's take functions that read Ticketable types and make them read
Tickets.
ticketize :: Ticketable a => (String -> Maybe a) -> (String -> Maybe Ticket)
ticketize = ((.).fmap) MkTicket -- a little pointfree fun
You could use some unusual sentinel string such as
"\n-+-+-+-+-+-Ticket-+-+-+-Border-+-+-+-+-+-+-+-\n" to separate your serialised data or better, use separate files
altogether. For this example, I'll just use "\n" as the separator.
readTickets :: [String -> Maybe Ticket] -> String -> [Maybe Ticket]
readTickets readers xs = map (foldr orelse (const Nothing) readers) (lines xs)
orelse :: (a -> Maybe b) -> (a -> Maybe b) -> (a -> Maybe b)
(f `orelse` g) x = case f x of
Nothing -> g x
just_y -> just_y
Now let's get rid of the Justs and ignore the Nothings:
runAll :: [String -> Maybe Ticket] -> String -> IO ()
runAll ps xs = mapM_ runT . catMaybes $ readTickets ps xs
Let's make a trivial ticket that just prints the contents of some directory
newtype Dir = Dir {unDir :: FilePath} deriving Show
readDir xs = let (front,back) = splitAt 4 xs in
if front == "dir:" then Just $ Dir back else Nothing
instance Ticketable Dir where
show' (Dir p) = "dir:"++show p
read' = readDir
runTicket (Dir p) = doesDirectoryExist p >>= flip when
(getDirectoryContents >=> mapM_ putStrLn $ p)
and an even more trivial ticket
data HelloWorld = HelloWorld deriving Show
readHW "HelloWorld" = Just HelloWorld
readHW _ = Nothing
instance Ticketable HelloWorld where
show' HelloWorld = "HelloWorld"
read' = readHW
runTicket HelloWorld = putStrLn "Hello World!"
and then put it all together:
myreaders = [ticketize readDir,ticketize readHW]
main = runAll myreaders $ unlines ["HelloWorld",".","HelloWorld","..",",HelloWorld"]
Just use Either. Your users don't even have to wrap it themselves. You have your deserializer wrap it in the Either for you. I don't know exactly what your serialization protocol is, but I assume that you have some way to detect which kind of request, and the following example assumes the first byte distinguishes the two requests:
deserializeRequest :: IO (Either A B)
deserializeRequest = do
byte <- get1stByte
case byte of
0 -> do
...
return $ Left $ A <A's fields>
1 -> do
...
return $ Right $ B <B's fields>
Then you don't even need to type-class spooge. Just make it a function of Either A B:
spooge :: Either A B -> Q

Resources