Saurabh Nanda
Saurabh Nanda

Reputation: 6793

How to get an enum constructor from a string?

Following up from my previous question I found the generic-deriving package which seems to have a lot of the building blocks that I need. Implementing a gEnumToString function was reduced to a one-liner. However, I'm running into problems with the gEnumFromString function:

{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

import Text.Read
import GHC.Generics
import Generics.Deriving
import Control.Lens
import Data.Default as DD
import           Data.Aeson.Casing
import Data.Aeson.Types (camelTo2)

data Options = Options
  {
    optConstructorTagModifier :: String -> String
  } deriving (Generic)

instance DD.Default Options where
  def = Options
    {
      optConstructorTagModifier = (camelTo2 '_')
    }

makeLensesWith abbreviatedFields ''Options

gEnumToString :: (ConNames (Rep a), Generic a) => Options -> a -> String
gEnumToString opt x = (opt ^. constructorTagModifier) $ conNameOf x

gEnumFromString :: forall a . (Generic a, Enum' (Rep a), ConNames (Rep a))
                => Options -> String -> Maybe a
gEnumFromString opt s = lookup s lookupTable
  where
    lookupTable :: [(String, a)]
    lookupTable = (zipWith (,) (conNames undefined)  genumDefault)

This code doesn't compile with the following errors. Even though I've tried constraining the type of conNames undefined by using ScopedTypeVariables and explicitly providing a forall a (as mentioned by one of the suggestions given in the answers). What am I doing wrong?

   168  33 error           error:
     • Could not deduce (Generic a0) arising from a use of ‘conNames’
       from the context: (Generic a, Enum' (Rep a), ConNames (Rep a))
         bound by the type signature for:
                    gEnumFromString :: (Generic a, Enum' (Rep a), ConNames (Rep a)) =>
                                       Options -> String -> Maybe a
         at /Users/saurabhnanda/projects/vl-haskell/.stack-work/intero/intero784UVH.hs:(163,1)-(164,47)
       The type variable ‘a0’ is ambiguous
       These potential instances exist:
         instance Generic (Either a b) -- Defined in ‘GHC.Generics’
         instance forall a k (b :: k). Generic (Const a b)
           -- Defined in ‘Data.Functor.Const’
         instance Generic (Identity a) -- Defined in ‘Data.Functor.Identity’
         ...plus 31 others
         ...plus 201 instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the second argument of ‘zipWith’, namely
         ‘(conNames undefined)’
       In the expression: (zipWith (,) (conNames undefined) genumDefault)
       In an equation for ‘lookupTable’:
           lookupTable = (zipWith (,) (conNames undefined) genumDefault) (intero)

Upvotes: 0

Views: 341

Answers (1)

chi
chi

Reputation: 116139

To make type variables in scope, leveraging the extension ScopedTypeVariables, you need an explicit forall a..

E.g.

gEnumFromString :: forall a. (Generic a, Enum' (Rep a), ConNames (Rep a))
                => Options -> String -> Maybe a
gEnumFromString opt s = lookup s lookupTable
  where
    lookupTable :: [(String, a)]
    lookupTable = zipWith (,) (conNames (undefined :: a))  genumDefault

There is no need to repeat the type constraints, since these are "carried" by a anyway.

Upvotes: 2

Related Questions