Reputation: 301
I have set of wrapper types FilePath
s (due to restrictions of library I'm using, that create a specific storage based on provided type) and couple of records that I need to obtain from these file-paths.
newtype SourceFilepath = SourceFilepath String deriving (Show)
newtype HeaderFilepath = HeaderFilepath String deriving (Show)
-- ..many more wrappers
data Source =
Source {..}
data Header =
Header {..}
data Metadata =
Metadata {..}
-- .. many more record types
I want to create generalized function loadSource
that accepts some types (actually only filepath wrappers) and based on the provided type produces value of another specific type (Source
, Header
, Metadata
, etc.). Pseudocode:
loadSource :: a -> Compiler b
loadSource (SourceFilepath path) = subload path
loadSource (HeaderFilepath path) = subload path
-- .. other cases for other types
--
-- `a` can be filepath wrappers
-- different `a` can lead to the same `b` sometimes
this function isn't operational I get multiple a’ is a rigid type variable bound by the type signature
and rigid b..
errors.
so I don't have multiple functions like this (code working properly):
subload :: FromJSON b => FilePath -> Compiler b
subload path = <already implemented operational logic>
loadHeader :: HeaderFilepath -> Comiler Header
loadHeader (HeaderPath path) = subload path
loadMetadata :: MetadataFilepath -> Comiler Metadata
loadMetadata (MetadataFilepath path) = subload path
-- .. many more similar functions
How can I achieve this?
Upvotes: 2
Views: 109
Reputation: 51129
There are several ways to accomplish this, though as @DanielWagner says, it's hard to tell what will work best for you without additional detail on what you're trying to achieve.
The simplest is probably to use a type class with an associated type family (or a multiparameter type class with a functional dependency) to map the type of the file path wrapper to the compiler subtype. The type family approach looks like this:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
class Loadable a where
filepath :: a -> String
type Load a
with boilerplatey instances like:
instance Loadable SourceFilepath where
filepath (SourceFilepath pth) = pth
type Load SourceFilepath = Source
instance Loadable HeaderFilepath where
filepath (HeaderFilepath pth) = pth
type Load HeaderFilepath = Header
instance Loadable MetadataFilepath where
filepath (MetadataFilepath pth) = pth
type Load MetadataFilepath = Metadata
Note that there's no problem here mapping two file path wrappers to the same compiler subtype (e.g., type Load HeaderFilepath = Source
would work fine).
Given:
subload :: FromJSON b => FilePath -> Compiler b
subload = ...
the definition of loadSource
is:
loadSource :: (Loadable a, FromJSON (Load a)) => a -> Compiler (Load a)
loadSource = subload . filepath
after which:
> :t loadSource (SourceFilepath "bob")
loadSource (SourceFilepath "bob") :: Compiler Source
> :t loadSource (MetadataFilepath "alice")
loadSource (MetadataFilepath "alice") :: Compiler Metadata
You can substantially reduce boilerplate by parametrizing the wrapper, and -- like @DanielWagner -- I don't understand your comment about the compiler treating them as the same type of file, so you'd need to show us what's going wrong when you try that.
Anyway, my complete source for the original type family solution:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall #-}
import Data.Aeson
import GHC.Generics
newtype SourceFilepath = SourceFilepath String deriving (Show)
newtype HeaderFilepath = HeaderFilepath String deriving (Show)
newtype MetadataFilepath = MetadataFilepath String deriving (Show)
data Source = Source deriving (Generic)
data Header = Header deriving (Generic)
data Metadata = Metadata deriving (Generic)
instance FromJSON Source
instance FromJSON Header
instance FromJSON Metadata
data Compiler b = Compiler
subload :: FromJSON b => FilePath -> Compiler b
subload = undefined
class Loadable a where
filepath :: a -> String
type Load a
instance Loadable SourceFilepath where
filepath (SourceFilepath pth) = pth
type Load SourceFilepath = Source
instance Loadable HeaderFilepath where
filepath (HeaderFilepath pth) = pth
type Load HeaderFilepath = Header
instance Loadable MetadataFilepath where
filepath (MetadataFilepath pth) = pth
type Load MetadataFilepath = Metadata
loadSource :: (Loadable a, FromJSON (Load a)) => a -> Compiler (Load a)
loadSource = subload . filepath
and the complete source for a tagged solution:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall #-}
import Data.Aeson
import GHC.Generics
newtype TypedFilePath a = TypedFilePath FilePath deriving (Show)
data Source = Source deriving (Generic)
data Header = Header deriving (Generic)
data Metadata = Metadata deriving (Generic)
instance FromJSON Source
instance FromJSON Header
instance FromJSON Metadata
data Compiler b = Compiler
subload :: FromJSON b => FilePath -> Compiler b
subload = undefined
type family Load a where
Load Source = Source
Load Header = Header
Load Metadata = Metadata
loadSource :: FromJSON (Load a) => TypedFilePath a -> Compiler (Load a)
loadSource (TypedFilePath fn) = subload fn
Upvotes: 2
Reputation: 153172
Just make your wrapper parameterized, too:
newtype WrappedFilePath a = WrappedFilePath FilePath
loadSource :: FromJSON a => WrappedFilePath a -> Compiler a
loadSource (WrappedFilePath p) = subload fp
You can reuse Tagged
instead of creating the new WrappedFilePath
if you like.
Upvotes: 1