Using a data type with constrained fields instead of constraints

TL, DR; Expanding the constraint, ad-hoc ...? My route is "forgetful" or uneven

Hi everyone, I am currently trying to make my overloaded function, which can either accept a constraint (in our case, IsString

) or a data type with fields of the same constraint. Here is my code:

{-# LANGUAGE
    OverloadedStrings
  , FlexibleInstances
  , UndecidableInstances
  , InstanceSigs
  , TypeFamilies
#-}

import Data.Monoid

class Bar a where
  bar :: ( IsString b
         , Monoid b ) => a -> b

-- | This instance won't work.
instance ( IsString a
         , Monoid a ) => RelativeUrl a where
  bar :: ( IsString b
         , Monoid b
         , a ~ b ) => a -> b
  bar = id

-- | This is the data type "extending" @IsString@
data Foo a where
  Foo :: ( IsString a, Monoid a ) =>
         a -> Foo a

-- | This is where my dreams end :(
instance Bar (Foo a) where
  bar :: ( IsString b
         , Monoid b
         , a ~ b ) => a -> b
  bar (Foo a) = a

      

I understand that the signatures of the instances are not kosher and why (technically) this won't work, but is there any other way to do this? Ideally, I would like all calls to bar

be taken out of context - such that bar "foo" :: IsString a => a

, without having to bind OverloadedString to a real type.

Is there any other way to achieve this? I am open to crazy ideas :)

+3


source to share


1 answer


A class Bar

is the ability to convert to anything that IsString

. I am assuming the instance Monoid

exists for some efficiency. We can give Bar

and Bar

more colorful names.

class ToStringPlus a where
  toStringPlus :: ( IsString b,
                    Monoid b ) => a -> b

      

You would like to bar "foo" :: IsString a => a

. Included OverloadedStrings

"foo" :: IsString a -> a

. You are asking how to convert a value that is already polymorphic in all instances IsString

to a value that is polymorphic in all instances IsString

. You don't need something like toStringPlus "foo"

that for this , just use "foo"

.

Hiding IsString

If you want to cast a type forall a. IsString a => a

to a datatype, you can do so with GADT. This is not useful at all, since the only possible value for the type forall a. IsString a => a

is fromString x

where x :: String

. This type can contain the same values ​​as and String

no utility String

provides.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}

import Data.String

data AString where
    AString :: (forall a. IsString a => a) -> AString

instance IsString AString where
    fromString x = AString (fromString x)

instance ToStringPlus AString where
    toStringPlus (AString a) = a

      

Something more useful

AString

not very useful as it can only contain the same values ​​as String

. The class ToStringPlus

allows you to convert something with more than String

s, it also allows operations Monoid

mappend

, mconcat

and mempty

. This means that the type forall a. (IsString a, Monoid a) => a

must contain nothing more than String

s.

data MonoidalString where
    MonoidalString :: (forall a. (IsString a, Monoid a) => a) -> MonoidalString

      

MonoidalString

form a Monoid

. Note that mconcat

and mappend

cannot be written in dotless style due to N rank types.

instance Monoid MonoidalString where
    mempty = MonoidalString mempty
    (MonoidalString x) `mappend` (MonoidalString y) = MonoidalString (x `mappend` y)
    mconcat ms = MonoidalString (mconcat (map toStringPlus ms))

      

MonoidalString

can also be instances IsString

and ToStringPlus

in the same way as AString

from the previous section.

instance IsString MonoidalString where
    fromString x = MonoidalString (fromString x)

instance ToStringPlus MonoidalString where
    toStringPlus (MonoidalString a) = a

      



This allows us to make sense of your request in the comment "I'm trying to convert something that's already polymorphic for all instances IsString

and anyone Foo

[to something that's polymorphic ...]". We can combine using operationsMonoid

that are already polymorphic in all instances IsString

, "poly string"

using MonoidalString

to get something that is polymorphic in all instances IsString

and Monoid

.

Given something existing :: MonoidalString

and "poly string" :: IsString a => a

, we can combine them with mappend

.

                                      existing  :: MonoidalString
              "poly string"                     :: IsString a => a
              "poly string" `mappend` existing  :: MonoidalString
toStringPlus ("poly string" `mappend` existing) :: (Monoid b, IsString b) => b

      

We can make a small sample program using this to show all the functions MonoidalString

main = do
    let existing = ("MS" :: MonoidalString)
    putStr . toStringPlus $ mconcat ["poly string", mempty `mappend` " ", existing]

      

Bar again

If you want to make a function Bar

that takes arguments of both types forall a. Ctx a => a

and D

, you can do so while it exists instance Ctx D

. Function type then D -> ...

. It works because it forall a. Ctx a => a

can be used wherever you need it D

.

We can use this to write Bar

for the last example.

bar :: (IsString a, Monoid a) => MonoidalString -> a
bar = toStringPlus

      

We can go to the Bar

polymorphic string "foo" :: IsString a => a

.

    "foo" :: IsString a => a
bar "foo"                    :: (Monoid a, IsString a) => a

      

We can also transfer a monogram MonoidalString

,existing :: MonoidalString

    existing = ("MS" :: MonoidalString)
bar existing                            :: (Monoid a, IsString a) => a

      

+3


source







All Articles