Get rid of the dummy values
This commit is contained in:
		
							parent
							
								
									424a688d15
								
							
						
					
					
						commit
						08fc0f30e4
					
				| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE GADTs #-} | ||||||
| {-# LANGUAGE FunctionalDependencies #-} | {-# LANGUAGE FunctionalDependencies #-} | ||||||
| module Function | module Function | ||||||
|   ( concatStrings |   ( concatStrings | ||||||
| @ -78,19 +79,19 @@ lowerString :: TokenableTo String a => a -> DepGenM (Token String) | |||||||
| lowerString a = runFunction LowerString =<< toToken a | lowerString a = runFunction LowerString =<< toToken a | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| class WitnessFor w t | w -> t where | class (Show w, Lift w) => WitnessFor w t | w -> t | ||||||
|   emptyValue :: w -> t |  | ||||||
| 
 | 
 | ||||||
| data StringType = StringType | data StringType = StringType deriving (Show, Lift) | ||||||
| instance WitnessFor StringType String where | instance WitnessFor StringType String | ||||||
|   emptyValue StringType = "" |  | ||||||
| 
 | 
 | ||||||
| data ElemOf a = ElemOf a deriving (Show, Lift) | data ElemOf a where ElemOf :: WitnessFor w a => w -> ElemOf a | ||||||
|  | deriving instance Show (ElemOf a) | ||||||
|  | deriving instance Lift (ElemOf a) | ||||||
| instance (Show a, Lift a, Valuable a, Eq a) => IsFunction (ElemOf a) (a, [a]) Bool where | instance (Show a, Lift a, Valuable a, Eq a) => IsFunction (ElemOf a) (a, [a]) Bool where | ||||||
|   evalFunction (ElemOf _) (y, ys) = y `elem` ys |   evalFunction (ElemOf _) (y, ys) = y `elem` ys | ||||||
| 
 | 
 | ||||||
| elemOf :: (Show t, Lift t, Valuable t, Eq t, TokenableTo t a, TokenableTo [t] b, WitnessFor w t) => w -> a -> b -> DepGenM (Token Bool) | elemOf :: (Show t, Lift t, Valuable t, Eq t, TokenableTo t a, TokenableTo [t] b, WitnessFor w t) => w -> a -> b -> DepGenM (Token Bool) | ||||||
| elemOf witness a b = runFunction (ElemOf (emptyValue witness)) =<< toTupleToken a b | elemOf witness a b = runFunction (ElemOf witness) =<< toTupleToken a b | ||||||
| 
 | 
 | ||||||
| elemOfString :: (TokenableTo String a, TokenableTo [String] b) => a -> b -> DepGenM (Token Bool) | elemOfString :: (TokenableTo String a, TokenableTo [String] b) => a -> b -> DepGenM (Token Bool) | ||||||
| elemOfString = elemOf StringType | elemOfString = elemOf StringType | ||||||
|  | |||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user