Hide a constructor but not the type on import - haskell

I've got an internal module I'd like to provide an external API for
module Positive.Internal where
newtype Positive a = Positive { getPositive :: a }
deriving (Eq, Ord)
-- smart constructor
toPositive :: (Num a, Ord a) => a -> Maybe (Positive a)
toPositive a | a <= 0 = Nothing
| otherwise = Just $ Positive a
-- ...
I want to hide the dumb constructor, and replace it with a unidirectional
pattern so users can still pattern match values, they just have to use the smart constructor to use new values.
Since I want the pattern and the dumb constructor to use the same name, I need to hide the dumb constructor to prevent namespace clashes.
However, since the dumb constructor and the type share names, it's a little tricky to import the everything BUT the dumb constructor.
Currently I'm doing this, which works ok:
{-# LANGUAGE PatternSynonyms #-}
module Positive
( module Positive.Internal, pattern Positive
) where
import Positive.Internal (Positive())
import Positive.Internal hiding (Positive)
import qualified Positive.Internal as Internal
pattern Positive :: a -> Positive a
pattern Positive a <- Internal.Positive a
I could simplify my imports by just using the qualified import, but I'm curious.
Is there a way to, in a single import statement, import all of Positive.Internal except the dumb constructor?
I tried hiding (Positive(Positive)), but that hid both the type and the dumb constructor. I've poked about the wiki, but I haven't noticed any way to differentiate between constructors and types in hiding lists.

Correct me if I am wrong, but I am almost certain this is what you are looking for:
{-# LANGUAGE PatternSynonyms #-}
module Positive
( module Positive.Internal, pattern Positive, foo
) where
import Positive.Internal hiding (pattern Positive)
import qualified Positive.Internal as Internal (pattern Positive)
pattern Positive :: a -> Positive a
pattern Positive a <- Internal.Positive a
foo :: Positive Int
foo = Internal.Positive 5
Internal module stays the same way as it is defined so far. And for the sake of example:
module Negative where
import Positive
bar :: Maybe Int
bar = getPositive <$> toPositive 6
Let's double check in GHCi:
Prelude> :load Negative
[1 of 3] Compiling Positive.Internal ( Positive/Internal.hs, interpreted )
[2 of 3] Compiling Positive ( Positive.hs, interpreted )
[3 of 3] Compiling Negative ( Negative.hs, interpreted )
Ok, modules loaded: Negative, Positive, Positive.Internal.
*Negative> bar
Just 6
*Negative> getPositive foo
5
*Negative> :i Positive
newtype Positive a = Positive.Internal.Positive {getPositive :: a}
-- Defined at Positive/Internal.hs:3:1
instance [safe] Ord a => Ord (Positive a)
-- Defined at Positive/Internal.hs:4:17
instance [safe] Eq a => Eq (Positive a)
-- Defined at Positive/Internal.hs:4:13
*Negative> :t Positive
<interactive>:1:1: error:
• non-bidirectional pattern synonym ‘Positive’ used in an expression
• In the expression: Positive

Related

How can I write COMPLETE pragmas for types with many constructors?

Suppose I have a type with many constructors and a few pattern synonyms. I'd like to use pattern synonyms to replace a few of the constructors. How can I write the necessary COMPLETE pragma(s) without having to write out all the constructors by hand and risk falling behind if more are added?
Using the th-abstraction package, this is quite simple. Some throat clearing:
import Language.Haskell.TH.Datatype (DatatypeInfo (..), ConstructorInfo(..), reifyDatatype)
import Language.Haskell.TH (Q, Dec, Name, pragCompleteD)
import Data.List ((\\))
Using reifyDatatype, we can get info about a type, and extract a list of the names of its constructors. Then we simply need to add on the patterns we want and remove the constructors we don't want.
-- | Produce a #COMPLETE# pragma for a type with many constructors,
-- without having to list them all out.
--
-- #completeWithButWithout ''T ['P] ['C1, 'C2]# produces a #COMPLETE#
-- pragma stating that pattern matching on the type #T# is complete with
-- with the pattern #P# and with all the constructors of #T# other than
-- #C1# and #C2#.
completeWithButWithout :: Name -> [Name] -> [Name] -> Q [Dec]
completeWithButWithout ty extra_patterns excl_constrs = do
di <- reifyDatatype ty
let constrs = map constructorName (datatypeCons di)
(:[]) <$> pragCompleteD (extra_patterns ++ (constrs \\ excl_constrs))
(Just ty)
Now the module defining the datatype just needs to import this one, and say
data Foo = Bar' Int | Baz | Quux | ...
pattern Bar :: Char -> Foo
$(completeWithButWithout ''Foo ['Bar] ['Bar'])
I recommend invoking completeWithButWithout at the very end of the module, to prevent the splice from splitting the module.

Limit a number to a range (Haskell)

I am exposing a function which takes two parameters, one is a minimum bound and the other is a maximum bound. How can I ensure, using types, that for example the minimum bound is not greater than the maximum bound?
I want to avoid creating a smart constructor and returning a Maybe because it would make the whole usage more cumbersome.
Thank you
This doesn't exactly answer your question, but one approach that sometimes works is to change your interpretation of your type. For example, instead of
data Range = {lo :: Integer, hi :: Integer}
you could use
data Range = {lo :: Integer, size :: Natural}
This way, there's no way to represent an invalid range.
This solution uses dependent types (and might be too heavyweight, check if dfeuer's answer is enough for your needs).
The solution makes use of the GHC.TypeLits module from base, and also of the typelits-witnesses package.
Here is a difference function that takes two integer arguments (known statically) and complains at compile-time when the first number is greater than the second:
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language DataKinds #-}
{-# language ScopedTypeVariables #-}
import GHC.TypeLits
import GHC.TypeLits.Compare
import Data.Type.Equality
import Data.Proxy
import Control.Applicative
difference :: forall n m. (KnownNat n,KnownNat m,n <= m)
=> Proxy n
-> Proxy m
-> Integer
difference pn pm = natVal pm - natVal pn
We can check it from GHCi:
ghci> import Data.Proxy
ghci> :set -XTypeApplications
ghci> :set -XDataKinds
ghci> difference (Proxy #2) (Proxy #7)
5
ghci> difference (Proxy #7) (Proxy #2)
** TYPE ERROR **
But what if we want to use the function with values determined at run time? Say, values that we read from console, or from a file?
main :: IO ()
main = do
case (,) <$> someNatVal 2 <*> someNatVal 7 of
Just (SomeNat proxyn,SomeNat proxym) ->
case isLE proxyn proxym of
Just Refl -> print $ difference proxyn proxym
Nothing -> error "first number not less or equal"
Nothing ->
error "could not bring KnownNat into scope"
In this case, we use functions like someNatVal and isLE. These functions might fail with Nothing. If they succeed, however, they return a value that "witnesses" some constraint. And by pattern-matching on the witness, we bring that constraint into scope (this works because the witness is a GADT).
In the example, the Just (SomeNat proxyn,SomeNat proxym) pattern match brings KnownNat constraints for the two arguments into scope. And the Just Refl pattern match brings the n <= m constraint into scope. Only then we can call our difference function.
So, in a way, we have shifted all the busywork of ensuring that the arguments satisfy the required preconditions out of the function itself.
What you're asking for is dependent types. There is a nice tutorial on it in
https://www.schoolofhaskell.com/user/konn/prove-your-haskell-for-great-safety/dependent-types-in-haskell
Although I don't know how friendly it will be. Do note that dependent typing was improved in GHC 8.0 but I have no experience in that area. I would make sure you're comfortable using template Haskell if you don't want it to be cumbersome.
You needn't invoke the Maybe type to take advantage of 'smart constructors'. If you like, you may accept constructors of either form (min,max) or (max,min) and still create a data type which correctly interprets which is which.
For instance, you could make a little module:
module RangeMinMax (
Range,
makeRange
)
where
data Range = Range (Integer,Integer)
deriving Show
makeRange a b = Range (min a b, max a b)
And now when you create a Range using makeRange, the 2-tuple will automatically be arranged so it's in the form (min,max). Note that the constructor for Range is not exported, so the user of the module is unable to create an invalid Range-- you just need to make sure that you create valid ones in the this module.

Haskell Import error: Not in scope

I have written this code:
import GHC.Float
next :: GHC.Float -> GHC.Float-> GHC.Float
next n x = (x + n / x) / 2
And I am getting the following error:
numerical.hs:3:9:
Not in scope: type constructor or class `GHC.Float'
numerical.hs:3:22:
Not in scope: type constructor or class `GHC.Float'
numerical.hs:3:34:
Not in scope: type constructor or class `GHC.Float'
The module imports without any problem, so I'm not sure if I'm referring to it with the wrong name or if the standard Float module is the same as the IEEE GHC.Float one and there's no need to explicitly import it.
I tried doing an import GHC.Float as Fl with no success--got the same type error on Fl.
I'm just starting Haskell (obviously), so any help is appreciated!
You don't have to import GHC.Float manually, you can just write Float, like so
next :: Float -> Float -> Float
next n x = (x + n / x) / 2
GHC implicitly imports a module called Prelude in every source file you have. Prelude includes a lot of handy types, functions, and other things that are used as the "built-ins" of the language. Types like Int, Float, Maybe, IO, and functions like head, +, /, and more.
You can test to see if a floating point number is an IEEE floating point with the function isIEEE from the GHC.Float module:
import GHC.Float
main = do
putStr "1.0 is an IEEE floating point: "
print $ isIEEE (1.0 :: Float)
If you run this, it will print True
I should have also mentioned that the reason why your code didn't compile earlier is because when you import a module with just import, everything from it comes into scope. You can force it to be qualified by using import qualified, here's a few examples:
import GHC.Float -- Everything now in scope
import qualified Data.Maybe -- Have to use full name
import qualified Data.List as L -- aliased to L
main = do
-- Don't have to type GHC.Float.isIEEE
print $ isIEEE (1.0 :: Float)
-- Have to use full name
print $ Data.Maybe.isJust $ Nothing
-- Uses aliased name
print $ L.sort [1, 4, 2, 5, 3]

Semantics for GHC extension allowing constraints on methods (-XConstrainedClassMethods)

The following is quoted from the GHC user guide (Haskell Platform 2012.4.0.0)...
7.6.1.3. Class method types
Haskell 98 prohibits class method types to mention constraints on the class type variable, thus:
class Seq s a where
fromList :: [a] -> s a
elem :: Eq a => a -> s a -> Bool
The type of elem is illegal in Haskell 98, because it contains the constraint Eq a, constrains only the class type variable (in this case a). GHC lifts this restriction (flag -XConstrainedClassMethods).
However, I don't see any explanation of what this means. I can see two possibilities...
The Seq type class implicitly gains the Eq a constraint from elem.
The elem method cannot be used for type class Seq in cases where a is not a member of class Eq (or where it is a member, but that's unknown where elem is used).
I strongly suspect (2) because it seems potentially useful whereas (1) seems useless. (2) basically allows methods to be defined for cases where they can be supported, without limiting the typeclass to only being instanced for those cases.
The example seems to motivate exactly this - the idea being that elem is often a useful operation for sequences, too valuable to live without, yet we also want to support those sequences where elem is unsupportable, such as sequences of functions.
Am I right, or have I missed something? What are the semantics for this extension?
NOTE: it seems like there is a bug in GHC >= 7 that makes GHC accept constrained class methods even in Haskell 98 mode.
Additionally, the example from the manual is always accepted when MultiParamTypeClasses are enabled, regardless of whether the ConstrainedMethodTypes extension is on (also likely a bug).
In the type of elem:
elem :: Eq a => a -> s a -> Bool
a and s are class type variables, and Eq a is a constraint on the class type variable a. As the manual says, Haskell 98 prohibits such constraints (FWIW, it also prohibits multi-parameter type classes). Therefore, the following code shouldn't be accepted in the Haskell 98 mode (and I think it's also prohibited in Haskell 2010):
class Compare a where
comp :: Eq a => a -> a -> Bool
And indeed, GHC 6.12.1 rejects it:
Prelude> :load Test.hs
[1 of 1] Compiling Main ( Test.hs, interpreted )
Test.hs:3:0:
All of the type variables in the constraint `Eq a'
are already in scope (at least one must be universally quantified here)
(Use -XFlexibleContexts to lift this restriction)
When checking the class method: comp :: (Eq a) => a -> a -> Bool
In the class declaration for `Compare'
Failed, modules loaded: none.
Prelude> :set -XConstrainedClassMethods
Prelude> :load Test.hs
[1 of 1] Compiling Main ( Test.hs, interpreted )
Ok, modules loaded: Main.
The idea is that superclass constraints should be used instead:
class (Eq a) => Compare a where
comp :: a -> a -> Bool
Regarding semantics, you can easily check whether a class method constraint implicitly adds a superclass constraint with the following code:
{-# LANGUAGE ConstrainedClassMethods #-}
module Main where
class Compare a where
comp :: (Eq a) => a -> a -> Bool
someMethod :: a -> a -> a
data A = A deriving Show
data B = B deriving (Show,Eq)
instance Compare A where
comp = undefined
someMethod A A = A
instance Compare B where
comp = (==)
someMethod B B = B
Testing with GHC 6.12.1:
*Main> :load Test.hs
[1 of 1] Compiling Main ( Test.hs, interpreted )
Ok, modules loaded: Main.
*Main> comp A
<interactive>:1:0:
No instance for (Eq A)
arising from a use of `comp' at <interactive>:1:0-5
Possible fix: add an instance declaration for (Eq A)
In the expression: comp A
In the definition of `it': it = comp A
*Main> someMethod A A
A
*Main> comp B B
True
Answer: no, it doesn't. The constraint applies only to the method that has a constrained type. So you are right, it's the possibility #2.

Overriding fromInteger in Haskell

So I like Haskell, but am dissatisfied with the Num class.
So I want to make my own typeclass hierarchic for algebraic types.
The problem is, even if I import Prelude hiding Num and everything associated with it, still the only way to make the literal 1 have type t is to make t instance Num.
I would love to make my own fromInteger class and leave Num out of the picture entirely, like this
import Prelude hiding (everything having to do with Num)
import qualified Prelude (everything having to do with Num)
class (Eq fi) => FromInteger fi where
fromInteger :: Integral -> fi
foo :: (FromInteger fi) => fi -> String
foo 1 = "that was a one"
foo 0 = "that was a zero"
foo n = "that was neither zero nor one"
and then I would implement fromInteger appropriately for brand new types and never have to say anything about Num.
Is there a way to tell the parser to use a different fromInteger method?
Thanks!
You are looking for GHC's RebindableSyntax extension.
Enable it by putting
{-# LANGUAGE RebindableSyntax #-}
at the top of your source file.

Resources